2011-11-06 François Dumont <fdumont@gcc.gnu.org>
[official-gcc.git] / gcc / ada / exp_ch11.adb
blobb2bf98cd1db386145c2bfb731b30e36055c66b2d
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-2011, 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 ------------------------------------------------------------------------------
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 Restrict; use Restrict;
39 with Rident; use Rident;
40 with Rtsfind; use Rtsfind;
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;
54 package body Exp_Ch11 is
56 -----------------------
57 -- Local Subprograms --
58 -----------------------
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.
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.
70 ---------------------------
71 -- Expand_At_End_Handler --
72 ---------------------------
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:
77 -- exception
78 -- when all others =>
79 -- cleanup call
80 -- raise;
82 -- Note: this exception handler is treated rather specially by
83 -- subsequent expansion in two respects:
85 -- The normal call to Undefer_Abort is omitted
86 -- The raise call does not do Defer_Abort
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.
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.
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.
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;
108 begin
109 pragma Assert (Present (Clean));
110 pragma Assert (No (Exception_Handlers (HSS)));
112 -- Don't expand if back end exception handling active
114 if Exception_Mechanism = Back_End_Exceptions then
115 return;
116 end if;
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
122 if Configurable_Run_Time_Violations > 0 then
123 return;
124 end if;
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).
130 if No_Exception_Handlers_Set then
131 return;
132 end if;
134 if Present (Block) then
135 Push_Scope (Block);
136 end if;
138 Ohandle :=
139 Make_Others_Choice (Loc);
140 Set_All_Others (Ohandle);
142 Stmnts := New_List (
143 Make_Procedure_Call_Statement (Loc,
144 Name => New_Occurrence_Of (Clean, Loc)));
146 -- Generate reraise statement as last statement of AT-END handler,
147 -- unless we are under control of No_Exception_Propagation, in which
148 -- case no exception propagation is possible anyway, so we do not need
149 -- a reraise (the AT END handler in this case is only for normal exits
150 -- not for exceptional exits). Also, we flag the Reraise statement as
151 -- being part of an AT END handler to prevent signalling this reraise
152 -- as a violation of the restriction when it is not set.
154 if not Restriction_Active (No_Exception_Propagation) then
155 declare
156 Rstm : constant Node_Id := Make_Raise_Statement (Loc);
157 begin
158 Set_From_At_End (Rstm);
159 Append_To (Stmnts, Rstm);
160 end;
161 end if;
163 Set_Exception_Handlers (HSS, New_List (
164 Make_Implicit_Exception_Handler (Loc,
165 Exception_Choices => New_List (Ohandle),
166 Statements => Stmnts)));
168 Analyze_List (Stmnts, Suppress => All_Checks);
169 Expand_Exception_Handlers (HSS);
171 if Present (Block) then
172 Pop_Scope;
173 end if;
174 end Expand_At_End_Handler;
176 -------------------------------
177 -- Expand_Exception_Handlers --
178 -------------------------------
180 procedure Expand_Exception_Handlers (HSS : Node_Id) is
181 Handlrs : constant List_Id := Exception_Handlers (HSS);
182 Loc : constant Source_Ptr := Sloc (HSS);
183 Handler : Node_Id;
184 Others_Choice : Boolean;
185 Obj_Decl : Node_Id;
186 Next_Handler : Node_Id;
188 procedure Expand_Local_Exception_Handlers;
189 -- This procedure handles the expansion of exception handlers for the
190 -- optimization of local raise statements into goto statements.
192 procedure Prepend_Call_To_Handler
193 (Proc : RE_Id;
194 Args : List_Id := No_List);
195 -- Routine to prepend a call to the procedure referenced by Proc at
196 -- the start of the handler code for the current Handler.
198 procedure Replace_Raise_By_Goto (Raise_S : Node_Id; Goto_L1 : Node_Id);
199 -- Raise_S is a raise statement (possibly expanded, and possibly of the
200 -- form of a Raise_xxx_Error node with a condition. This procedure is
201 -- called to replace the raise action with the (already analyzed) goto
202 -- statement passed as Goto_L1. This procedure also takes care of the
203 -- requirement of inserting a Local_Raise call where possible.
205 -------------------------------------
206 -- Expand_Local_Exception_Handlers --
207 -------------------------------------
209 -- There are two cases for this transformation. First the case of
210 -- explicit raise statements. For this case, the transformation we do
211 -- looks like this. Right now we have for example (where L1, L2 are
212 -- exception labels)
214 -- begin
215 -- ...
216 -- raise_exception (excep1'identity); -- was raise excep1
217 -- ...
218 -- raise_exception (excep2'identity); -- was raise excep2
219 -- ...
220 -- exception
221 -- when excep1 =>
222 -- estmts1
223 -- when excep2 =>
224 -- estmts2
225 -- end;
227 -- This gets transformed into:
229 -- begin
230 -- L1 : label; -- marked Exception_Junk
231 -- L2 : label; -- marked Exception_Junk
232 -- L3 : label; -- marked Exception_Junk
234 -- begin -- marked Exception_Junk
235 -- ...
236 -- local_raise (excep1'address); -- was raise excep1
237 -- goto L1;
238 -- ...
239 -- local_raise (excep2'address); -- was raise excep2
240 -- goto L2;
241 -- ...
242 -- exception
243 -- when excep1 =>
244 -- goto L1;
245 -- when excep2 =>
246 -- goto L2;
247 -- end;
249 -- goto L3; -- skip handler if no raise, marked Exception_Junk
251 -- <<L1>> -- local excep target label, marked Exception_Junk
252 -- begin -- marked Exception_Junk
253 -- estmts1
254 -- end;
255 -- goto L3; -- marked Exception_Junk
257 -- <<L2>> -- marked Exception_Junk
258 -- begin -- marked Exception_Junk
259 -- estmts2
260 -- end;
261 -- goto L3; -- marked Exception_Junk
262 -- <<L3>> -- marked Exception_Junk
263 -- end;
265 -- Note: the reason we wrap the original statement sequence in an
266 -- inner block is that there may be raise statements within the
267 -- sequence of statements in the handlers, and we must ensure that
268 -- these are properly handled, and in particular, such raise statements
269 -- must not reenter the same exception handlers.
271 -- If the restriction No_Exception_Propagation is in effect, then we
272 -- can omit the exception handlers.
274 -- begin
275 -- L1 : label; -- marked Exception_Junk
276 -- L2 : label; -- marked Exception_Junk
277 -- L3 : label; -- marked Exception_Junk
279 -- begin -- marked Exception_Junk
280 -- ...
281 -- local_raise (excep1'address); -- was raise excep1
282 -- goto L1;
283 -- ...
284 -- local_raise (excep2'address); -- was raise excep2
285 -- goto L2;
286 -- ...
287 -- end;
289 -- goto L3; -- skip handler if no raise, marked Exception_Junk
291 -- <<L1>> -- local excep target label, marked Exception_Junk
292 -- begin -- marked Exception_Junk
293 -- estmts1
294 -- end;
295 -- goto L3; -- marked Exception_Junk
297 -- <<L2>> -- marked Exception_Junk
298 -- begin -- marked Exception_Junk
299 -- estmts2
300 -- end;
302 -- <<L3>> -- marked Exception_Junk
303 -- end;
305 -- The second case is for exceptions generated by the back end in one
306 -- of three situations:
308 -- 1. Front end generates N_Raise_xxx_Error node
309 -- 2. Front end sets Do_xxx_Check flag in subexpression node
310 -- 3. Back end detects a situation where an exception is appropriate
312 -- In all these cases, the current processing in gigi is to generate a
313 -- call to the appropriate Rcheck_xx routine (where xx encodes both the
314 -- exception message and the exception to be raised, Constraint_Error,
315 -- Program_Error, or Storage_Error.
317 -- We could handle some subcases of 1 using the same front end expansion
318 -- into gotos, but even for case 1, we can't handle all cases, since
319 -- generating gotos in the middle of expressions is not possible (it's
320 -- possible at the gigi/gcc level, but not at the level of the GNAT
321 -- tree).
323 -- In any case, it seems easier to have a scheme which handles all three
324 -- cases in a uniform manner. So here is how we proceed in this case.
326 -- This procedure detects all handlers for these three exceptions,
327 -- Constraint_Error, Program_Error and Storage_Error (including WHEN
328 -- OTHERS handlers that cover one or more of these cases).
330 -- If the handler meets the requirements for being the target of a local
331 -- raise, then the front end does the expansion described previously,
332 -- creating a label to be used as a goto target to raise the exception.
333 -- However, no attempt is made in the front end to convert any related
334 -- raise statements into gotos, e.g. all N_Raise_xxx_Error nodes are
335 -- left unchanged and passed to the back end.
337 -- Instead, the front end generates three nodes
339 -- N_Push_Constraint_Error_Label
340 -- N_Push_Program_Error_Label
341 -- N_Push_Storage_Error_Label
343 -- The Push node is generated at the start of the statements
344 -- covered by the handler, and has as a parameter the label to be
345 -- used as the raise target.
347 -- N_Pop_Constraint_Error_Label
348 -- N_Pop_Program_Error_Label
349 -- N_Pop_Storage_Error_Label
351 -- The Pop node is generated at the end of the covered statements
352 -- and undoes the effect of the preceding corresponding Push node.
354 -- In the case where the handler does NOT meet the requirements, the
355 -- front end will still generate the Push and Pop nodes, but the label
356 -- field in the Push node will be empty signifying that for this region
357 -- of code, no optimization is possible.
359 -- These Push/Pop nodes are inhibited if No_Exception_Handlers is set
360 -- since they are useless in this case, and in CodePeer mode, where
361 -- they serve no purpose and can intefere with the analysis.
363 -- The back end must maintain three stacks, one for each exception case,
364 -- the Push node pushes an entry onto the corresponding stack, and Pop
365 -- node pops off the entry. Then instead of calling Rcheck_nn, if the
366 -- corresponding top stack entry has an non-empty label, a goto is
367 -- generated. This goto should be preceded by a call to Local_Raise as
368 -- described above.
370 -- An example of this transformation is as follows, given:
372 -- declare
373 -- A : Integer range 1 .. 10;
374 -- begin
375 -- A := B + C;
376 -- exception
377 -- when Constraint_Error =>
378 -- estmts
379 -- end;
381 -- gets transformed to:
383 -- declare
384 -- A : Integer range 1 .. 10;
386 -- begin
387 -- L1 : label;
388 -- L2 : label;
390 -- begin
391 -- %push_constraint_error_label (L1)
392 -- R1b : constant long_long_integer := long_long_integer?(b) +
393 -- long_long_integer?(c);
394 -- [constraint_error when
395 -- not (R1b in -16#8000_0000# .. 16#7FFF_FFFF#)
396 -- "overflow check failed"]
397 -- a := integer?(R1b);
398 -- %pop_constraint_error_Label
400 -- exception
401 -- ...
402 -- when constraint_error =>
403 -- goto L1;
404 -- end;
406 -- goto L2; -- skip handler when exception not raised
407 -- <<L1>> -- target label for local exception
408 -- estmts
409 -- <<L2>>
410 -- end;
412 -- Note: the generated labels and goto statements all have the flag
413 -- Exception_Junk set True, so that Sem_Ch6.Check_Returns will ignore
414 -- this generated exception stuff when checking for missing return
415 -- statements (see circuitry in Check_Statement_Sequence).
417 -- Note: All of the processing described above occurs only if
418 -- restriction No_Exception_Propagation applies or debug flag .g is
419 -- enabled.
421 CE_Locally_Handled : Boolean := False;
422 SE_Locally_Handled : Boolean := False;
423 PE_Locally_Handled : Boolean := False;
424 -- These three flags indicate whether a handler for the corresponding
425 -- exception (CE=Constraint_Error, SE=Storage_Error, PE=Program_Error)
426 -- is present. If so the switch is set to True, the Exception_Label
427 -- field of the corresponding handler is set, and appropriate Push
428 -- and Pop nodes are inserted into the code.
430 Local_Expansion_Required : Boolean := False;
431 -- Set True if we have at least one handler requiring local raise
432 -- expansion as described above.
434 procedure Expand_Local_Exception_Handlers is
436 procedure Add_Exception_Label (H : Node_Id);
437 -- H is an exception handler. First check for an Exception_Label
438 -- already allocated for H. If none, allocate one, set the field in
439 -- the handler node, add the label declaration, and set the flag
440 -- Local_Expansion_Required. Note: if Local_Raise_Not_OK is set
441 -- the call has no effect and Exception_Label is left empty.
443 procedure Add_Label_Declaration (L : Entity_Id);
444 -- Add an implicit declaration of the given label to the declaration
445 -- list in the parent of the current sequence of handled statements.
447 generic
448 Exc_Locally_Handled : in out Boolean;
449 -- Flag indicating whether a local handler for this exception
450 -- has already been generated.
452 with function Make_Push_Label (Loc : Source_Ptr) return Node_Id;
453 -- Function to create a Push_xxx_Label node
455 with function Make_Pop_Label (Loc : Source_Ptr) return Node_Id;
456 -- Function to create a Pop_xxx_Label node
458 procedure Generate_Push_Pop (H : Node_Id);
459 -- Common code for Generate_Push_Pop_xxx below, used to generate an
460 -- exception label and Push/Pop nodes for Constraint_Error,
461 -- Program_Error, or Storage_Error.
463 -------------------------
464 -- Add_Exception_Label --
465 -------------------------
467 procedure Add_Exception_Label (H : Node_Id) is
468 begin
469 if No (Exception_Label (H))
470 and then not Local_Raise_Not_OK (H)
471 and then not Special_Exception_Package_Used
472 then
473 Local_Expansion_Required := True;
475 declare
476 L : constant Entity_Id := Make_Temporary (Sloc (H), 'L');
477 begin
478 Set_Exception_Label (H, L);
479 Add_Label_Declaration (L);
480 end;
481 end if;
482 end Add_Exception_Label;
484 ---------------------------
485 -- Add_Label_Declaration --
486 ---------------------------
488 procedure Add_Label_Declaration (L : Entity_Id) is
489 P : constant Node_Id := Parent (HSS);
491 Decl_L : constant Node_Id :=
492 Make_Implicit_Label_Declaration (Loc,
493 Defining_Identifier => L);
495 begin
496 if Declarations (P) = No_List then
497 Set_Declarations (P, Empty_List);
498 end if;
500 Append (Decl_L, Declarations (P));
501 Analyze (Decl_L);
502 end Add_Label_Declaration;
504 -----------------------
505 -- Generate_Push_Pop --
506 -----------------------
508 procedure Generate_Push_Pop (H : Node_Id) is
509 begin
510 if Restriction_Active (No_Exception_Handlers)
511 or else CodePeer_Mode
512 then
513 return;
514 end if;
516 if Exc_Locally_Handled then
517 return;
518 else
519 Exc_Locally_Handled := True;
520 end if;
522 Add_Exception_Label (H);
524 declare
525 F : constant Node_Id := First (Statements (HSS));
526 L : constant Node_Id := Last (Statements (HSS));
528 Push : constant Node_Id := Make_Push_Label (Sloc (F));
529 Pop : constant Node_Id := Make_Pop_Label (Sloc (L));
531 begin
532 -- We make sure that a call to Get_Local_Raise_Call_Entity is
533 -- made during front end processing, so that when we need it
534 -- in the back end, it will already be available and loaded.
536 Discard_Node (Get_Local_Raise_Call_Entity);
538 -- Prepare and insert Push and Pop nodes
540 Set_Exception_Label (Push, Exception_Label (H));
541 Insert_Before (F, Push);
542 Set_Analyzed (Push);
544 Insert_After (L, Pop);
545 Set_Analyzed (Pop);
546 end;
547 end Generate_Push_Pop;
549 -- Local declarations
551 Loc : constant Source_Ptr := Sloc (HSS);
552 Stmts : List_Id := No_List;
553 Choice : Node_Id;
554 Excep : Entity_Id;
556 procedure Generate_Push_Pop_For_Constraint_Error is
557 new Generate_Push_Pop
558 (Exc_Locally_Handled => CE_Locally_Handled,
559 Make_Push_Label => Make_Push_Constraint_Error_Label,
560 Make_Pop_Label => Make_Pop_Constraint_Error_Label);
561 -- If no Push/Pop has been generated for CE yet, then set the flag
562 -- CE_Locally_Handled, allocate an Exception_Label for handler H (if
563 -- not already done), and generate Push/Pop nodes for the exception
564 -- label at the start and end of the statements of HSS.
566 procedure Generate_Push_Pop_For_Program_Error is
567 new Generate_Push_Pop
568 (Exc_Locally_Handled => PE_Locally_Handled,
569 Make_Push_Label => Make_Push_Program_Error_Label,
570 Make_Pop_Label => Make_Pop_Program_Error_Label);
571 -- If no Push/Pop has been generated for PE yet, then set the flag
572 -- PE_Locally_Handled, allocate an Exception_Label for handler H (if
573 -- not already done), and generate Push/Pop nodes for the exception
574 -- label at the start and end of the statements of HSS.
576 procedure Generate_Push_Pop_For_Storage_Error is
577 new Generate_Push_Pop
578 (Exc_Locally_Handled => SE_Locally_Handled,
579 Make_Push_Label => Make_Push_Storage_Error_Label,
580 Make_Pop_Label => Make_Pop_Storage_Error_Label);
581 -- If no Push/Pop has been generated for SE yet, then set the flag
582 -- SE_Locally_Handled, allocate an Exception_Label for handler H (if
583 -- not already done), and generate Push/Pop nodes for the exception
584 -- label at the start and end of the statements of HSS.
586 -- Start of processing for Expand_Local_Exception_Handlers
588 begin
589 -- No processing if all exception handlers will get removed
591 if Debug_Flag_Dot_X then
592 return;
593 end if;
595 -- See for each handler if we have any local raises to expand
597 Handler := First_Non_Pragma (Handlrs);
598 while Present (Handler) loop
600 -- Note, we do not test Local_Raise_Not_OK here, because in the
601 -- case of Push/Pop generation we want to generate push with a
602 -- null label. The Add_Exception_Label routine has no effect if
603 -- Local_Raise_Not_OK is set, so this works as required.
605 if Present (Local_Raise_Statements (Handler)) then
606 Add_Exception_Label (Handler);
607 end if;
609 -- If we are doing local raise to goto optimization (restriction
610 -- No_Exception_Propagation set or debug flag .g set), then check
611 -- to see if handler handles CE, PE, SE and if so generate the
612 -- appropriate push/pop sequence for the back end.
614 if (Debug_Flag_Dot_G
615 or else Restriction_Active (No_Exception_Propagation))
616 and then Has_Local_Raise (Handler)
617 then
618 Choice := First (Exception_Choices (Handler));
619 while Present (Choice) loop
620 if Nkind (Choice) = N_Others_Choice
621 and then not All_Others (Choice)
622 then
623 Generate_Push_Pop_For_Constraint_Error (Handler);
624 Generate_Push_Pop_For_Program_Error (Handler);
625 Generate_Push_Pop_For_Storage_Error (Handler);
627 elsif Is_Entity_Name (Choice) then
628 Excep := Get_Renamed_Entity (Entity (Choice));
630 if Excep = Standard_Constraint_Error then
631 Generate_Push_Pop_For_Constraint_Error (Handler);
632 elsif Excep = Standard_Program_Error then
633 Generate_Push_Pop_For_Program_Error (Handler);
634 elsif Excep = Standard_Storage_Error then
635 Generate_Push_Pop_For_Storage_Error (Handler);
636 end if;
637 end if;
639 Next (Choice);
640 end loop;
641 end if;
643 Next_Non_Pragma (Handler);
644 end loop;
646 -- Nothing to do if no handlers requiring the goto transformation
648 if not (Local_Expansion_Required) then
649 return;
650 end if;
652 -- Prepare to do the transformation
654 declare
655 -- L3 is the label to exit the HSS
657 L3_Dent : constant Entity_Id := Make_Temporary (Loc, 'L');
659 Labl_L3 : constant Node_Id :=
660 Make_Label (Loc,
661 Identifier => New_Occurrence_Of (L3_Dent, Loc));
663 Blk_Stm : Node_Id;
664 Relmt : Elmt_Id;
666 begin
667 Set_Exception_Junk (Labl_L3);
668 Add_Label_Declaration (L3_Dent);
670 -- Wrap existing statements and handlers in an inner block
672 Blk_Stm :=
673 Make_Block_Statement (Loc,
674 Handled_Statement_Sequence => Relocate_Node (HSS));
675 Set_Exception_Junk (Blk_Stm);
677 Rewrite (HSS,
678 Make_Handled_Sequence_Of_Statements (Loc,
679 Statements => New_List (Blk_Stm),
680 End_Label => Relocate_Node (End_Label (HSS))));
682 -- Set block statement as analyzed, we don't want to actually call
683 -- Analyze on this block, it would cause a recursion in exception
684 -- handler processing which would mess things up.
686 Set_Analyzed (Blk_Stm);
688 -- Now loop through the exception handlers to deal with those that
689 -- are targets of local raise statements.
691 Handler := First_Non_Pragma (Handlrs);
692 while Present (Handler) loop
693 if Present (Exception_Label (Handler)) then
695 -- This handler needs the goto expansion
697 declare
698 Loc : constant Source_Ptr := Sloc (Handler);
700 -- L1 is the start label for this handler
702 L1_Dent : constant Entity_Id := Exception_Label (Handler);
704 Labl_L1 : constant Node_Id :=
705 Make_Label (Loc,
706 Identifier =>
707 New_Occurrence_Of (L1_Dent, Loc));
709 -- Jump to L1 to be used as replacement for the original
710 -- handler (used in the case where exception propagation
711 -- may still occur).
713 Name_L1 : constant Node_Id :=
714 New_Occurrence_Of (L1_Dent, Loc);
716 Goto_L1 : constant Node_Id :=
717 Make_Goto_Statement (Loc,
718 Name => Name_L1);
720 -- Jump to L3 to be used at the end of handler
722 Name_L3 : constant Node_Id :=
723 New_Occurrence_Of (L3_Dent, Loc);
725 Goto_L3 : constant Node_Id :=
726 Make_Goto_Statement (Loc,
727 Name => Name_L3);
729 H_Stmts : constant List_Id := Statements (Handler);
731 begin
732 Set_Exception_Junk (Labl_L1);
733 Set_Exception_Junk (Goto_L3);
735 -- Note: we do NOT set Exception_Junk in Goto_L1, since
736 -- this is a real transfer of control that we want the
737 -- Sem_Ch6.Check_Returns procedure to recognize properly.
739 -- Replace handler by a goto L1. We can mark this as
740 -- analyzed since it is fully formed, and we don't
741 -- want it going through any further checks. We save
742 -- the last statement location in the goto L1 node for
743 -- the benefit of Sem_Ch6.Check_Returns.
745 Set_Statements (Handler, New_List (Goto_L1));
746 Set_Analyzed (Goto_L1);
747 Set_Etype (Name_L1, Standard_Void_Type);
749 -- Now replace all the raise statements by goto L1
751 if Present (Local_Raise_Statements (Handler)) then
752 Relmt := First_Elmt (Local_Raise_Statements (Handler));
753 while Present (Relmt) loop
754 declare
755 Raise_S : constant Node_Id := Node (Relmt);
756 RLoc : constant Source_Ptr := Sloc (Raise_S);
757 Name_L1 : constant Node_Id :=
758 New_Occurrence_Of (L1_Dent, Loc);
759 Goto_L1 : constant Node_Id :=
760 Make_Goto_Statement (RLoc,
761 Name => Name_L1);
763 begin
764 -- Replace raise by goto L1
766 Set_Analyzed (Goto_L1);
767 Set_Etype (Name_L1, Standard_Void_Type);
768 Replace_Raise_By_Goto (Raise_S, Goto_L1);
769 end;
771 Next_Elmt (Relmt);
772 end loop;
773 end if;
775 -- Add a goto L3 at end of statement list in block. The
776 -- first time, this is what skips over the exception
777 -- handlers in the normal case. Subsequent times, it
778 -- terminates the execution of the previous handler code,
779 -- and skips subsequent handlers.
781 Stmts := Statements (HSS);
783 Insert_After (Last (Stmts), Goto_L3);
784 Set_Analyzed (Goto_L3);
785 Set_Etype (Name_L3, Standard_Void_Type);
787 -- Now we drop the label that marks the handler start,
788 -- followed by the statements of the handler.
790 Set_Etype (Identifier (Labl_L1), Standard_Void_Type);
792 Insert_After_And_Analyze (Last (Stmts), Labl_L1);
794 declare
795 Loc : constant Source_Ptr := Sloc (First (H_Stmts));
796 Blk : constant Node_Id :=
797 Make_Block_Statement (Loc,
798 Handled_Statement_Sequence =>
799 Make_Handled_Sequence_Of_Statements (Loc,
800 Statements => H_Stmts));
801 begin
802 Set_Exception_Junk (Blk);
803 Insert_After_And_Analyze (Last (Stmts), Blk);
804 end;
805 end;
807 -- Here if we have local raise statements but the handler is
808 -- not suitable for processing with a local raise. In this
809 -- case we have to generate possible diagnostics.
811 elsif Has_Local_Raise (Handler)
812 and then Local_Raise_Statements (Handler) /= No_Elist
813 then
814 Relmt := First_Elmt (Local_Raise_Statements (Handler));
815 while Present (Relmt) loop
816 Warn_If_No_Propagation (Node (Relmt));
817 Next_Elmt (Relmt);
818 end loop;
819 end if;
821 Next (Handler);
822 end loop;
824 -- Only remaining step is to drop the L3 label and we are done
826 Set_Etype (Identifier (Labl_L3), Standard_Void_Type);
828 -- If we had at least one handler, then we drop the label after
829 -- the last statement of that handler.
831 if Stmts /= No_List then
832 Insert_After_And_Analyze (Last (Stmts), Labl_L3);
834 -- Otherwise we have removed all the handlers (this results from
835 -- use of pragma Restrictions (No_Exception_Propagation), and we
836 -- drop the label at the end of the statements of the HSS.
838 else
839 Insert_After_And_Analyze (Last (Statements (HSS)), Labl_L3);
840 end if;
842 return;
843 end;
844 end Expand_Local_Exception_Handlers;
846 -----------------------------
847 -- Prepend_Call_To_Handler --
848 -----------------------------
850 procedure Prepend_Call_To_Handler
851 (Proc : RE_Id;
852 Args : List_Id := No_List)
854 Ent : constant Entity_Id := RTE (Proc);
856 begin
857 -- If we have no Entity, then we are probably in no run time mode or
858 -- some weird error has occurred. In either case do nothing. Note use
859 -- of No_Location to hide this code from the debugger, so single
860 -- stepping doesn't jump back and forth.
862 if Present (Ent) then
863 declare
864 Call : constant Node_Id :=
865 Make_Procedure_Call_Statement (No_Location,
866 Name => New_Occurrence_Of (RTE (Proc), No_Location),
867 Parameter_Associations => Args);
869 begin
870 Prepend_To (Statements (Handler), Call);
871 Analyze (Call, Suppress => All_Checks);
872 end;
873 end if;
874 end Prepend_Call_To_Handler;
876 ---------------------------
877 -- Replace_Raise_By_Goto --
878 ---------------------------
880 procedure Replace_Raise_By_Goto (Raise_S : Node_Id; Goto_L1 : Node_Id) is
881 Loc : constant Source_Ptr := Sloc (Raise_S);
882 Excep : Entity_Id;
883 LR : Node_Id;
884 Cond : Node_Id;
885 Orig : Node_Id;
887 begin
888 -- If we have a null statement, it means that there is no replacement
889 -- needed (typically this results from a suppressed check).
891 if Nkind (Raise_S) = N_Null_Statement then
892 return;
894 -- Test for Raise_xxx_Error
896 elsif Nkind (Raise_S) = N_Raise_Constraint_Error then
897 Excep := Standard_Constraint_Error;
898 Cond := Condition (Raise_S);
900 elsif Nkind (Raise_S) = N_Raise_Storage_Error then
901 Excep := Standard_Storage_Error;
902 Cond := Condition (Raise_S);
904 elsif Nkind (Raise_S) = N_Raise_Program_Error then
905 Excep := Standard_Program_Error;
906 Cond := Condition (Raise_S);
908 -- The only other possibility is a node that is or used to be a
909 -- simple raise statement.
911 else
912 Orig := Original_Node (Raise_S);
913 pragma Assert (Nkind (Orig) = N_Raise_Statement
914 and then Present (Name (Orig))
915 and then No (Expression (Orig)));
916 Excep := Entity (Name (Orig));
917 Cond := Empty;
918 end if;
920 -- Here Excep is the exception to raise, and Cond is the condition
921 -- First prepare the call to Local_Raise (excep'address).
923 if RTE_Available (RE_Local_Raise) then
924 LR :=
925 Make_Procedure_Call_Statement (Loc,
926 Name => New_Occurrence_Of (RTE (RE_Local_Raise), Loc),
927 Parameter_Associations => New_List (
928 Unchecked_Convert_To (RTE (RE_Address),
929 Make_Attribute_Reference (Loc,
930 Prefix => New_Occurrence_Of (Excep, Loc),
931 Attribute_Name => Name_Identity))));
933 -- Use null statement if Local_Raise not available
935 else
936 LR :=
937 Make_Null_Statement (Loc);
938 end if;
940 -- If there is no condition, we rewrite as
942 -- begin
943 -- Local_Raise (excep'Identity);
944 -- goto L1;
945 -- end;
947 if No (Cond) then
948 Rewrite (Raise_S,
949 Make_Block_Statement (Loc,
950 Handled_Statement_Sequence =>
951 Make_Handled_Sequence_Of_Statements (Loc,
952 Statements => New_List (LR, Goto_L1))));
953 Set_Exception_Junk (Raise_S);
955 -- If there is a condition, we rewrite as
957 -- if condition then
958 -- Local_Raise (excep'Identity);
959 -- goto L1;
960 -- end if;
962 else
963 Rewrite (Raise_S,
964 Make_If_Statement (Loc,
965 Condition => Cond,
966 Then_Statements => New_List (LR, Goto_L1)));
967 end if;
969 Analyze (Raise_S);
970 end Replace_Raise_By_Goto;
972 -- Start of processing for Expand_Exception_Handlers
974 begin
975 Expand_Local_Exception_Handlers;
977 -- Loop through handlers
979 Handler := First_Non_Pragma (Handlrs);
980 Handler_Loop : while Present (Handler) loop
981 Process_Statements_For_Controlled_Objects (Handler);
983 Next_Handler := Next_Non_Pragma (Handler);
985 -- Remove source handler if gnat debug flag .x is set
987 if Debug_Flag_Dot_X and then Comes_From_Source (Handler) then
988 Remove (Handler);
990 -- Remove handler if no exception propagation, generating a warning
991 -- if a source generated handler was not the target of a local raise.
993 else
994 if Restriction_Active (No_Exception_Propagation)
995 and then not Has_Local_Raise (Handler)
996 and then Comes_From_Source (Handler)
997 and then Warn_On_Non_Local_Exception
998 then
999 Warn_No_Exception_Propagation_Active (Handler);
1000 Error_Msg_N
1001 ("\?this handler can never be entered, and has been removed",
1002 Handler);
1003 end if;
1005 if No_Exception_Propagation_Active then
1006 Remove (Handler);
1008 -- Exception handler is active and retained and must be processed
1010 else
1011 -- If an exception occurrence is present, then we must declare
1012 -- it and initialize it from the value stored in the TSD
1014 -- declare
1015 -- name : Exception_Occurrence;
1016 -- begin
1017 -- Save_Occurrence (name, Get_Current_Excep.all)
1018 -- ...
1019 -- end;
1021 if Present (Choice_Parameter (Handler)) then
1022 declare
1023 Cparm : constant Entity_Id := Choice_Parameter (Handler);
1024 Cloc : constant Source_Ptr := Sloc (Cparm);
1025 Hloc : constant Source_Ptr := Sloc (Handler);
1026 Save : Node_Id;
1028 begin
1029 -- Note use of No_Location to hide this code from the
1030 -- debugger, so single stepping doesn't jump back and
1031 -- forth.
1033 Save :=
1034 Make_Procedure_Call_Statement (No_Location,
1035 Name =>
1036 New_Occurrence_Of (RTE (RE_Save_Occurrence),
1037 No_Location),
1038 Parameter_Associations => New_List (
1039 New_Occurrence_Of (Cparm, Cloc),
1040 Make_Explicit_Dereference (No_Location,
1041 Make_Function_Call (No_Location,
1042 Name => Make_Explicit_Dereference (No_Location,
1043 New_Occurrence_Of
1044 (RTE (RE_Get_Current_Excep),
1045 No_Location))))));
1047 Mark_Rewrite_Insertion (Save);
1048 Prepend (Save, Statements (Handler));
1050 Obj_Decl :=
1051 Make_Object_Declaration
1052 (Cloc,
1053 Defining_Identifier => Cparm,
1054 Object_Definition =>
1055 New_Occurrence_Of
1056 (RTE (RE_Exception_Occurrence), Cloc));
1057 Set_No_Initialization (Obj_Decl, True);
1059 Rewrite (Handler,
1060 Make_Exception_Handler (Hloc,
1061 Choice_Parameter => Empty,
1062 Exception_Choices => Exception_Choices (Handler),
1064 Statements => New_List (
1065 Make_Block_Statement (Hloc,
1066 Declarations => New_List (Obj_Decl),
1067 Handled_Statement_Sequence =>
1068 Make_Handled_Sequence_Of_Statements (Hloc,
1069 Statements => Statements (Handler))))));
1071 -- Local raise statements can't occur, since exception
1072 -- handlers with choice parameters are not allowed when
1073 -- No_Exception_Propagation applies, so set attributes
1074 -- accordingly.
1076 Set_Local_Raise_Statements (Handler, No_Elist);
1077 Set_Local_Raise_Not_OK (Handler);
1079 Analyze_List
1080 (Statements (Handler), Suppress => All_Checks);
1081 end;
1082 end if;
1084 -- The processing at this point is rather different for the JVM
1085 -- case, so we completely separate the processing.
1087 -- For the VM case, we unconditionally call Update_Exception,
1088 -- passing a call to the intrinsic Current_Target_Exception
1089 -- (see JVM/.NET versions of Ada.Exceptions for details).
1091 if VM_Target /= No_VM then
1092 declare
1093 Arg : constant Node_Id :=
1094 Make_Function_Call (Loc,
1095 Name =>
1096 New_Occurrence_Of
1097 (RTE (RE_Current_Target_Exception), Loc));
1098 begin
1099 Prepend_Call_To_Handler
1100 (RE_Update_Exception, New_List (Arg));
1101 end;
1103 -- For the normal case, we have to worry about the state of
1104 -- abort deferral. Generally, we defer abort during runtime
1105 -- handling of exceptions. When control is passed to the
1106 -- handler, then in the normal case we undefer aborts. In
1107 -- any case this entire handling is relevant only if aborts
1108 -- are allowed!
1110 elsif Abort_Allowed
1111 and then Exception_Mechanism /= Back_End_Exceptions
1112 then
1113 -- There are some special cases in which we do not do the
1114 -- undefer. In particular a finalization (AT END) handler
1115 -- wants to operate with aborts still deferred.
1117 -- We also suppress the call if this is the special handler
1118 -- for Abort_Signal, since if we are aborting, we want to
1119 -- keep aborts deferred (one abort is enough).
1121 -- If abort really needs to be deferred the expander must
1122 -- add this call explicitly, see
1123 -- Expand_N_Asynchronous_Select.
1125 Others_Choice :=
1126 Nkind (First (Exception_Choices (Handler))) =
1127 N_Others_Choice;
1129 if (Others_Choice
1130 or else Entity (First (Exception_Choices (Handler))) /=
1131 Stand.Abort_Signal)
1132 and then not
1133 (Others_Choice
1134 and then
1135 All_Others (First (Exception_Choices (Handler))))
1136 then
1137 Prepend_Call_To_Handler (RE_Abort_Undefer);
1138 end if;
1139 end if;
1140 end if;
1141 end if;
1143 Handler := Next_Handler;
1144 end loop Handler_Loop;
1146 -- If all handlers got removed, then remove the list. Note we cannot
1147 -- reference HSS here, since expanding local handlers may have buried
1148 -- the handlers in an inner block.
1150 if Is_Empty_List (Handlrs) then
1151 Set_Exception_Handlers (Parent (Handlrs), No_List);
1152 end if;
1153 end Expand_Exception_Handlers;
1155 ------------------------------------
1156 -- Expand_N_Exception_Declaration --
1157 ------------------------------------
1159 -- Generates:
1160 -- exceptE : constant String := "A.B.EXCEP"; -- static data
1161 -- except : exception_data := (
1162 -- Handled_By_Other => False,
1163 -- Lang => 'A',
1164 -- Name_Length => exceptE'Length,
1165 -- Full_Name => exceptE'Address,
1166 -- HTable_Ptr => null,
1167 -- Import_Code => 0,
1168 -- Raise_Hook => null,
1169 -- );
1171 -- (protecting test only needed if not at library level)
1173 -- exceptF : Boolean := True -- static data
1174 -- if exceptF then
1175 -- exceptF := False;
1176 -- Register_Exception (except'Unchecked_Access);
1177 -- end if;
1179 procedure Expand_N_Exception_Declaration (N : Node_Id) is
1180 Loc : constant Source_Ptr := Sloc (N);
1181 Id : constant Entity_Id := Defining_Identifier (N);
1182 L : List_Id := New_List;
1183 Flag_Id : Entity_Id;
1185 Name_Exname : constant Name_Id := New_External_Name (Chars (Id), 'E');
1186 Exname : constant Node_Id :=
1187 Make_Defining_Identifier (Loc, Name_Exname);
1189 procedure Force_Static_Allocation_Of_Referenced_Objects
1190 (Aggregate : Node_Id);
1191 -- A specialized solution to one particular case of an ugly problem
1193 -- The given aggregate includes an Unchecked_Conversion as one of the
1194 -- component values. The call to Analyze_And_Resolve below ends up
1195 -- calling Exp_Ch4.Expand_N_Unchecked_Type_Conversion, which may decide
1196 -- to introduce a (constant) temporary and then obtain the component
1197 -- value by evaluating the temporary.
1199 -- In the case of an exception declared within a subprogram (or any
1200 -- other dynamic scope), this is a bad transformation. The exception
1201 -- object is marked as being Statically_Allocated but the temporary is
1202 -- not. If the initial value of a Statically_Allocated declaration
1203 -- references a dynamically allocated object, this prevents static
1204 -- initialization of the object.
1206 -- We cope with this here by marking the temporary Statically_Allocated.
1207 -- It might seem cleaner to generalize this utility and then use it to
1208 -- enforce a rule that the entities referenced in the declaration of any
1209 -- "hoisted" (i.e., Is_Statically_Allocated and not Is_Library_Level)
1210 -- entity must also be either Library_Level or hoisted. It turns out
1211 -- that this would be incompatible with the current treatment of an
1212 -- object which is local to a subprogram, subject to an Export pragma,
1213 -- not subject to an address clause, and whose declaration contains
1214 -- references to other local (non-hoisted) objects (e.g., in the initial
1215 -- value expression).
1217 ---------------------------------------------------
1218 -- Force_Static_Allocation_Of_Referenced_Objects --
1219 ---------------------------------------------------
1221 procedure Force_Static_Allocation_Of_Referenced_Objects
1222 (Aggregate : Node_Id)
1224 function Fixup_Node (N : Node_Id) return Traverse_Result;
1225 -- If the given node references a dynamically allocated object, then
1226 -- correct the declaration of the object.
1228 ----------------
1229 -- Fixup_Node --
1230 ----------------
1232 function Fixup_Node (N : Node_Id) return Traverse_Result is
1233 begin
1234 if Nkind (N) in N_Has_Entity
1235 and then Present (Entity (N))
1236 and then not Is_Library_Level_Entity (Entity (N))
1238 -- Note: the following test is not needed but it seems cleaner
1239 -- to do this test (this would be more important if procedure
1240 -- Force_Static_Allocation_Of_Referenced_Objects recursively
1241 -- traversed the declaration of an entity after marking it as
1242 -- statically allocated).
1244 and then not Is_Statically_Allocated (Entity (N))
1245 then
1246 Set_Is_Statically_Allocated (Entity (N));
1247 end if;
1249 return OK;
1250 end Fixup_Node;
1252 procedure Fixup_Tree is new Traverse_Proc (Fixup_Node);
1254 -- Start of processing for Force_Static_Allocation_Of_Referenced_Objects
1256 begin
1257 Fixup_Tree (Aggregate);
1258 end Force_Static_Allocation_Of_Referenced_Objects;
1260 -- Start of processing for Expand_N_Exception_Declaration
1262 begin
1263 -- There is no expansion needed when compiling for the JVM since the
1264 -- JVM has a built-in exception mechanism. See cil/gnatlib/a-except.ads
1265 -- for details.
1267 if VM_Target /= No_VM then
1268 return;
1269 end if;
1271 -- Definition of the external name: nam : constant String := "A.B.NAME";
1273 Insert_Action (N,
1274 Make_Object_Declaration (Loc,
1275 Defining_Identifier => Exname,
1276 Constant_Present => True,
1277 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1278 Expression =>
1279 Make_String_Literal (Loc,
1280 Strval => Fully_Qualified_Name_String (Id))));
1282 Set_Is_Statically_Allocated (Exname);
1284 -- Create the aggregate list for type Standard.Exception_Type:
1285 -- Handled_By_Other component: False
1287 Append_To (L, New_Occurrence_Of (Standard_False, Loc));
1289 -- Lang component: 'A'
1291 Append_To (L,
1292 Make_Character_Literal (Loc,
1293 Chars => Name_uA,
1294 Char_Literal_Value => UI_From_Int (Character'Pos ('A'))));
1296 -- Name_Length component: Nam'Length
1298 Append_To (L,
1299 Make_Attribute_Reference (Loc,
1300 Prefix => New_Occurrence_Of (Exname, Loc),
1301 Attribute_Name => Name_Length));
1303 -- Full_Name component: Standard.A_Char!(Nam'Address)
1305 Append_To (L, Unchecked_Convert_To (Standard_A_Char,
1306 Make_Attribute_Reference (Loc,
1307 Prefix => New_Occurrence_Of (Exname, Loc),
1308 Attribute_Name => Name_Address)));
1310 -- HTable_Ptr component: null
1312 Append_To (L, Make_Null (Loc));
1314 -- Import_Code component: 0
1316 Append_To (L, Make_Integer_Literal (Loc, 0));
1318 -- Raise_Hook component: null
1320 Append_To (L, Make_Null (Loc));
1322 Set_Expression (N, Make_Aggregate (Loc, Expressions => L));
1323 Analyze_And_Resolve (Expression (N), Etype (Id));
1325 Force_Static_Allocation_Of_Referenced_Objects (Expression (N));
1327 -- Register_Exception (except'Unchecked_Access);
1329 if not No_Exception_Handlers_Set
1330 and then not Restriction_Active (No_Exception_Registration)
1331 then
1332 L := New_List (
1333 Make_Procedure_Call_Statement (Loc,
1334 Name => New_Occurrence_Of (RTE (RE_Register_Exception), Loc),
1335 Parameter_Associations => New_List (
1336 Unchecked_Convert_To (RTE (RE_Exception_Data_Ptr),
1337 Make_Attribute_Reference (Loc,
1338 Prefix => New_Occurrence_Of (Id, Loc),
1339 Attribute_Name => Name_Unrestricted_Access)))));
1341 Set_Register_Exception_Call (Id, First (L));
1343 if not Is_Library_Level_Entity (Id) then
1344 Flag_Id := Make_Defining_Identifier (Loc,
1345 New_External_Name (Chars (Id), 'F'));
1347 Insert_Action (N,
1348 Make_Object_Declaration (Loc,
1349 Defining_Identifier => Flag_Id,
1350 Object_Definition =>
1351 New_Occurrence_Of (Standard_Boolean, Loc),
1352 Expression =>
1353 New_Occurrence_Of (Standard_True, Loc)));
1355 Set_Is_Statically_Allocated (Flag_Id);
1357 Append_To (L,
1358 Make_Assignment_Statement (Loc,
1359 Name => New_Occurrence_Of (Flag_Id, Loc),
1360 Expression => New_Occurrence_Of (Standard_False, Loc)));
1362 Insert_After_And_Analyze (N,
1363 Make_Implicit_If_Statement (N,
1364 Condition => New_Occurrence_Of (Flag_Id, Loc),
1365 Then_Statements => L));
1367 else
1368 Insert_List_After_And_Analyze (N, L);
1369 end if;
1370 end if;
1371 end Expand_N_Exception_Declaration;
1373 ---------------------------------------------
1374 -- Expand_N_Handled_Sequence_Of_Statements --
1375 ---------------------------------------------
1377 procedure Expand_N_Handled_Sequence_Of_Statements (N : Node_Id) is
1378 begin
1379 -- Expand exception handlers
1381 if Present (Exception_Handlers (N))
1382 and then not Restriction_Active (No_Exception_Handlers)
1383 then
1384 Expand_Exception_Handlers (N);
1385 end if;
1387 -- If local exceptions are being expanded, the previous call will
1388 -- have rewritten the construct as a block and reanalyzed it. No
1389 -- further expansion is needed.
1391 if Analyzed (N) then
1392 return;
1393 end if;
1395 -- Add clean up actions if required
1397 if Nkind (Parent (N)) /= N_Package_Body
1398 and then Nkind (Parent (N)) /= N_Accept_Statement
1399 and then Nkind (Parent (N)) /= N_Extended_Return_Statement
1400 and then not Delay_Cleanups (Current_Scope)
1401 then
1402 Expand_Cleanup_Actions (Parent (N));
1403 else
1404 Set_First_Real_Statement (N, First (Statements (N)));
1405 end if;
1406 end Expand_N_Handled_Sequence_Of_Statements;
1408 -------------------------------------
1409 -- Expand_N_Raise_Constraint_Error --
1410 -------------------------------------
1412 procedure Expand_N_Raise_Constraint_Error (N : Node_Id) is
1413 begin
1414 -- We adjust the condition to deal with the C/Fortran boolean case. This
1415 -- may well not be necessary, as all such conditions are generated by
1416 -- the expander and probably are all standard boolean, but who knows
1417 -- what strange optimization in future may require this adjustment!
1419 Adjust_Condition (Condition (N));
1421 -- Now deal with possible local raise handling
1423 Possible_Local_Raise (N, Standard_Constraint_Error);
1424 end Expand_N_Raise_Constraint_Error;
1426 ----------------------------------
1427 -- Expand_N_Raise_Program_Error --
1428 ----------------------------------
1430 procedure Expand_N_Raise_Program_Error (N : Node_Id) is
1431 begin
1432 -- We adjust the condition to deal with the C/Fortran boolean case. This
1433 -- may well not be necessary, as all such conditions are generated by
1434 -- the expander and probably are all standard boolean, but who knows
1435 -- what strange optimization in future may require this adjustment!
1437 Adjust_Condition (Condition (N));
1439 -- Now deal with possible local raise handling
1441 Possible_Local_Raise (N, Standard_Program_Error);
1442 end Expand_N_Raise_Program_Error;
1444 ------------------------------
1445 -- Expand_N_Raise_Statement --
1446 ------------------------------
1448 procedure Expand_N_Raise_Statement (N : Node_Id) is
1449 Loc : constant Source_Ptr := Sloc (N);
1450 Ehand : Node_Id;
1451 E : Entity_Id;
1452 Str : String_Id;
1453 H : Node_Id;
1454 Src : Boolean;
1456 begin
1457 -- Processing for locally handled exception (exclude reraise case)
1459 if Present (Name (N)) and then Nkind (Name (N)) = N_Identifier then
1460 if Debug_Flag_Dot_G
1461 or else Restriction_Active (No_Exception_Propagation)
1462 then
1463 -- If we have a local handler, then note that this is potentially
1464 -- able to be transformed into a goto statement.
1466 H := Find_Local_Handler (Entity (Name (N)), N);
1468 if Present (H) then
1469 if Local_Raise_Statements (H) = No_Elist then
1470 Set_Local_Raise_Statements (H, New_Elmt_List);
1471 end if;
1473 -- Append the new entry if it is not there already. Sometimes
1474 -- we have situations where due to reexpansion, the same node
1475 -- is analyzed twice and would otherwise be added twice.
1477 Append_Unique_Elmt (N, Local_Raise_Statements (H));
1478 Set_Has_Local_Raise (H);
1480 -- If no local handler, then generate no propagation warning
1482 else
1483 Warn_If_No_Propagation (N);
1484 end if;
1486 end if;
1487 end if;
1489 -- If a string expression is present, then the raise statement is
1490 -- converted to a call:
1491 -- Raise_Exception (exception-name'Identity, string);
1492 -- and there is nothing else to do.
1494 if Present (Expression (N)) then
1496 -- Avoid passing exception-name'identity in runtimes in which this
1497 -- argument is not used. This avoids generating undefined references
1498 -- to these exceptions when compiling with no optimization
1500 if Configurable_Run_Time_On_Target
1501 and then (Restriction_Active (No_Exception_Handlers)
1502 or else
1503 Restriction_Active (No_Exception_Propagation))
1504 then
1505 Rewrite (N,
1506 Make_Procedure_Call_Statement (Loc,
1507 Name => New_Occurrence_Of (RTE (RE_Raise_Exception), Loc),
1508 Parameter_Associations => New_List (
1509 New_Occurrence_Of (RTE (RE_Null_Id), Loc),
1510 Expression (N))));
1511 else
1512 Rewrite (N,
1513 Make_Procedure_Call_Statement (Loc,
1514 Name => New_Occurrence_Of (RTE (RE_Raise_Exception), Loc),
1515 Parameter_Associations => New_List (
1516 Make_Attribute_Reference (Loc,
1517 Prefix => Name (N),
1518 Attribute_Name => Name_Identity),
1519 Expression (N))));
1520 end if;
1522 Analyze (N);
1523 return;
1524 end if;
1526 -- Remaining processing is for the case where no string expression is
1527 -- present.
1529 -- Don't expand a raise statement that does not come from source if we
1530 -- have already had configurable run-time violations, since most likely
1531 -- it will be junk cascaded nonsense.
1533 if Configurable_Run_Time_Violations > 0
1534 and then not Comes_From_Source (N)
1535 then
1536 return;
1537 end if;
1539 -- Convert explicit raise of Program_Error, Constraint_Error, and
1540 -- Storage_Error into the corresponding raise (in High_Integrity_Mode
1541 -- all other raises will get normal expansion and be disallowed,
1542 -- but this is also faster in all modes). Propagate Comes_From_Source
1543 -- flag to the new node.
1545 if Present (Name (N)) and then Nkind (Name (N)) = N_Identifier then
1546 Src := Comes_From_Source (N);
1548 if Entity (Name (N)) = Standard_Constraint_Error then
1549 Rewrite (N,
1550 Make_Raise_Constraint_Error (Loc, Reason => CE_Explicit_Raise));
1551 Set_Comes_From_Source (N, Src);
1552 Analyze (N);
1553 return;
1555 elsif Entity (Name (N)) = Standard_Program_Error then
1556 Rewrite (N,
1557 Make_Raise_Program_Error (Loc, Reason => PE_Explicit_Raise));
1558 Set_Comes_From_Source (N, Src);
1559 Analyze (N);
1560 return;
1562 elsif Entity (Name (N)) = Standard_Storage_Error then
1563 Rewrite (N,
1564 Make_Raise_Storage_Error (Loc, Reason => SE_Explicit_Raise));
1565 Set_Comes_From_Source (N, Src);
1566 Analyze (N);
1567 return;
1568 end if;
1569 end if;
1571 -- Case of name present, in this case we expand raise name to
1573 -- Raise_Exception (name'Identity, location_string);
1575 -- where location_string identifies the file/line of the raise
1577 if Present (Name (N)) then
1578 declare
1579 Id : Entity_Id := Entity (Name (N));
1581 begin
1582 Name_Len := 0;
1583 Build_Location_String (Loc);
1585 -- If the exception is a renaming, use the exception that it
1586 -- renames (which might be a predefined exception, e.g.).
1588 if Present (Renamed_Object (Id)) then
1589 Id := Renamed_Object (Id);
1590 end if;
1592 -- Build a C-compatible string in case of no exception handlers,
1593 -- since this is what the last chance handler is expecting.
1595 if No_Exception_Handlers_Set then
1597 -- Generate an empty message if configuration pragma
1598 -- Suppress_Exception_Locations is set for this unit.
1600 if Opt.Exception_Locations_Suppressed then
1601 Name_Len := 1;
1602 else
1603 Name_Len := Name_Len + 1;
1604 end if;
1606 Name_Buffer (Name_Len) := ASCII.NUL;
1607 end if;
1609 if Opt.Exception_Locations_Suppressed then
1610 Name_Len := 0;
1611 end if;
1613 Str := String_From_Name_Buffer;
1615 -- For VMS exceptions, convert the raise into a call to
1616 -- lib$stop so it will be handled by __gnat_error_handler.
1618 if Is_VMS_Exception (Id) then
1619 declare
1620 Excep_Image : String_Id;
1621 Cond : Node_Id;
1623 begin
1624 if Present (Interface_Name (Id)) then
1625 Excep_Image := Strval (Interface_Name (Id));
1626 else
1627 Get_Name_String (Chars (Id));
1628 Set_All_Upper_Case;
1629 Excep_Image := String_From_Name_Buffer;
1630 end if;
1632 if Exception_Code (Id) /= No_Uint then
1633 Cond :=
1634 Make_Integer_Literal (Loc, Exception_Code (Id));
1635 else
1636 Cond :=
1637 Unchecked_Convert_To (Standard_Integer,
1638 Make_Function_Call (Loc,
1639 Name => New_Occurrence_Of
1640 (RTE (RE_Import_Value), Loc),
1641 Parameter_Associations => New_List
1642 (Make_String_Literal (Loc,
1643 Strval => Excep_Image))));
1644 end if;
1646 Rewrite (N,
1647 Make_Procedure_Call_Statement (Loc,
1648 Name =>
1649 New_Occurrence_Of (RTE (RE_Lib_Stop), Loc),
1650 Parameter_Associations => New_List (Cond)));
1651 Analyze_And_Resolve (Cond, Standard_Integer);
1652 end;
1654 -- Not VMS exception case, convert raise to call to the
1655 -- Raise_Exception routine.
1657 else
1658 Rewrite (N,
1659 Make_Procedure_Call_Statement (Loc,
1660 Name => New_Occurrence_Of (RTE (RE_Raise_Exception), Loc),
1661 Parameter_Associations => New_List (
1662 Make_Attribute_Reference (Loc,
1663 Prefix => Name (N),
1664 Attribute_Name => Name_Identity),
1665 Make_String_Literal (Loc,
1666 Strval => Str))));
1667 end if;
1668 end;
1670 -- Case of no name present (reraise). We rewrite the raise to:
1672 -- Reraise_Occurrence_Always (EO);
1674 -- where EO is the current exception occurrence. If the current handler
1675 -- does not have a choice parameter specification, then we provide one.
1677 else
1678 -- Bypass expansion to a run-time call when back-end exception
1679 -- handling is active, unless the target is a VM, CodePeer or
1680 -- GNATprove. In CodePeer, raising an exception is treated as an
1681 -- error, while in GNATprove all code with exceptions falls outside
1682 -- the subset of code which can be formally analyzed.
1684 if VM_Target = No_VM
1685 and then not CodePeer_Mode
1686 and then Exception_Mechanism = Back_End_Exceptions
1687 then
1688 return;
1689 end if;
1691 -- Find innermost enclosing exception handler (there must be one,
1692 -- since the semantics has already verified that this raise statement
1693 -- is valid, and a raise with no arguments is only permitted in the
1694 -- context of an exception handler.
1696 Ehand := Parent (N);
1697 while Nkind (Ehand) /= N_Exception_Handler loop
1698 Ehand := Parent (Ehand);
1699 end loop;
1701 -- Make exception choice parameter if none present. Note that we do
1702 -- not need to put the entity on the entity chain, since no one will
1703 -- be referencing this entity by normal visibility methods.
1705 if No (Choice_Parameter (Ehand)) then
1706 E := Make_Temporary (Loc, 'E');
1707 Set_Choice_Parameter (Ehand, E);
1708 Set_Ekind (E, E_Variable);
1709 Set_Etype (E, RTE (RE_Exception_Occurrence));
1710 Set_Scope (E, Current_Scope);
1711 end if;
1713 -- Now rewrite the raise as a call to Reraise. A special case arises
1714 -- if this raise statement occurs in the context of a handler for
1715 -- all others (i.e. an at end handler). in this case we avoid
1716 -- the call to defer abort, cleanup routines are expected to be
1717 -- called in this case with aborts deferred.
1719 declare
1720 Ech : constant Node_Id := First (Exception_Choices (Ehand));
1721 Ent : Entity_Id;
1723 begin
1724 if Nkind (Ech) = N_Others_Choice
1725 and then All_Others (Ech)
1726 then
1727 Ent := RTE (RE_Reraise_Occurrence_No_Defer);
1728 else
1729 Ent := RTE (RE_Reraise_Occurrence_Always);
1730 end if;
1732 Rewrite (N,
1733 Make_Procedure_Call_Statement (Loc,
1734 Name => New_Occurrence_Of (Ent, Loc),
1735 Parameter_Associations => New_List (
1736 New_Occurrence_Of (Choice_Parameter (Ehand), Loc))));
1737 end;
1738 end if;
1740 Analyze (N);
1741 end Expand_N_Raise_Statement;
1743 ----------------------------------
1744 -- Expand_N_Raise_Storage_Error --
1745 ----------------------------------
1747 procedure Expand_N_Raise_Storage_Error (N : Node_Id) is
1748 begin
1749 -- We adjust the condition to deal with the C/Fortran boolean case. This
1750 -- may well not be necessary, as all such conditions are generated by
1751 -- the expander and probably are all standard boolean, but who knows
1752 -- what strange optimization in future may require this adjustment!
1754 Adjust_Condition (Condition (N));
1756 -- Now deal with possible local raise handling
1758 Possible_Local_Raise (N, Standard_Storage_Error);
1759 end Expand_N_Raise_Storage_Error;
1761 --------------------------
1762 -- Possible_Local_Raise --
1763 --------------------------
1765 procedure Possible_Local_Raise (N : Node_Id; E : Entity_Id) is
1766 begin
1767 -- Nothing to do if local raise optimization not active
1769 if not Debug_Flag_Dot_G
1770 and then not Restriction_Active (No_Exception_Propagation)
1771 then
1772 return;
1773 end if;
1775 -- Nothing to do if original node was an explicit raise, because in
1776 -- that case, we already generated the required warning for the raise.
1778 if Nkind (Original_Node (N)) = N_Raise_Statement then
1779 return;
1780 end if;
1782 -- Otherwise see if we have a local handler for the exception
1784 declare
1785 H : constant Node_Id := Find_Local_Handler (E, N);
1787 begin
1788 -- If so, mark that it has a local raise
1790 if Present (H) then
1791 Set_Has_Local_Raise (H, True);
1793 -- Otherwise, if the No_Exception_Propagation restriction is active
1794 -- and the warning is enabled, generate the appropriate warnings.
1796 elsif Warn_On_Non_Local_Exception
1797 and then Restriction_Active (No_Exception_Propagation)
1798 then
1799 Warn_No_Exception_Propagation_Active (N);
1801 if Configurable_Run_Time_Mode then
1802 Error_Msg_NE
1803 ("\?& may call Last_Chance_Handler", N, E);
1804 else
1805 Error_Msg_NE
1806 ("\?& may result in unhandled exception", N, E);
1807 end if;
1808 end if;
1809 end;
1810 end Possible_Local_Raise;
1812 ------------------------------
1813 -- Expand_N_Subprogram_Info --
1814 ------------------------------
1816 procedure Expand_N_Subprogram_Info (N : Node_Id) is
1817 Loc : constant Source_Ptr := Sloc (N);
1819 begin
1820 -- For now, we replace an Expand_N_Subprogram_Info node with an
1821 -- attribute reference that gives the address of the procedure.
1822 -- This is because gigi does not yet recognize this node, and
1823 -- for the initial targets, this is the right value anyway.
1825 Rewrite (N,
1826 Make_Attribute_Reference (Loc,
1827 Prefix => Identifier (N),
1828 Attribute_Name => Name_Code_Address));
1830 Analyze_And_Resolve (N, RTE (RE_Code_Loc));
1831 end Expand_N_Subprogram_Info;
1833 ------------------------
1834 -- Find_Local_Handler --
1835 ------------------------
1837 function Find_Local_Handler
1838 (Ename : Entity_Id;
1839 Nod : Node_Id) return Node_Id
1841 N : Node_Id;
1842 P : Node_Id;
1843 H : Node_Id;
1844 C : Node_Id;
1846 SSE : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
1847 -- This is used to test for wrapped actions below
1849 ERaise : Entity_Id;
1850 EHandle : Entity_Id;
1851 -- The entity Id's for the exception we are raising and handling, using
1852 -- the renamed exception if a Renamed_Entity is present.
1854 begin
1855 -- Never any local handler if all handlers removed
1857 if Debug_Flag_Dot_X then
1858 return Empty;
1859 end if;
1861 -- Get the exception we are raising, allowing for renaming
1863 ERaise := Get_Renamed_Entity (Ename);
1865 -- We need to check if the node we are looking at is contained in
1868 -- Loop to search up the tree
1870 N := Nod;
1871 loop
1872 P := Parent (N);
1874 -- If we get to the top of the tree, or to a subprogram, task, entry,
1875 -- protected body, or accept statement without having found a
1876 -- matching handler, then there is no local handler.
1878 if No (P)
1879 or else Nkind (P) = N_Subprogram_Body
1880 or else Nkind (P) = N_Task_Body
1881 or else Nkind (P) = N_Protected_Body
1882 or else Nkind (P) = N_Entry_Body
1883 or else Nkind (P) = N_Accept_Statement
1884 then
1885 return Empty;
1887 -- Test for handled sequence of statements with at least one
1888 -- exception handler which might be the one we are looking for.
1890 elsif Nkind (P) = N_Handled_Sequence_Of_Statements
1891 and then Present (Exception_Handlers (P))
1892 then
1893 -- Before we proceed we need to check if the node N is covered
1894 -- by the statement part of P rather than one of its exception
1895 -- handlers (an exception handler obviously does not cover its
1896 -- own statements).
1898 -- This test is more delicate than might be thought. It is not
1899 -- just a matter of checking the Statements (P), because the node
1900 -- might be waiting to be wrapped in a transient scope, in which
1901 -- case it will end up in the block statements, even though it
1902 -- is not there now.
1904 if Is_List_Member (N)
1905 and then (List_Containing (N) = Statements (P)
1906 or else
1907 List_Containing (N) = SSE.Actions_To_Be_Wrapped_Before
1908 or else
1909 List_Containing (N) = SSE.Actions_To_Be_Wrapped_After)
1910 then
1911 -- Loop through exception handlers
1913 H := First (Exception_Handlers (P));
1914 while Present (H) loop
1916 -- Loop through choices in one handler
1918 C := First (Exception_Choices (H));
1919 while Present (C) loop
1921 -- Deal with others case
1923 if Nkind (C) = N_Others_Choice then
1925 -- Matching others handler, but we need to ensure
1926 -- there is no choice parameter. If there is, then we
1927 -- don't have a local handler after all (since we do
1928 -- not allow choice parameters for local handlers).
1930 if No (Choice_Parameter (H)) then
1931 return H;
1932 else
1933 return Empty;
1934 end if;
1936 -- If not others must be entity name
1938 elsif Nkind (C) /= N_Others_Choice then
1939 pragma Assert (Is_Entity_Name (C));
1940 pragma Assert (Present (Entity (C)));
1942 -- Get exception being handled, dealing with renaming
1944 EHandle := Get_Renamed_Entity (Entity (C));
1946 -- If match, then check choice parameter
1948 if ERaise = EHandle then
1949 if No (Choice_Parameter (H)) then
1950 return H;
1951 else
1952 return Empty;
1953 end if;
1954 end if;
1955 end if;
1957 Next (C);
1958 end loop;
1960 Next (H);
1961 end loop;
1962 end if;
1963 end if;
1965 N := P;
1966 end loop;
1967 end Find_Local_Handler;
1969 ---------------------------------
1970 -- Get_Local_Raise_Call_Entity --
1971 ---------------------------------
1973 -- Note: this is primary provided for use by the back end in generating
1974 -- calls to Local_Raise. But it would be too late in the back end to call
1975 -- RTE if this actually caused a load/analyze of the unit. So what we do
1976 -- is to ensure there is a dummy call to this function during front end
1977 -- processing so that the unit gets loaded then, and not later.
1979 Local_Raise_Call_Entity : Entity_Id;
1980 Local_Raise_Call_Entity_Set : Boolean := False;
1982 function Get_Local_Raise_Call_Entity return Entity_Id is
1983 begin
1984 if not Local_Raise_Call_Entity_Set then
1985 Local_Raise_Call_Entity_Set := True;
1987 if RTE_Available (RE_Local_Raise) then
1988 Local_Raise_Call_Entity := RTE (RE_Local_Raise);
1989 else
1990 Local_Raise_Call_Entity := Empty;
1991 end if;
1992 end if;
1994 return Local_Raise_Call_Entity;
1995 end Get_Local_Raise_Call_Entity;
1997 -----------------------------
1998 -- Get_RT_Exception_Entity --
1999 -----------------------------
2001 function Get_RT_Exception_Entity (R : RT_Exception_Code) return Entity_Id is
2002 begin
2003 case R is
2004 when RT_CE_Exceptions => return Standard_Constraint_Error;
2005 when RT_PE_Exceptions => return Standard_Program_Error;
2006 when RT_SE_Exceptions => return Standard_Storage_Error;
2007 end case;
2008 end Get_RT_Exception_Entity;
2010 ----------------------
2011 -- Is_Non_Ada_Error --
2012 ----------------------
2014 function Is_Non_Ada_Error (E : Entity_Id) return Boolean is
2015 begin
2016 if not OpenVMS_On_Target then
2017 return False;
2018 end if;
2020 Get_Name_String (Chars (E));
2022 -- Note: it is a little irregular for the body of exp_ch11 to know
2023 -- the details of the encoding scheme for names, but on the other
2024 -- hand, gigi knows them, and this is for gigi's benefit anyway!
2026 if Name_Buffer (1 .. 30) /= "system__aux_dec__non_ada_error" then
2027 return False;
2028 end if;
2030 return True;
2031 end Is_Non_Ada_Error;
2033 ----------------------------
2034 -- Warn_If_No_Propagation --
2035 ----------------------------
2037 procedure Warn_If_No_Propagation (N : Node_Id) is
2038 begin
2039 if Restriction_Check_Required (No_Exception_Propagation)
2040 and then Warn_On_Non_Local_Exception
2041 then
2042 Warn_No_Exception_Propagation_Active (N);
2044 if Configurable_Run_Time_Mode then
2045 Error_Msg_N
2046 ("\?Last_Chance_Handler will be called on exception", N);
2047 else
2048 Error_Msg_N
2049 ("\?execution may raise unhandled exception", N);
2050 end if;
2051 end if;
2052 end Warn_If_No_Propagation;
2054 ------------------------------------------
2055 -- Warn_No_Exception_Propagation_Active --
2056 ------------------------------------------
2058 procedure Warn_No_Exception_Propagation_Active (N : Node_Id) is
2059 begin
2060 Error_Msg_N
2061 ("?pragma Restrictions (No_Exception_Propagation) in effect", N);
2062 end Warn_No_Exception_Propagation_Active;
2064 end Exp_Ch11;