OSDN Git Service

2007-09-26 Thomas Quinot <quinot@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / exp_ch11.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             E X P _ C H 1 1                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2007, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license.          --
20 --                                                                          --
21 -- GNAT was originally developed  by the GNAT team at  New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
23 --                                                                          --
24 ------------------------------------------------------------------------------
25
26 with Atree;    use Atree;
27 with Casing;   use Casing;
28 with Debug;    use Debug;
29 with Einfo;    use Einfo;
30 with Elists;   use Elists;
31 with Errout;   use Errout;
32 with Exp_Ch7;  use Exp_Ch7;
33 with Exp_Util; use Exp_Util;
34 with Namet;    use Namet;
35 with Nlists;   use Nlists;
36 with Nmake;    use Nmake;
37 with Opt;      use Opt;
38 with Rtsfind;  use Rtsfind;
39 with Restrict; use Restrict;
40 with Rident;   use Rident;
41 with Sem;      use Sem;
42 with Sem_Ch8;  use Sem_Ch8;
43 with Sem_Res;  use Sem_Res;
44 with Sem_Util; use Sem_Util;
45 with Sinfo;    use Sinfo;
46 with Sinput;   use Sinput;
47 with Snames;   use Snames;
48 with Stand;    use Stand;
49 with Stringt;  use Stringt;
50 with Targparm; use Targparm;
51 with Tbuild;   use Tbuild;
52 with Uintp;    use Uintp;
53
54 package body Exp_Ch11 is
55
56    -----------------------
57    -- Local Subprograms --
58    -----------------------
59
60    procedure Warn_No_Exception_Propagation_Active (N : Node_Id);
61    --  Generates warning that pragma Restrictions (No_Exception_Propagation)
62    --  is in effect. Caller then generates appropriate continuation message.
63    --  N is the node on which the warning is placed.
64
65    procedure Warn_If_No_Propagation (N : Node_Id);
66    --  Called for an exception raise that is not a local raise (and thus can
67    --  not be optimized to a goto. Issues warning if No_Exception_Propagation
68    --  restriction is set. N is the node for the raise or equivalent call.
69
70    ---------------------------
71    -- Expand_At_End_Handler --
72    ---------------------------
73
74    --  For a handled statement sequence that has a cleanup (At_End_Proc
75    --  field set), an exception handler of the following form is required:
76
77    --     exception
78    --       when all others =>
79    --          cleanup call
80    --          raise;
81
82    --  Note: this exception handler is treated rather specially by
83    --  subsequent expansion in two respects:
84
85    --    The normal call to Undefer_Abort is omitted
86    --    The raise call does not do Defer_Abort
87
88    --  This is because the current tasking code seems to assume that
89    --  the call to the cleanup routine that is made from an exception
90    --  handler for the abort signal is called with aborts deferred.
91
92    --  This expansion is only done if we have front end exception handling.
93    --  If we have back end exception handling, then the AT END handler is
94    --  left alone, and cleanups (including the exceptional case) are handled
95    --  by the back end.
96
97    --  In the front end case, the exception handler described above handles
98    --  the exceptional case. The AT END handler is left in the generated tree
99    --  and the code generator (e.g. gigi) must still handle proper generation
100    --  of cleanup calls for the non-exceptional case.
101
102    procedure Expand_At_End_Handler (HSS : Node_Id; Block : Node_Id) is
103       Clean   : constant Entity_Id  := Entity (At_End_Proc (HSS));
104       Loc     : constant Source_Ptr := Sloc (Clean);
105       Ohandle : Node_Id;
106       Stmnts  : List_Id;
107
108    begin
109       pragma Assert (Present (Clean));
110       pragma Assert (No (Exception_Handlers (HSS)));
111
112       --  Don't expand if back end exception handling active
113
114       if Exception_Mechanism = Back_End_Exceptions then
115          return;
116       end if;
117
118       --  Don't expand an At End handler if we have already had configurable
119       --  run-time violations, since likely this will just be a matter of
120       --  generating useless cascaded messages
121
122       if Configurable_Run_Time_Violations > 0 then
123          return;
124       end if;
125
126       --  Don't expand an At End handler if we are not allowing exceptions
127       --  or if exceptions are transformed into local gotos, and never
128       --  propagated (No_Exception_Propagation).
129
130       if No_Exception_Handlers_Set then
131          return;
132       end if;
133
134       if Present (Block) then
135          Push_Scope (Block);
136       end if;
137
138       Ohandle :=
139         Make_Others_Choice (Loc);
140       Set_All_Others (Ohandle);
141
142       Stmnts := New_List (
143         Make_Procedure_Call_Statement (Loc,
144           Name => New_Occurrence_Of (Clean, Loc)));
145
146       --  Avoid generation of raise stmt if compiling with no exceptions
147       --  propagation
148
149       if not Restriction_Active (No_Exception_Propagation) then
150          Append_To (Stmnts,
151            Make_Raise_Statement (Loc));
152       end if;
153
154       Set_Exception_Handlers (HSS, New_List (
155         Make_Implicit_Exception_Handler (Loc,
156           Exception_Choices => New_List (Ohandle),
157           Statements        => Stmnts)));
158
159       Analyze_List (Stmnts, Suppress => All_Checks);
160       Expand_Exception_Handlers (HSS);
161
162       if Present (Block) then
163          Pop_Scope;
164       end if;
165    end Expand_At_End_Handler;
166
167    -------------------------------
168    -- Expand_Exception_Handlers --
169    -------------------------------
170
171    procedure Expand_Exception_Handlers (HSS : Node_Id) is
172       Handlrs       : constant List_Id    := Exception_Handlers (HSS);
173       Loc           : constant Source_Ptr := Sloc (HSS);
174       Handler       : Node_Id;
175       Others_Choice : Boolean;
176       Obj_Decl      : Node_Id;
177       Next_Handler  : Node_Id;
178
179       procedure Expand_Local_Exception_Handlers;
180       --  This procedure handles the expansion of exception handlers for the
181       --  optimization of local raise statements into goto statements.
182
183       procedure Prepend_Call_To_Handler
184         (Proc : RE_Id;
185          Args : List_Id := No_List);
186       --  Routine to prepend a call to the procedure referenced by Proc at
187       --  the start of the handler code for the current Handler.
188
189       procedure Replace_Raise_By_Goto (Raise_S : Node_Id; Goto_L1 : Node_Id);
190       --  Raise_S is a raise statement (possibly expanded, and possibly of the
191       --  form of a Raise_xxx_Error node with a condition. This procedure is
192       --  called to replace the raise action with the (already analyzed) goto
193       --  statement passed as Goto_L1. This procedure also takes care of the
194       --  requirement of inserting a Local_Raise call where possible.
195
196       -------------------------------------
197       -- Expand_Local_Exception_Handlers --
198       -------------------------------------
199
200       --  There are two cases for this transformation. First the case of
201       --  explicit raise statements. For this case, the transformation we do
202       --  looks like this. Right now we have for example (where L1, L2 are
203       --  exception labels)
204
205       --  begin
206       --     ...
207       --     raise_exception (excep1'identity);  -- was raise excep1
208       --     ...
209       --     raise_exception (excep2'identity);  -- was raise excep2
210       --     ...
211       --  exception
212       --     when excep1 =>
213       --        estmts1
214       --     when excep2 =>
215       --        estmts2
216       --  end;
217
218       --  This gets transformed into:
219
220       --  begin
221       --     L1 : label;                        -- marked Exception_Junk
222       --     L2 : label;                        -- marked Exception_Junk
223       --     L3 : label;                        -- marked Exception_Junk
224
225       --     begin                              -- marked Exception_Junk
226       --        ...
227       --        local_raise (excep1'address);   -- was raise excep1
228       --        goto L1;
229       --        ...
230       --        local_raise (excep2'address);   -- was raise excep2
231       --        goto L2;
232       --        ...
233       --     exception
234       --        when excep1 =>
235       --           goto L1;
236       --        when excep2 =>
237       --           goto L2;
238       --     end;
239
240       --     goto L3;        -- skip handler if no raise, marked Exception_Junk
241
242       --     <<L1>>          -- local excep target label, marked Exception_Junk
243       --        begin        -- marked Exception_Junk
244       --           estmts1
245       --        end;
246       --        goto L3;     -- marked Exception_Junk
247
248       --     <<L2>>          -- marked Exception_Junk
249       --        begin        -- marked Exception_Junk
250       --           estmts2
251       --        end;
252       --        goto L3;     -- marked Exception_Junk
253       --     <<L3>>          -- marked Exception_Junk
254       --  end;
255
256       --  Note: the reason we wrap the original statement sequence in an
257       --  inner block is that there may be raise statements within the
258       --  sequence of statements in the handlers, and we must ensure that
259       --  these are properly handled, and in particular, such raise statements
260       --  must not reenter the same exception handlers.
261
262       --  If the restriction No_Exception_Propagation is in effect, then we
263       --  can omit the exception handlers.
264
265       --  begin
266       --     L1 : label;                        -- marked Exception_Junk
267       --     L2 : label;                        -- marked Exception_Junk
268       --     L3 : label;                        -- marked Exception_Junk
269
270       --     begin                              -- marked Exception_Junk
271       --        ...
272       --        local_raise (excep1'address);   -- was raise excep1
273       --        goto L1;
274       --        ...
275       --        local_raise (excep2'address);   -- was raise excep2
276       --        goto L2;
277       --        ...
278       --     end;
279
280       --     goto L3;        -- skip handler if no raise, marked Exception_Junk
281
282       --     <<L1>>          -- local excep target label, marked Exception_Junk
283       --        begin        -- marked Exception_Junk
284       --           estmts1
285       --        end;
286       --        goto L3;     -- marked Exception_Junk
287
288       --     <<L2>>          -- marked Exception_Junk
289       --        begin        -- marked Exception_Junk
290       --           estmts2
291       --        end;
292
293       --     <<L3>>          -- marked Exception_Junk
294       --  end;
295
296       --  The second case is for exceptions generated by the back end in one
297       --  of three situations:
298
299       --    1. Front end generates N_Raise_xxx_Error node
300       --    2. Front end sets Do_xxx_Check flag in subexpression node
301       --    3. Back end detects a situation where an exception is appropriate
302
303       --  In all these cases, the current processing in gigi is to generate a
304       --  call to the appropriate Rcheck_xx routine (where xx encodes both the
305       --  exception message and the exception to be raised, Constraint_Error,
306       --  Program_Error, or Storage_Error.
307
308       --  We could handle some subcases of 1 using the same front end expansion
309       --  into gotos, but even for case 1, we can't handle all cases, since
310       --  generating gotos in the middle of expressions is not possible (it's
311       --  possible at the gigi/gcc level, but not at the level of the GNAT
312       --  tree).
313
314       --  In any case, it seems easier to have a scheme which handles all three
315       --  cases in a uniform manner. So here is how we proceed in this case.
316
317       --  This procedure detects all handlers for these three exceptions,
318       --  Constraint_Error, Program_Error and Storage_Error (including WHEN
319       --  OTHERS handlers that cover one or more of these cases).
320
321       --  If the handler meets the requirements for being the target of a local
322       --  raise, then the front end does the expansion described previously,
323       --  creating a label to be used as a goto target to raise the exception.
324       --  However, no attempt is made in the front end to convert any related
325       --  raise statements into gotos, e.g. all N_Raise_xxx_Error nodes are
326       --  left unchanged and passed to the back end.
327
328       --  Instead, the front end generates two nodes
329
330       --     N_Push_Constraint_Error_Label
331       --     N_Push_Program_Error_Label
332       --     N_Push_Storage_Error_Label
333
334       --       The Push node is generated at the start of the statements
335       --       covered by the handler, and has as a parameter the label to be
336       --       used as the raise target.
337
338       --     N_Pop_Constraint_Error_Label
339       --     N_Pop_Program_Error_Label
340       --     N_Pop_Storage_Error_Label
341
342       --       The Pop node is generated at the end of the covered statements
343       --       and undoes the effect of the preceding corresponding Push node.
344
345       --  In the case where the handler does NOT meet the requirements, the
346       --  front end will still generate the Push and Pop nodes, but the label
347       --  field in the Push node will be empty signifying that for this region
348       --  of code, no optimization is possible.
349
350       --  The back end must maintain three stacks, one for each exception case,
351       --  the Push node pushes an entry onto the corresponding stack, and Pop
352       --  node pops off the entry. Then instead of calling Rcheck_nn, if the
353       --  corresponding top stack entry has an non-empty label, a goto is
354       --  generated. This goto should be preceded by a call to Local_Raise as
355       --  described above.
356
357       --  An example of this transformation is as follows, given:
358
359       --  declare
360       --    A : Integer range 1 .. 10;
361       --  begin
362       --    A := B + C;
363       --  exception
364       --    when Constraint_Error =>
365       --       estmts
366       --  end;
367
368       --  gets transformed to:
369
370       --  declare
371       --    A : Integer range 1 .. 10;
372
373       --  begin
374       --     L1 : label;
375       --     L2 : label;
376
377       --     begin
378       --        %push_constraint_error_label (L1)
379       --        R1b : constant long_long_integer := long_long_integer?(b) +
380       --          long_long_integer?(c);
381       --        [constraint_error when
382       --          not (R1b in -16#8000_0000# .. 16#7FFF_FFFF#)
383       --          "overflow check failed"]
384       --        a := integer?(R1b);
385       --        %pop_constraint_error_Label
386
387       --     exception
388       --        ...
389       --        when constraint_error =>
390       --           goto L1;
391       --     end;
392
393       --     goto L2;       -- skip handler when exception not raised
394       --     <<L1>>         -- target label for local exception
395       --     estmts
396       --     <<L2>>
397       --  end;
398
399       --  Note: the generated labels and goto statements all have the flag
400       --  Exception_Junk set True, so that Sem_Ch6.Check_Returns will ignore
401       --  this generated exception stuff when checking for missing return
402       --  statements (see circuitry in Check_Statement_Sequence).
403
404       --  Note: All of the processing described above occurs only if
405       --  restriction No_Exception_Propagation applies or debug flag .g is
406       --  enabled.
407
408       CE_Locally_Handled : Boolean := False;
409       SE_Locally_Handled : Boolean := False;
410       PE_Locally_Handled : Boolean := False;
411       --  These three flags indicate whether a handler for the corresponding
412       --  exception (CE=Constraint_Error, SE=Storage_Error, PE=Program_Error)
413       --  is present. If so the switch is set to True, the Exception_Label
414       --  field of the corresponding handler is set, and appropriate Push
415       --  and Pop nodes are inserted into the code.
416
417       Local_Expansion_Required : Boolean := False;
418       --  Set True if we have at least one handler requiring local raise
419       --  expansion as described above.
420
421       procedure Expand_Local_Exception_Handlers is
422
423          procedure Add_Exception_Label (H : Node_Id);
424          --  H is an exception handler. First check for an Exception_Label
425          --  already allocated for H. If none, allocate one, set the field in
426          --  the handler node, add the label declaration, and set the flag
427          --  Local_Expansion_Required. Note: if Local_Raise_Not_OK is set
428          --  the call has no effect and Exception_Label is left empty.
429
430          procedure Add_Label_Declaration (L : Entity_Id);
431          --  Add an implicit declaration of the given label to the declaration
432          --  list in the parent of the current sequence of handled statements.
433
434          generic
435             Exc_Locally_Handled : in out Boolean;
436             --  Flag indicating whether a local handler for this exception
437             --  has already been generated.
438
439             with function Make_Push_Label (Loc : Source_Ptr) return Node_Id;
440             --  Function to create a Push_xxx_Label node
441
442             with function Make_Pop_Label (Loc : Source_Ptr) return Node_Id;
443             --  Function to create a Pop_xxx_Label node
444
445          procedure Generate_Push_Pop (H : Node_Id);
446          --  Common code for Generate_Push_Pop_xxx below, used to generate an
447          --  exception label and Push/Pop nodes for Constraint_Error,
448          --  Program_Error, or Storage_Error.
449
450          -------------------------
451          -- Add_Exception_Label --
452          -------------------------
453
454          procedure Add_Exception_Label (H : Node_Id) is
455          begin
456             if No (Exception_Label (H))
457               and then not Local_Raise_Not_OK (H)
458               and then not Special_Exception_Package_Used
459             then
460                Local_Expansion_Required := True;
461
462                declare
463                   L : constant Entity_Id :=
464                         Make_Defining_Identifier (Sloc (H),
465                           Chars => New_Internal_Name ('L'));
466                begin
467                   Set_Exception_Label (H, L);
468                   Add_Label_Declaration (L);
469                end;
470             end if;
471          end Add_Exception_Label;
472
473          ---------------------------
474          -- Add_Label_Declaration --
475          ---------------------------
476
477          procedure Add_Label_Declaration (L : Entity_Id) is
478             P : constant Node_Id := Parent (HSS);
479
480             Decl_L : constant Node_Id :=
481                        Make_Implicit_Label_Declaration (Loc,
482                          Defining_Identifier => L);
483
484          begin
485             if Declarations (P) = No_List then
486                Set_Declarations (P, Empty_List);
487             end if;
488
489             Append (Decl_L, Declarations (P));
490             Analyze (Decl_L);
491          end Add_Label_Declaration;
492
493          -----------------------
494          -- Generate_Push_Pop --
495          -----------------------
496
497          procedure Generate_Push_Pop (H : Node_Id) is
498          begin
499             if Exc_Locally_Handled then
500                return;
501             else
502                Exc_Locally_Handled := True;
503             end if;
504
505             Add_Exception_Label (H);
506
507             declare
508                F : constant Node_Id := First (Statements (HSS));
509                L : constant Node_Id := Last  (Statements (HSS));
510
511                Push : constant Node_Id := Make_Push_Label (Sloc (F));
512                Pop  : constant Node_Id := Make_Pop_Label  (Sloc (L));
513
514             begin
515                --  We make sure that a call to Get_Local_Raise_Call_Entity is
516                --  made during front end processing, so that when we need it
517                --  in the back end, it will already be available and loaded.
518
519                Discard_Node (Get_Local_Raise_Call_Entity);
520
521                --  Prepare and insert Push and Pop nodes
522
523                Set_Exception_Label (Push, Exception_Label (H));
524                Insert_Before (F, Push);
525                Set_Analyzed (Push);
526
527                Insert_After (L, Pop);
528                Set_Analyzed (Pop);
529             end;
530          end Generate_Push_Pop;
531
532          --  Local declarations
533
534          Loc    : constant Source_Ptr := Sloc (HSS);
535          Stmts  : List_Id := No_List;
536          Choice : Node_Id;
537          Excep  : Entity_Id;
538
539          procedure Generate_Push_Pop_For_Constraint_Error is
540            new Generate_Push_Pop
541              (Exc_Locally_Handled => CE_Locally_Handled,
542               Make_Push_Label     => Make_Push_Constraint_Error_Label,
543               Make_Pop_Label      => Make_Pop_Constraint_Error_Label);
544          --  If no Push/Pop has been generated for CE yet, then set the flag
545          --  CE_Locally_Handled, allocate an Exception_Label for handler H (if
546          --  not already done), and generate Push/Pop nodes for the exception
547          --  label at the start and end of the statements of HSS.
548
549          procedure Generate_Push_Pop_For_Program_Error is
550            new Generate_Push_Pop
551              (Exc_Locally_Handled => PE_Locally_Handled,
552               Make_Push_Label     => Make_Push_Program_Error_Label,
553               Make_Pop_Label      => Make_Pop_Program_Error_Label);
554          --  If no Push/Pop has been generated for PE yet, then set the flag
555          --  PE_Locally_Handled, allocate an Exception_Label for handler H (if
556          --  not already done), and generate Push/Pop nodes for the exception
557          --  label at the start and end of the statements of HSS.
558
559          procedure Generate_Push_Pop_For_Storage_Error is
560            new Generate_Push_Pop
561              (Exc_Locally_Handled => SE_Locally_Handled,
562               Make_Push_Label     => Make_Push_Storage_Error_Label,
563               Make_Pop_Label      => Make_Pop_Storage_Error_Label);
564          --  If no Push/Pop has been generated for SE yet, then set the flag
565          --  SE_Locally_Handled, allocate an Exception_Label for handler H (if
566          --  not already done), and generate Push/Pop nodes for the exception
567          --  label at the start and end of the statements of HSS.
568
569       --  Start of processing for Expand_Local_Exception_Handlers
570
571       begin
572          --  No processing if all exception handlers will get removed
573
574          if Debug_Flag_Dot_X then
575             return;
576          end if;
577
578          --  See for each handler if we have any local raises to expand
579
580          Handler := First_Non_Pragma (Handlrs);
581          while Present (Handler) loop
582
583             --  Note, we do not test Local_Raise_Not_OK here, because in the
584             --  case of Push/Pop generation we want to generate push with a
585             --  null label. The Add_Exception_Label routine has no effect if
586             --  Local_Raise_Not_OK is set, so this works as required.
587
588             if Present (Local_Raise_Statements (Handler)) then
589                Add_Exception_Label (Handler);
590             end if;
591
592             --  If we are doing local raise to goto optimization (restriction
593             --  No_Exception_Propagation set or debug flag .g set), then check
594             --  to see if handler handles CE, PE, SE and if so generate the
595             --  appropriate push/pop sequence for the back end.
596
597             if (Debug_Flag_Dot_G
598                  or else Restriction_Active (No_Exception_Propagation))
599               and then Has_Local_Raise (Handler)
600             then
601                Choice := First (Exception_Choices (Handler));
602                while Present (Choice) loop
603                   if Nkind (Choice) = N_Others_Choice
604                     and then not All_Others (Choice)
605                   then
606                      Generate_Push_Pop_For_Constraint_Error (Handler);
607                      Generate_Push_Pop_For_Program_Error    (Handler);
608                      Generate_Push_Pop_For_Storage_Error    (Handler);
609
610                   elsif Is_Entity_Name (Choice) then
611                      Excep := Get_Renamed_Entity (Entity (Choice));
612
613                      if Excep = Standard_Constraint_Error then
614                         Generate_Push_Pop_For_Constraint_Error (Handler);
615                      elsif Excep = Standard_Program_Error then
616                         Generate_Push_Pop_For_Program_Error    (Handler);
617                      elsif Excep = Standard_Storage_Error then
618                         Generate_Push_Pop_For_Storage_Error    (Handler);
619                      end if;
620                   end if;
621
622                   Next (Choice);
623                end loop;
624             end if;
625
626             Next_Non_Pragma (Handler);
627          end loop;
628
629          --  Nothing to do if no handlers requiring the goto transformation
630
631          if not (Local_Expansion_Required) then
632             return;
633          end if;
634
635          --  Prepare to do the transformation
636
637          declare
638             --  L3 is the label to exit the HSS
639
640             L3_Dent : constant Entity_Id :=
641                         Make_Defining_Identifier (Loc,
642                           Chars => New_Internal_Name ('L'));
643
644             Labl_L3 : constant Node_Id :=
645                         Make_Label (Loc,
646                           Identifier => New_Occurrence_Of (L3_Dent, Loc));
647
648             Blk_Stm : Node_Id;
649             Relmt   : Elmt_Id;
650
651          begin
652             Set_Exception_Junk (Labl_L3);
653             Add_Label_Declaration (L3_Dent);
654
655             --  Wrap existing statements and handlers in an inner block
656
657             Blk_Stm :=
658               Make_Block_Statement (Loc,
659                 Handled_Statement_Sequence => Relocate_Node (HSS));
660             Set_Exception_Junk (Blk_Stm);
661
662             Rewrite (HSS,
663               Make_Handled_Sequence_Of_Statements (Loc,
664                 Statements => New_List (Blk_Stm)));
665
666             --  Set block statement as analyzed, we don't want to actually call
667             --  Analyze on this block, it would cause a recursion in exception
668             --  handler processing which would mess things up.
669
670             Set_Analyzed (Blk_Stm);
671
672             --  Now loop through the exception handlers to deal with those that
673             --  are targets of local raise statements.
674
675             Handler := First_Non_Pragma (Handlrs);
676             while Present (Handler) loop
677                if Present (Exception_Label (Handler)) then
678
679                   --  This handler needs the goto expansion
680
681                   declare
682                      Loc : constant Source_Ptr := Sloc (Handler);
683
684                      --  L1 is the start label for this handler
685
686                      L1_Dent : constant Entity_Id := Exception_Label (Handler);
687
688                      Labl_L1 : constant Node_Id :=
689                                  Make_Label (Loc,
690                                    Identifier =>
691                                      New_Occurrence_Of (L1_Dent, Loc));
692
693                      --  Jump to L1 to be used as replacement for the original
694                      --  handler (used in the case where exception propagation
695                      --  may still occur).
696
697                      Name_L1 : constant Node_Id :=
698                                  New_Occurrence_Of (L1_Dent, Loc);
699
700                      Goto_L1 : constant Node_Id :=
701                                  Make_Goto_Statement (Loc,
702                                    Name => Name_L1);
703
704                      --  Jump to L3 to be used at the end of handler
705
706                      Name_L3 : constant Node_Id :=
707                                  New_Occurrence_Of (L3_Dent, Loc);
708
709                      Goto_L3 : constant Node_Id :=
710                                  Make_Goto_Statement (Loc,
711                                    Name => Name_L3);
712
713                      H_Stmts : constant List_Id := Statements (Handler);
714
715                   begin
716                      Set_Exception_Junk (Labl_L1);
717                      Set_Exception_Junk (Goto_L3);
718
719                      --  Note: we do NOT set Exception_Junk in Goto_L1, since
720                      --  this is a real transfer of control that we want the
721                      --  Sem_Ch6.Check_Returns procedure to recognize properly.
722
723                      --  Replace handler by a goto L1. We can mark this as
724                      --  analyzed since it is fully formed, and we don't
725                      --  want it going through any further checks. We save
726                      --  the last statement location in the goto L1 node for
727                      --  the benefit of Sem_Ch6.Check_Returns.
728
729                      Set_Statements (Handler, New_List (Goto_L1));
730                      Set_Analyzed (Goto_L1);
731                      Set_Etype (Name_L1, Standard_Void_Type);
732
733                      --  Now replace all the raise statements by goto L1
734
735                      if Present (Local_Raise_Statements (Handler)) then
736                         Relmt := First_Elmt (Local_Raise_Statements (Handler));
737                         while Present (Relmt) loop
738                            declare
739                               Raise_S : constant Node_Id := Node (Relmt);
740
741                               Name_L1 : constant Node_Id :=
742                                           New_Occurrence_Of (L1_Dent, Loc);
743
744                               Goto_L1 : constant Node_Id :=
745                                           Make_Goto_Statement (Loc,
746                                             Name => Name_L1);
747
748                            begin
749                               --  Replace raise by goto L1
750
751                               Set_Analyzed (Goto_L1);
752                               Set_Etype (Name_L1, Standard_Void_Type);
753                               Replace_Raise_By_Goto (Raise_S, Goto_L1);
754                            end;
755
756                            Next_Elmt (Relmt);
757                         end loop;
758                      end if;
759
760                      --  Add a goto L3 at end of statement list in block. The
761                      --  first time, this is what skips over the exception
762                      --  handlers in the normal case. Subsequent times, it
763                      --  terminates the execution of the previous handler code,
764                      --  and skips subsequent handlers.
765
766                      Stmts := Statements (HSS);
767
768                      Insert_After (Last (Stmts), Goto_L3);
769                      Set_Analyzed (Goto_L3);
770                      Set_Etype (Name_L3, Standard_Void_Type);
771
772                      --  Now we drop the label that marks the handler start,
773                      --  followed by the statements of the handler.
774
775                      Set_Etype (Identifier (Labl_L1), Standard_Void_Type);
776
777                      Insert_After_And_Analyze (Last (Stmts), Labl_L1);
778
779                      declare
780                         Loc : constant Source_Ptr := Sloc (First (H_Stmts));
781                         Blk : constant Node_Id :=
782                                 Make_Block_Statement (Loc,
783                                   Handled_Statement_Sequence =>
784                                     Make_Handled_Sequence_Of_Statements (Loc,
785                                       Statements => H_Stmts));
786                      begin
787                         Set_Exception_Junk (Blk);
788                         Insert_After_And_Analyze (Last (Stmts), Blk);
789                      end;
790                   end;
791
792                   --  Here if we have local raise statements but the handler is
793                   --  not suitable for processing with a local raise. In this
794                   --  case we have to generate possible diagnostics.
795
796                elsif Has_Local_Raise (Handler)
797                  and then Local_Raise_Statements (Handler) /= No_Elist
798                then
799                   Relmt := First_Elmt (Local_Raise_Statements (Handler));
800                   while Present (Relmt) loop
801                      Warn_If_No_Propagation (Node (Relmt));
802                      Next_Elmt (Relmt);
803                   end loop;
804                end if;
805
806                Next (Handler);
807             end loop;
808
809             --  Only remaining step is to drop the L3 label and we are done
810
811             Set_Etype (Identifier (Labl_L3), Standard_Void_Type);
812
813             --  If we had at least one handler, then we drop the label after
814             --  the last statement of that handler.
815
816             if Stmts /= No_List then
817                Insert_After_And_Analyze (Last (Stmts), Labl_L3);
818
819             --  Otherwise we have removed all the handlers (this results from
820             --  use of pragma Restrictions (No_Exception_Propagation), and we
821             --  drop the label at the end of the statements of the HSS.
822
823             else
824                Insert_After_And_Analyze (Last (Statements (HSS)), Labl_L3);
825             end if;
826
827             return;
828          end;
829       end Expand_Local_Exception_Handlers;
830
831       -----------------------------
832       -- Prepend_Call_To_Handler --
833       -----------------------------
834
835       procedure Prepend_Call_To_Handler
836         (Proc : RE_Id;
837          Args : List_Id := No_List)
838       is
839          Ent : constant Entity_Id := RTE (Proc);
840
841       begin
842          --  If we have no Entity, then we are probably in no run time mode
843          --  or some weird error has occured. In either case do do nothing!
844
845          if Present (Ent) then
846             declare
847                Call : constant Node_Id :=
848                         Make_Procedure_Call_Statement (Loc,
849                           Name => New_Occurrence_Of (RTE (Proc), Loc),
850                           Parameter_Associations => Args);
851
852             begin
853                Prepend_To (Statements (Handler), Call);
854                Analyze (Call, Suppress => All_Checks);
855             end;
856          end if;
857       end Prepend_Call_To_Handler;
858
859       ---------------------------
860       -- Replace_Raise_By_Goto --
861       ---------------------------
862
863       procedure Replace_Raise_By_Goto (Raise_S : Node_Id; Goto_L1 : Node_Id) is
864          Loc   : constant Source_Ptr := Sloc (Raise_S);
865          Excep : Entity_Id;
866          LR    : Node_Id;
867          Cond  : Node_Id;
868          Orig  : Node_Id;
869
870       begin
871          --  If we have a null statement, it means that there is no replacement
872          --  needed (typically this results from a suppressed check).
873
874          if Nkind (Raise_S) = N_Null_Statement then
875             return;
876
877          --  Test for Raise_xxx_Error
878
879          elsif Nkind (Raise_S) = N_Raise_Constraint_Error then
880             Excep := Standard_Constraint_Error;
881             Cond  := Condition (Raise_S);
882
883          elsif Nkind (Raise_S) = N_Raise_Storage_Error then
884             Excep := Standard_Storage_Error;
885             Cond := Condition (Raise_S);
886
887          elsif Nkind (Raise_S) = N_Raise_Program_Error then
888             Excep := Standard_Program_Error;
889             Cond := Condition (Raise_S);
890
891             --  The only other possibility is a node that is or used to be a
892             --  simple raise statement.
893
894          else
895             Orig := Original_Node (Raise_S);
896             pragma Assert (Nkind (Orig) = N_Raise_Statement
897                              and then Present (Name (Orig))
898                              and then No (Expression (Orig)));
899             Excep := Entity (Name (Orig));
900             Cond := Empty;
901          end if;
902
903          --  Here Excep is the exception to raise, and Cond is the condition
904          --  First prepare the call to Local_Raise (excep'address).
905
906          if RTE_Available (RE_Local_Raise) then
907             LR :=
908               Make_Procedure_Call_Statement (Loc,
909                 Name => New_Occurrence_Of (RTE (RE_Local_Raise), Loc),
910                 Parameter_Associations => New_List (
911                   Unchecked_Convert_To (RTE (RE_Address),
912                     Make_Attribute_Reference (Loc,
913                       Prefix         => New_Occurrence_Of (Excep, Loc),
914                       Attribute_Name => Name_Identity))));
915
916             --  Use null statement if Local_Raise not available
917
918          else
919             LR :=
920               Make_Null_Statement (Loc);
921          end if;
922
923          --  If there is no condition, we rewrite as
924
925          --    begin
926          --       Local_Raise (excep'Identity);
927          --       goto L1;
928          --    end;
929
930          if No (Cond) then
931             Rewrite (Raise_S,
932               Make_Block_Statement (Loc,
933                 Handled_Statement_Sequence =>
934                   Make_Handled_Sequence_Of_Statements (Loc,
935                     Statements => New_List (LR, Goto_L1))));
936             Set_Exception_Junk (Raise_S);
937
938          --  If there is a condition, we rewrite as
939
940          --    if condition then
941          --       Local_Raise (excep'Identity);
942          --       goto L1;
943          --    end if;
944
945          else
946             Rewrite (Raise_S,
947               Make_If_Statement (Loc,
948                 Condition       => Cond,
949                 Then_Statements => New_List (LR, Goto_L1)));
950          end if;
951
952          Analyze (Raise_S);
953       end Replace_Raise_By_Goto;
954
955    --  Start of processing for Expand_Exception_Handlers
956
957    begin
958       Expand_Local_Exception_Handlers;
959
960       --  Loop through handlers
961
962       Handler := First_Non_Pragma (Handlrs);
963       Handler_Loop : while Present (Handler) loop
964          Next_Handler := Next_Non_Pragma (Handler);
965
966          --  Remove source handler if gnat debug flag N is set
967
968          if Debug_Flag_Dot_X and then Comes_From_Source (Handler) then
969             Remove (Handler);
970
971          --  Remove handler if no exception propagation, generating a warning
972          --  if a source generated handler was not the target of a local raise.
973
974          elsif Restriction_Active (No_Exception_Propagation) then
975             if not Has_Local_Raise (Handler)
976               and then Comes_From_Source (Handler)
977               and then Warn_On_Non_Local_Exception
978             then
979                Warn_No_Exception_Propagation_Active (Handler);
980                Error_Msg_N
981                  ("\?this handler can never be entered, and has been removed",
982                   Handler);
983             end if;
984
985             Remove (Handler);
986
987          --  Exception handler is active and retained and must be processed
988
989          else
990             --  If an exception occurrence is present, then we must declare it
991             --  and initialize it from the value stored in the TSD
992
993             --     declare
994             --        name : Exception_Occurrence;
995             --     begin
996             --        Save_Occurrence (name, Get_Current_Excep.all)
997             --        ...
998             --     end;
999
1000             if Present (Choice_Parameter (Handler)) then
1001                declare
1002                   Cparm : constant Entity_Id  := Choice_Parameter (Handler);
1003                   Clc   : constant Source_Ptr := Sloc (Cparm);
1004                   Save  : Node_Id;
1005
1006                begin
1007                   Save :=
1008                     Make_Procedure_Call_Statement (Loc,
1009                       Name =>
1010                         New_Occurrence_Of (RTE (RE_Save_Occurrence), Loc),
1011                       Parameter_Associations => New_List (
1012                         New_Occurrence_Of (Cparm, Clc),
1013                         Make_Explicit_Dereference (Loc,
1014                           Make_Function_Call (Loc,
1015                             Name => Make_Explicit_Dereference (Loc,
1016                               New_Occurrence_Of
1017                                 (RTE (RE_Get_Current_Excep), Loc))))));
1018
1019                   Mark_Rewrite_Insertion (Save);
1020                   Prepend (Save, Statements (Handler));
1021
1022                   Obj_Decl :=
1023                     Make_Object_Declaration
1024                       (Clc,
1025                        Defining_Identifier => Cparm,
1026                        Object_Definition   =>
1027                          New_Occurrence_Of
1028                            (RTE (RE_Exception_Occurrence), Clc));
1029                   Set_No_Initialization (Obj_Decl, True);
1030
1031                   Rewrite (Handler,
1032                     Make_Implicit_Exception_Handler (Loc,
1033                       Exception_Choices => Exception_Choices (Handler),
1034
1035                       Statements => New_List (
1036                         Make_Block_Statement (Loc,
1037                           Declarations => New_List (Obj_Decl),
1038                           Handled_Statement_Sequence =>
1039                             Make_Handled_Sequence_Of_Statements (Loc,
1040                               Statements => Statements (Handler))))));
1041
1042                   Analyze_List (Statements (Handler), Suppress => All_Checks);
1043                end;
1044             end if;
1045
1046             --  The processing at this point is rather different for the JVM
1047             --  case, so we completely separate the processing.
1048
1049             --  For the JVM case, we unconditionally call Update_Exception,
1050             --  passing a call to the intrinsic Current_Target_Exception (see
1051             --  JVM version of Ada.Exceptions in 4jexcept.adb for details).
1052
1053             if VM_Target /= No_VM then
1054                declare
1055                   Arg : constant Node_Id :=
1056                           Make_Function_Call (Loc,
1057                             Name =>
1058                               New_Occurrence_Of
1059                                 (RTE (RE_Current_Target_Exception), Loc));
1060                begin
1061                   Prepend_Call_To_Handler
1062                     (RE_Update_Exception, New_List (Arg));
1063                end;
1064
1065                --  For the normal case, we have to worry about the state of
1066                --  abort deferral. Generally, we defer abort during runtime
1067                --  handling of exceptions. When control is passed to the
1068                --  handler, then in the normal case we undefer aborts. In any
1069                --  case this entire handling is relevant only if aborts are
1070                --  allowed!
1071
1072             elsif Abort_Allowed then
1073
1074                --  There are some special cases in which we do not do the
1075                --  undefer. In particular a finalization (AT END) handler
1076                --  wants to operate with aborts still deferred.
1077
1078                --  We also suppress the call if this is the special handler
1079                --  for Abort_Signal, since if we are aborting, we want to keep
1080                --  aborts deferred (one abort is enough).
1081
1082                --  If abort really needs to be deferred the expander must add
1083                --  this call explicitly, see Expand_N_Asynchronous_Select.
1084
1085                Others_Choice :=
1086                  Nkind (First (Exception_Choices (Handler))) = N_Others_Choice;
1087
1088                if (Others_Choice
1089                    or else Entity (First (Exception_Choices (Handler))) /=
1090                      Stand.Abort_Signal)
1091                  and then not
1092                    (Others_Choice
1093                     and then All_Others (First (Exception_Choices (Handler))))
1094                  and then Abort_Allowed
1095                then
1096                   Prepend_Call_To_Handler (RE_Abort_Undefer);
1097                end if;
1098             end if;
1099          end if;
1100
1101          Handler := Next_Handler;
1102       end loop Handler_Loop;
1103
1104       --  If all handlers got removed, then remove the list. Note we cannot
1105       --  reference HSS here, since expanding local handlers may have buried
1106       --  the handlers in an inner block.
1107
1108       if Is_Empty_List (Handlrs) then
1109          Set_Exception_Handlers (Parent (Handlrs), No_List);
1110       end if;
1111    end Expand_Exception_Handlers;
1112
1113    ------------------------------------
1114    -- Expand_N_Exception_Declaration --
1115    ------------------------------------
1116
1117    --  Generates:
1118    --     exceptE : constant String := "A.B.EXCEP";   -- static data
1119    --     except : exception_data :=  (
1120    --                    Handled_By_Other => False,
1121    --                    Lang             => 'A',
1122    --                    Name_Length      => exceptE'Length,
1123    --                    Full_Name        => exceptE'Address,
1124    --                    HTable_Ptr       => null,
1125    --                    Import_Code      => 0,
1126    --                    Raise_Hook       => null,
1127    --                    );
1128
1129    --  (protecting test only needed if not at library level)
1130    --
1131    --     exceptF : Boolean := True --  static data
1132    --     if exceptF then
1133    --        exceptF := False;
1134    --        Register_Exception (except'Unchecked_Access);
1135    --     end if;
1136
1137    procedure Expand_N_Exception_Declaration (N : Node_Id) is
1138       Loc     : constant Source_Ptr := Sloc (N);
1139       Id      : constant Entity_Id  := Defining_Identifier (N);
1140       L       : List_Id             := New_List;
1141       Flag_Id : Entity_Id;
1142
1143       Name_Exname : constant Name_Id := New_External_Name (Chars (Id), 'E');
1144       Exname      : constant Node_Id :=
1145                       Make_Defining_Identifier (Loc, Name_Exname);
1146
1147    begin
1148       --  There is no expansion needed when compiling for the JVM since the
1149       --  JVM has a built-in exception mechanism. See 4jexcept.ads for details.
1150
1151       if VM_Target /= No_VM then
1152          return;
1153       end if;
1154
1155       --  Definition of the external name: nam : constant String := "A.B.NAME";
1156
1157       Insert_Action (N,
1158         Make_Object_Declaration (Loc,
1159           Defining_Identifier => Exname,
1160           Constant_Present    => True,
1161           Object_Definition   => New_Occurrence_Of (Standard_String, Loc),
1162           Expression => Make_String_Literal (Loc, Full_Qualified_Name (Id))));
1163
1164       Set_Is_Statically_Allocated (Exname);
1165
1166       --  Create the aggregate list for type Standard.Exception_Type:
1167       --  Handled_By_Other component: False
1168
1169       Append_To (L, New_Occurrence_Of (Standard_False, Loc));
1170
1171       --  Lang component: 'A'
1172
1173       Append_To (L,
1174         Make_Character_Literal (Loc,
1175           Chars              =>  Name_uA,
1176           Char_Literal_Value =>  UI_From_Int (Character'Pos ('A'))));
1177
1178       --  Name_Length component: Nam'Length
1179
1180       Append_To (L,
1181         Make_Attribute_Reference (Loc,
1182           Prefix         => New_Occurrence_Of (Exname, Loc),
1183           Attribute_Name => Name_Length));
1184
1185       --  Full_Name component: Standard.A_Char!(Nam'Address)
1186
1187       Append_To (L, Unchecked_Convert_To (Standard_A_Char,
1188         Make_Attribute_Reference (Loc,
1189           Prefix         => New_Occurrence_Of (Exname, Loc),
1190           Attribute_Name => Name_Address)));
1191
1192       --  HTable_Ptr component: null
1193
1194       Append_To (L, Make_Null (Loc));
1195
1196       --  Import_Code component: 0
1197
1198       Append_To (L, Make_Integer_Literal (Loc, 0));
1199
1200       --  Raise_Hook component: null
1201
1202       Append_To (L, Make_Null (Loc));
1203
1204       Set_Expression (N, Make_Aggregate (Loc, Expressions => L));
1205       Analyze_And_Resolve (Expression (N), Etype (Id));
1206
1207       --  Register_Exception (except'Unchecked_Access);
1208
1209       if not No_Exception_Handlers_Set
1210         and then not Restriction_Active (No_Exception_Registration)
1211       then
1212          L := New_List (
1213                 Make_Procedure_Call_Statement (Loc,
1214                   Name => New_Occurrence_Of (RTE (RE_Register_Exception), Loc),
1215                   Parameter_Associations => New_List (
1216                     Unchecked_Convert_To (RTE (RE_Exception_Data_Ptr),
1217                       Make_Attribute_Reference (Loc,
1218                         Prefix         => New_Occurrence_Of (Id, Loc),
1219                         Attribute_Name => Name_Unrestricted_Access)))));
1220
1221          Set_Register_Exception_Call (Id, First (L));
1222
1223          if not Is_Library_Level_Entity (Id) then
1224             Flag_Id :=  Make_Defining_Identifier (Loc,
1225                           New_External_Name (Chars (Id), 'F'));
1226
1227             Insert_Action (N,
1228               Make_Object_Declaration (Loc,
1229                 Defining_Identifier => Flag_Id,
1230                 Object_Definition   =>
1231                   New_Occurrence_Of (Standard_Boolean, Loc),
1232                 Expression          =>
1233                   New_Occurrence_Of (Standard_True, Loc)));
1234
1235             Set_Is_Statically_Allocated (Flag_Id);
1236
1237             Append_To (L,
1238               Make_Assignment_Statement (Loc,
1239                 Name       => New_Occurrence_Of (Flag_Id, Loc),
1240                 Expression => New_Occurrence_Of (Standard_False, Loc)));
1241
1242             Insert_After_And_Analyze (N,
1243               Make_Implicit_If_Statement (N,
1244                 Condition       => New_Occurrence_Of (Flag_Id, Loc),
1245                 Then_Statements => L));
1246
1247          else
1248             Insert_List_After_And_Analyze (N, L);
1249          end if;
1250       end if;
1251
1252    end Expand_N_Exception_Declaration;
1253
1254    ---------------------------------------------
1255    -- Expand_N_Handled_Sequence_Of_Statements --
1256    ---------------------------------------------
1257
1258    procedure Expand_N_Handled_Sequence_Of_Statements (N : Node_Id) is
1259    begin
1260       --  Expand exception handlers
1261
1262       if Present (Exception_Handlers (N))
1263         and then not Restriction_Active (No_Exception_Handlers)
1264       then
1265          Expand_Exception_Handlers (N);
1266       end if;
1267
1268       --  If local exceptions are being expanded, the previous call will
1269       --  have rewritten the construct as a block and reanalyzed it. No
1270       --  further expansion is needed.
1271
1272       if Analyzed (N) then
1273          return;
1274       end if;
1275
1276       --  Add clean up actions if required
1277
1278       if Nkind (Parent (N)) /= N_Package_Body
1279         and then Nkind (Parent (N)) /= N_Accept_Statement
1280         and then Nkind (Parent (N)) /= N_Extended_Return_Statement
1281         and then not Delay_Cleanups (Current_Scope)
1282       then
1283          Expand_Cleanup_Actions (Parent (N));
1284       else
1285          Set_First_Real_Statement (N, First (Statements (N)));
1286       end if;
1287    end Expand_N_Handled_Sequence_Of_Statements;
1288
1289    -------------------------------------
1290    -- Expand_N_Raise_Constraint_Error --
1291    -------------------------------------
1292
1293    procedure Expand_N_Raise_Constraint_Error (N : Node_Id) is
1294    begin
1295       --  We adjust the condition to deal with the C/Fortran boolean case. This
1296       --  may well not be necessary, as all such conditions are generated by
1297       --  the expander and probably are all standard boolean, but who knows
1298       --  what strange optimization in future may require this adjustment!
1299
1300       Adjust_Condition (Condition (N));
1301
1302       --  Now deal with possible local raise handling
1303
1304       Possible_Local_Raise (N, Standard_Constraint_Error);
1305    end Expand_N_Raise_Constraint_Error;
1306
1307    ----------------------------------
1308    -- Expand_N_Raise_Program_Error --
1309    ----------------------------------
1310
1311    procedure Expand_N_Raise_Program_Error (N : Node_Id) is
1312    begin
1313       --  We adjust the condition to deal with the C/Fortran boolean case. This
1314       --  may well not be necessary, as all such conditions are generated by
1315       --  the expander and probably are all standard boolean, but who knows
1316       --  what strange optimization in future may require this adjustment!
1317
1318       Adjust_Condition (Condition (N));
1319
1320       --  Now deal with possible local raise handling
1321
1322       Possible_Local_Raise (N, Standard_Program_Error);
1323    end Expand_N_Raise_Program_Error;
1324
1325    ------------------------------
1326    -- Expand_N_Raise_Statement --
1327    ------------------------------
1328
1329    procedure Expand_N_Raise_Statement (N : Node_Id) is
1330       Loc   : constant Source_Ptr := Sloc (N);
1331       Ehand : Node_Id;
1332       E     : Entity_Id;
1333       Str   : String_Id;
1334       H     : Node_Id;
1335
1336    begin
1337       --  Debug_Flag_Dot_G := True;
1338
1339       --  Processing for locally handled exception (exclude reraise case)
1340
1341       if Present (Name (N)) and then Nkind (Name (N)) = N_Identifier then
1342          if Debug_Flag_Dot_G
1343            or else Restriction_Active (No_Exception_Propagation)
1344          then
1345             --  If we have a local handler, then note that this is potentially
1346             --  able to be transformed into a goto statement.
1347
1348             H := Find_Local_Handler (Entity (Name (N)), N);
1349
1350             if Present (H) then
1351                if Local_Raise_Statements (H) = No_Elist then
1352                   Set_Local_Raise_Statements (H, New_Elmt_List);
1353                end if;
1354
1355                --  Append the new entry if it is not there already. Sometimes
1356                --  we have situations where due to reexpansion, the same node
1357                --  is analyzed twice and would otherwise be added twice.
1358
1359                Append_Unique_Elmt (N, Local_Raise_Statements (H));
1360                Set_Has_Local_Raise (H);
1361
1362             --  If no local handler, then generate no propagation warning
1363
1364             else
1365                Warn_If_No_Propagation (N);
1366             end if;
1367
1368          end if;
1369       end if;
1370
1371       --  If a string expression is present, then the raise statement is
1372       --  converted to a call:
1373
1374       --     Raise_Exception (exception-name'Identity, string);
1375
1376       --  and there is nothing else to do
1377
1378       if Present (Expression (N)) then
1379          Rewrite (N,
1380            Make_Procedure_Call_Statement (Loc,
1381              Name => New_Occurrence_Of (RTE (RE_Raise_Exception), Loc),
1382              Parameter_Associations => New_List (
1383                Make_Attribute_Reference (Loc,
1384                  Prefix => Name (N),
1385                  Attribute_Name => Name_Identity),
1386                Expression (N))));
1387          Analyze (N);
1388          return;
1389       end if;
1390
1391       --  Remaining processing is for the case where no string expression
1392       --  is present.
1393
1394       --  There is no expansion needed for statement "raise <exception>;" when
1395       --  compiling for the JVM since the JVM has a built-in exception
1396       --  mechanism. However we need to keep the expansion for "raise;"
1397       --  statements. See 4jexcept.ads for details.
1398
1399       if Present (Name (N)) and then VM_Target /= No_VM then
1400          return;
1401       end if;
1402
1403       --  Don't expand a raise statement that does not come from source
1404       --  if we have already had configurable run-time violations, since
1405       --  most likely it will be junk cascaded nonsense.
1406
1407       if Configurable_Run_Time_Violations > 0
1408         and then not Comes_From_Source (N)
1409       then
1410          return;
1411       end if;
1412
1413       --  Convert explicit raise of Program_Error, Constraint_Error, and
1414       --  Storage_Error into the corresponding raise (in High_Integrity_Mode
1415       --  all other raises will get normal expansion and be disallowed,
1416       --  but this is also faster in all modes).
1417
1418       if Present (Name (N)) and then Nkind (Name (N)) = N_Identifier then
1419          if Entity (Name (N)) = Standard_Constraint_Error then
1420             Rewrite (N,
1421               Make_Raise_Constraint_Error (Loc,
1422                 Reason => CE_Explicit_Raise));
1423             Analyze (N);
1424             return;
1425
1426          elsif Entity (Name (N)) = Standard_Program_Error then
1427             Rewrite (N,
1428               Make_Raise_Program_Error (Loc,
1429                 Reason => PE_Explicit_Raise));
1430             Analyze (N);
1431             return;
1432
1433          elsif Entity (Name (N)) = Standard_Storage_Error then
1434             Rewrite (N,
1435               Make_Raise_Storage_Error (Loc,
1436                 Reason => SE_Explicit_Raise));
1437             Analyze (N);
1438             return;
1439          end if;
1440       end if;
1441
1442       --  Case of name present, in this case we expand raise name to
1443
1444       --    Raise_Exception (name'Identity, location_string);
1445
1446       --  where location_string identifies the file/line of the raise
1447
1448       if Present (Name (N)) then
1449          declare
1450             Id : Entity_Id := Entity (Name (N));
1451
1452          begin
1453             Build_Location_String (Loc);
1454
1455             --  If the exception is a renaming, use the exception that it
1456             --  renames (which might be a predefined exception, e.g.).
1457
1458             if Present (Renamed_Object (Id)) then
1459                Id := Renamed_Object (Id);
1460             end if;
1461
1462             --  Build a C-compatible string in case of no exception handlers,
1463             --  since this is what the last chance handler is expecting.
1464
1465             if No_Exception_Handlers_Set then
1466
1467                --  Generate an empty message if configuration pragma
1468                --  Suppress_Exception_Locations is set for this unit.
1469
1470                if Opt.Exception_Locations_Suppressed then
1471                   Name_Len := 1;
1472                else
1473                   Name_Len := Name_Len + 1;
1474                end if;
1475
1476                Name_Buffer (Name_Len) := ASCII.NUL;
1477             end if;
1478
1479             if Opt.Exception_Locations_Suppressed then
1480                Name_Len := 0;
1481             end if;
1482
1483             Str := String_From_Name_Buffer;
1484
1485             --  For VMS exceptions, convert the raise into a call to
1486             --  lib$stop so it will be handled by __gnat_error_handler.
1487
1488             if Is_VMS_Exception (Id) then
1489                declare
1490                   Excep_Image : String_Id;
1491                   Cond        : Node_Id;
1492
1493                begin
1494                   if Present (Interface_Name (Id)) then
1495                      Excep_Image := Strval (Interface_Name (Id));
1496                   else
1497                      Get_Name_String (Chars (Id));
1498                      Set_All_Upper_Case;
1499                      Excep_Image := String_From_Name_Buffer;
1500                   end if;
1501
1502                   if Exception_Code (Id) /= No_Uint then
1503                      Cond :=
1504                        Make_Integer_Literal (Loc, Exception_Code (Id));
1505                   else
1506                      Cond :=
1507                        Unchecked_Convert_To (Standard_Integer,
1508                          Make_Function_Call (Loc,
1509                            Name => New_Occurrence_Of
1510                              (RTE (RE_Import_Value), Loc),
1511                            Parameter_Associations => New_List
1512                              (Make_String_Literal (Loc,
1513                                Strval => Excep_Image))));
1514                   end if;
1515
1516                   Rewrite (N,
1517                     Make_Procedure_Call_Statement (Loc,
1518                       Name =>
1519                         New_Occurrence_Of (RTE (RE_Lib_Stop), Loc),
1520                       Parameter_Associations => New_List (Cond)));
1521                         Analyze_And_Resolve (Cond, Standard_Integer);
1522                end;
1523
1524             --  Not VMS exception case, convert raise to call to the
1525             --  Raise_Exception routine.
1526
1527             else
1528                Rewrite (N,
1529                  Make_Procedure_Call_Statement (Loc,
1530                     Name => New_Occurrence_Of (RTE (RE_Raise_Exception), Loc),
1531                     Parameter_Associations => New_List (
1532                       Make_Attribute_Reference (Loc,
1533                         Prefix => Name (N),
1534                         Attribute_Name => Name_Identity),
1535                       Make_String_Literal (Loc,
1536                         Strval => Str))));
1537             end if;
1538          end;
1539
1540       --  Case of no name present (reraise). We rewrite the raise to:
1541
1542       --    Reraise_Occurrence_Always (EO);
1543
1544       --  where EO is the current exception occurrence. If the current handler
1545       --  does not have a choice parameter specification, then we provide one.
1546
1547       else
1548          --  Find innermost enclosing exception handler (there must be one,
1549          --  since the semantics has already verified that this raise statement
1550          --  is valid, and a raise with no arguments is only permitted in the
1551          --  context of an exception handler.
1552
1553          Ehand := Parent (N);
1554          while Nkind (Ehand) /= N_Exception_Handler loop
1555             Ehand := Parent (Ehand);
1556          end loop;
1557
1558          --  Make exception choice parameter if none present. Note that we do
1559          --  not need to put the entity on the entity chain, since no one will
1560          --  be referencing this entity by normal visibility methods.
1561
1562          if No (Choice_Parameter (Ehand)) then
1563             E := Make_Defining_Identifier (Loc, New_Internal_Name ('E'));
1564             Set_Choice_Parameter (Ehand, E);
1565             Set_Ekind (E, E_Variable);
1566             Set_Etype (E, RTE (RE_Exception_Occurrence));
1567             Set_Scope (E, Current_Scope);
1568          end if;
1569
1570          --  Now rewrite the raise as a call to Reraise. A special case arises
1571          --  if this raise statement occurs in the context of a handler for
1572          --  all others (i.e. an at end handler). in this case we avoid
1573          --  the call to defer abort, cleanup routines are expected to be
1574          --  called in this case with aborts deferred.
1575
1576          declare
1577             Ech : constant Node_Id := First (Exception_Choices (Ehand));
1578             Ent : Entity_Id;
1579
1580          begin
1581             if Nkind (Ech) = N_Others_Choice
1582               and then All_Others (Ech)
1583             then
1584                Ent := RTE (RE_Reraise_Occurrence_No_Defer);
1585             else
1586                Ent := RTE (RE_Reraise_Occurrence_Always);
1587             end if;
1588
1589             Rewrite (N,
1590               Make_Procedure_Call_Statement (Loc,
1591                 Name => New_Occurrence_Of (Ent, Loc),
1592                 Parameter_Associations => New_List (
1593                   New_Occurrence_Of (Choice_Parameter (Ehand), Loc))));
1594          end;
1595       end if;
1596
1597       Analyze (N);
1598    end Expand_N_Raise_Statement;
1599
1600    ----------------------------------
1601    -- Expand_N_Raise_Storage_Error --
1602    ----------------------------------
1603
1604    procedure Expand_N_Raise_Storage_Error (N : Node_Id) is
1605    begin
1606       --  We adjust the condition to deal with the C/Fortran boolean case. This
1607       --  may well not be necessary, as all such conditions are generated by
1608       --  the expander and probably are all standard boolean, but who knows
1609       --  what strange optimization in future may require this adjustment!
1610
1611       Adjust_Condition (Condition (N));
1612
1613       --  Now deal with possible local raise handling
1614
1615       Possible_Local_Raise (N, Standard_Storage_Error);
1616    end Expand_N_Raise_Storage_Error;
1617
1618    --------------------------
1619    -- Possible_Local_Raise --
1620    --------------------------
1621
1622    procedure Possible_Local_Raise (N : Node_Id; E : Entity_Id) is
1623    begin
1624       --  Nothing to do if local raise optimization not active
1625
1626       if not Debug_Flag_Dot_G
1627         and then not Restriction_Active (No_Exception_Propagation)
1628       then
1629          return;
1630       end if;
1631
1632       --  Nothing to do if original node was an explicit raise, because in
1633       --  that case, we already generated the required warning for the raise.
1634
1635       if Nkind (Original_Node (N)) = N_Raise_Statement then
1636          return;
1637       end if;
1638
1639       --  Otherwise see if we have a local handler for the exception
1640
1641       declare
1642          H : constant Node_Id := Find_Local_Handler (E, N);
1643
1644       begin
1645          --  If so, mark that it has a local raise
1646
1647          if Present (H) then
1648             Set_Has_Local_Raise (H, True);
1649
1650          --  Otherwise, if the No_Exception_Propagation restriction is active
1651          --  and the warning is enabled, generate the appropriate warnings.
1652
1653          elsif Warn_On_Non_Local_Exception
1654            and then Restriction_Active (No_Exception_Propagation)
1655          then
1656             Warn_No_Exception_Propagation_Active (N);
1657
1658             if Configurable_Run_Time_Mode then
1659                Error_Msg_NE
1660                  ("\?& may call Last_Chance_Handler", N, E);
1661             else
1662                Error_Msg_NE
1663                  ("\?& may result in unhandled exception", N, E);
1664             end if;
1665          end if;
1666       end;
1667    end Possible_Local_Raise;
1668
1669    ------------------------------
1670    -- Expand_N_Subprogram_Info --
1671    ------------------------------
1672
1673    procedure Expand_N_Subprogram_Info (N : Node_Id) is
1674       Loc : constant Source_Ptr := Sloc (N);
1675
1676    begin
1677       --  For now, we replace an Expand_N_Subprogram_Info node with an
1678       --  attribute reference that gives the address of the procedure.
1679       --  This is because gigi does not yet recognize this node, and
1680       --  for the initial targets, this is the right value anyway.
1681
1682       Rewrite (N,
1683         Make_Attribute_Reference (Loc,
1684           Prefix => Identifier (N),
1685           Attribute_Name => Name_Code_Address));
1686
1687       Analyze_And_Resolve (N, RTE (RE_Code_Loc));
1688    end Expand_N_Subprogram_Info;
1689
1690    ------------------------
1691    -- Find_Local_Handler --
1692    ------------------------
1693
1694    function Find_Local_Handler
1695      (Ename : Entity_Id;
1696       Nod   : Node_Id) return Node_Id
1697    is
1698       N : Node_Id;
1699       P : Node_Id;
1700       H : Node_Id;
1701       C : Node_Id;
1702
1703       SSE : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
1704       --  This is used to test for wrapped actions below
1705
1706       ERaise  : Entity_Id;
1707       EHandle : Entity_Id;
1708       --  The entity Id's for the exception we are raising and handling, using
1709       --  the renamed exception if a Renamed_Entity is present.
1710
1711    begin
1712       --  Never any local handler if all handlers removed
1713
1714       if Debug_Flag_Dot_X then
1715          return Empty;
1716       end if;
1717
1718       --  Get the exception we are raising, allowing for renaming
1719
1720       ERaise := Get_Renamed_Entity (Ename);
1721
1722       --  We need to check if the node we are looking at is contained in
1723       --
1724
1725       --  Loop to search up the tree
1726
1727       N := Nod;
1728       loop
1729          P := Parent (N);
1730
1731          --  If we get to the top of the tree, or to a subprogram, task, entry,
1732          --  protected body, or accept statement without having found a
1733          --  matching handler, then there is no local handler.
1734
1735          if No (P)
1736            or else Nkind (P) = N_Subprogram_Body
1737            or else Nkind (P) = N_Task_Body
1738            or else Nkind (P) = N_Protected_Body
1739            or else Nkind (P) = N_Entry_Body
1740            or else Nkind (P) = N_Accept_Statement
1741          then
1742             return Empty;
1743
1744             --  Test for handled sequence of statements with at least one
1745             --  exception handler which might be the one we are looking for.
1746
1747          elsif Nkind (P) = N_Handled_Sequence_Of_Statements
1748            and then Present (Exception_Handlers (P))
1749          then
1750             --  Before we proceed we need to check if the node N is covered
1751             --  by the statement part of P rather than one of its exception
1752             --  handlers (an exception handler obviously does not cover its
1753             --  own statements).
1754
1755             --  This test is more delicate than might be thought. It is not
1756             --  just a matter of checking the Statements (P), because the node
1757             --  might be waiting to be wrapped in a transient scope, in which
1758             --  case it will end up in the block statements, even though it
1759             --  is not there now.
1760
1761             if Is_List_Member (N)
1762               and then (List_Containing (N) = Statements (P)
1763                           or else
1764                         List_Containing (N) = SSE.Actions_To_Be_Wrapped_Before
1765                           or else
1766                         List_Containing (N) = SSE.Actions_To_Be_Wrapped_After)
1767             then
1768                --  Loop through exception handlers
1769
1770                H := First (Exception_Handlers (P));
1771                while Present (H) loop
1772
1773                   --  Loop through choices in one handler
1774
1775                   C := First (Exception_Choices (H));
1776                   while Present (C) loop
1777
1778                      --  Deal with others case
1779
1780                      if Nkind (C) = N_Others_Choice then
1781
1782                         --  Matching others handler, but we need to ensure
1783                         --  there is no choice parameter. If there is, then we
1784                         --  don't have a local handler after all (since we do
1785                         --  not allow choice parameters for local handlers).
1786
1787                         if No (Choice_Parameter (H)) then
1788                            return H;
1789                         else
1790                            return Empty;
1791                         end if;
1792
1793                      --  If not others must be entity name
1794
1795                      elsif Nkind (C) /= N_Others_Choice then
1796                         pragma Assert (Is_Entity_Name (C));
1797                         pragma Assert (Present (Entity (C)));
1798
1799                         --  Get exception being handled, dealing with renaming
1800
1801                         EHandle := Get_Renamed_Entity (Entity (C));
1802
1803                         --  If match, then check choice parameter
1804
1805                         if ERaise = EHandle then
1806                            if No (Choice_Parameter (H)) then
1807                               return H;
1808                            else
1809                               return Empty;
1810                            end if;
1811                         end if;
1812                      end if;
1813
1814                      Next (C);
1815                   end loop;
1816
1817                   Next (H);
1818                end loop;
1819             end if;
1820          end if;
1821
1822          N := P;
1823       end loop;
1824    end Find_Local_Handler;
1825
1826    ---------------------------------
1827    -- Get_Local_Raise_Call_Entity --
1828    ---------------------------------
1829
1830    --  Note: this is primary provided for use by the back end in generating
1831    --  calls to Local_Raise. But it would be too late in the back end to call
1832    --  RTE if this actually caused a load/analyze of the unit. So what we do
1833    --  is to ensure there is a dummy call to this function during front end
1834    --  processing so that the unit gets loaded then, and not later.
1835
1836    Local_Raise_Call_Entity     : Entity_Id;
1837    Local_Raise_Call_Entity_Set : Boolean := False;
1838
1839    function Get_Local_Raise_Call_Entity return Entity_Id is
1840    begin
1841       if not Local_Raise_Call_Entity_Set then
1842          Local_Raise_Call_Entity_Set := True;
1843
1844          if RTE_Available (RE_Local_Raise) then
1845             Local_Raise_Call_Entity := RTE (RE_Local_Raise);
1846          else
1847             Local_Raise_Call_Entity := Empty;
1848          end if;
1849       end if;
1850
1851       return Local_Raise_Call_Entity;
1852    end Get_Local_Raise_Call_Entity;
1853
1854    -----------------------------
1855    -- Get_RT_Exception_Entity --
1856    -----------------------------
1857
1858    function Get_RT_Exception_Entity (R : RT_Exception_Code) return Entity_Id is
1859    begin
1860       case R is
1861          when RT_CE_Exceptions => return Standard_Constraint_Error;
1862          when RT_PE_Exceptions => return Standard_Program_Error;
1863          when RT_SE_Exceptions => return Standard_Storage_Error;
1864       end case;
1865    end Get_RT_Exception_Entity;
1866
1867    ----------------------
1868    -- Is_Non_Ada_Error --
1869    ----------------------
1870
1871    function Is_Non_Ada_Error (E : Entity_Id) return Boolean is
1872    begin
1873       if not OpenVMS_On_Target then
1874          return False;
1875       end if;
1876
1877       Get_Name_String (Chars (E));
1878
1879       --  Note: it is a little irregular for the body of exp_ch11 to know
1880       --  the details of the encoding scheme for names, but on the other
1881       --  hand, gigi knows them, and this is for gigi's benefit anyway!
1882
1883       if Name_Buffer (1 .. 30) /= "system__aux_dec__non_ada_error" then
1884          return False;
1885       end if;
1886
1887       return True;
1888    end Is_Non_Ada_Error;
1889
1890    ----------------------------
1891    -- Warn_If_No_Propagation --
1892    ----------------------------
1893
1894    procedure Warn_If_No_Propagation (N : Node_Id) is
1895    begin
1896       if Restriction_Active (No_Exception_Propagation)
1897         and then Warn_On_Non_Local_Exception
1898       then
1899          Warn_No_Exception_Propagation_Active (N);
1900
1901          if Configurable_Run_Time_Mode then
1902             Error_Msg_N
1903               ("\?Last_Chance_Handler will be called on exception", N);
1904          else
1905             Error_Msg_N
1906               ("\?execution may raise unhandled exception", N);
1907          end if;
1908       end if;
1909    end Warn_If_No_Propagation;
1910
1911    ------------------------------------------
1912    -- Warn_No_Exception_Propagation_Active --
1913    ------------------------------------------
1914
1915    procedure Warn_No_Exception_Propagation_Active (N : Node_Id) is
1916    begin
1917       Error_Msg_N
1918         ("?pragma Restrictions (No_Exception_Propagation) in effect", N);
1919    end Warn_No_Exception_Propagation_Active;
1920
1921 end Exp_Ch11;