PR rtl-optimization/57003
[official-gcc.git] / gcc / ada / exp_ch11.adb
blobaafa2b4fdb60a4f8218e71310e0b20f5c3c4679d
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-2014, 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 Debug; use Debug;
28 with Einfo; use Einfo;
29 with Elists; use Elists;
30 with Errout; use Errout;
31 with Exp_Ch7; use Exp_Ch7;
32 with Exp_Util; use Exp_Util;
33 with Namet; use Namet;
34 with Nlists; use Nlists;
35 with Nmake; use Nmake;
36 with Opt; use Opt;
37 with Restrict; use Restrict;
38 with Rident; use Rident;
39 with Rtsfind; use Rtsfind;
40 with Sem; use Sem;
41 with Sem_Ch8; use Sem_Ch8;
42 with Sem_Res; use Sem_Res;
43 with Sem_Util; use Sem_Util;
44 with Sinfo; use Sinfo;
45 with Sinput; use Sinput;
46 with Snames; use Snames;
47 with Stand; use Stand;
48 with Stringt; use Stringt;
49 with Targparm; use Targparm;
50 with Tbuild; use Tbuild;
51 with Uintp; use Uintp;
53 package body Exp_Ch11 is
55 -----------------------
56 -- Local Subprograms --
57 -----------------------
59 procedure Warn_No_Exception_Propagation_Active (N : Node_Id);
60 -- Generates warning that pragma Restrictions (No_Exception_Propagation)
61 -- is in effect. Caller then generates appropriate continuation message.
62 -- N is the node on which the warning is placed.
64 procedure Warn_If_No_Propagation (N : Node_Id);
65 -- Called for an exception raise that is not a local raise (and thus can
66 -- not be optimized to a goto. Issues warning if No_Exception_Propagation
67 -- restriction is set. N is the node for the raise or equivalent call.
69 ---------------------------
70 -- Expand_At_End_Handler --
71 ---------------------------
73 -- For a handled statement sequence that has a cleanup (At_End_Proc
74 -- field set), an exception handler of the following form is required:
76 -- exception
77 -- when all others =>
78 -- cleanup call
79 -- raise;
81 -- Note: this exception handler is treated rather specially by
82 -- subsequent expansion in two respects:
84 -- The normal call to Undefer_Abort is omitted
85 -- The raise call does not do Defer_Abort
87 -- This is because the current tasking code seems to assume that
88 -- the call to the cleanup routine that is made from an exception
89 -- handler for the abort signal is called with aborts deferred.
91 -- This expansion is only done if we have front end exception handling.
92 -- If we have back end exception handling, then the AT END handler is
93 -- left alone, and cleanups (including the exceptional case) are handled
94 -- by the back end.
96 -- In the front end case, the exception handler described above handles
97 -- the exceptional case. The AT END handler is left in the generated tree
98 -- and the code generator (e.g. gigi) must still handle proper generation
99 -- of cleanup calls for the non-exceptional case.
101 procedure Expand_At_End_Handler (HSS : Node_Id; Block : Node_Id) is
102 Clean : constant Entity_Id := Entity (At_End_Proc (HSS));
103 Ohandle : Node_Id;
104 Stmnts : List_Id;
106 Loc : constant Source_Ptr := No_Location;
107 -- Location used for expansion. We quite deliberately do not set a
108 -- specific source location for the expanded handler. This makes
109 -- sense since really the handler is not associated with specific
110 -- source. We used to set this to Sloc (Clean), but that caused
111 -- useless and annoying bouncing around of line numbers in the
112 -- debugger in some circumstances.
114 begin
115 pragma Assert (Present (Clean));
116 pragma Assert (No (Exception_Handlers (HSS)));
118 -- Don't expand if back end exception handling active
120 if Exception_Mechanism = Back_End_Exceptions then
121 return;
122 end if;
124 -- Don't expand an At End handler if we have already had configurable
125 -- run-time violations, since likely this will just be a matter of
126 -- generating useless cascaded messages
128 if Configurable_Run_Time_Violations > 0 then
129 return;
130 end if;
132 -- Don't expand an At End handler if we are not allowing exceptions
133 -- or if exceptions are transformed into local gotos, and never
134 -- propagated (No_Exception_Propagation).
136 if No_Exception_Handlers_Set then
137 return;
138 end if;
140 if Present (Block) then
141 Push_Scope (Block);
142 end if;
144 Ohandle :=
145 Make_Others_Choice (Loc);
146 Set_All_Others (Ohandle);
148 Stmnts := New_List (
149 Make_Procedure_Call_Statement (Loc,
150 Name => New_Occurrence_Of (Clean, Loc)));
152 -- Generate reraise statement as last statement of AT-END handler,
153 -- unless we are under control of No_Exception_Propagation, in which
154 -- case no exception propagation is possible anyway, so we do not need
155 -- a reraise (the AT END handler in this case is only for normal exits
156 -- not for exceptional exits). Also, we flag the Reraise statement as
157 -- being part of an AT END handler to prevent signalling this reraise
158 -- as a violation of the restriction when it is not set.
160 if not Restriction_Active (No_Exception_Propagation) then
161 declare
162 Rstm : constant Node_Id := Make_Raise_Statement (Loc);
163 begin
164 Set_From_At_End (Rstm);
165 Append_To (Stmnts, Rstm);
166 end;
167 end if;
169 Set_Exception_Handlers (HSS, New_List (
170 Make_Implicit_Exception_Handler (Loc,
171 Exception_Choices => New_List (Ohandle),
172 Statements => Stmnts)));
174 Analyze_List (Stmnts, Suppress => All_Checks);
175 Expand_Exception_Handlers (HSS);
177 if Present (Block) then
178 Pop_Scope;
179 end if;
180 end Expand_At_End_Handler;
182 -------------------------------
183 -- Expand_Exception_Handlers --
184 -------------------------------
186 procedure Expand_Exception_Handlers (HSS : Node_Id) is
187 Handlrs : constant List_Id := Exception_Handlers (HSS);
188 Loc : constant Source_Ptr := Sloc (HSS);
189 Handler : Node_Id;
190 Others_Choice : Boolean;
191 Obj_Decl : Node_Id;
192 Next_Handler : Node_Id;
194 procedure Expand_Local_Exception_Handlers;
195 -- This procedure handles the expansion of exception handlers for the
196 -- optimization of local raise statements into goto statements.
198 procedure Prepend_Call_To_Handler
199 (Proc : RE_Id;
200 Args : List_Id := No_List);
201 -- Routine to prepend a call to the procedure referenced by Proc at
202 -- the start of the handler code for the current Handler.
204 procedure Replace_Raise_By_Goto (Raise_S : Node_Id; Goto_L1 : Node_Id);
205 -- Raise_S is a raise statement (possibly expanded, and possibly of the
206 -- form of a Raise_xxx_Error node with a condition. This procedure is
207 -- called to replace the raise action with the (already analyzed) goto
208 -- statement passed as Goto_L1. This procedure also takes care of the
209 -- requirement of inserting a Local_Raise call where possible.
211 -------------------------------------
212 -- Expand_Local_Exception_Handlers --
213 -------------------------------------
215 -- There are two cases for this transformation. First the case of
216 -- explicit raise statements. For this case, the transformation we do
217 -- looks like this. Right now we have for example (where L1, L2 are
218 -- exception labels)
220 -- begin
221 -- ...
222 -- raise_exception (excep1'identity); -- was raise excep1
223 -- ...
224 -- raise_exception (excep2'identity); -- was raise excep2
225 -- ...
226 -- exception
227 -- when excep1 =>
228 -- estmts1
229 -- when excep2 =>
230 -- estmts2
231 -- end;
233 -- This gets transformed into:
235 -- begin
236 -- L1 : label; -- marked Exception_Junk
237 -- L2 : label; -- marked Exception_Junk
238 -- L3 : label; -- marked Exception_Junk
240 -- begin -- marked Exception_Junk
241 -- ...
242 -- local_raise (excep1'address); -- was raise excep1
243 -- goto L1;
244 -- ...
245 -- local_raise (excep2'address); -- was raise excep2
246 -- goto L2;
247 -- ...
248 -- exception
249 -- when excep1 =>
250 -- goto L1;
251 -- when excep2 =>
252 -- goto L2;
253 -- end;
255 -- goto L3; -- skip handler if no raise, marked Exception_Junk
257 -- <<L1>> -- local excep target label, marked Exception_Junk
258 -- begin -- marked Exception_Junk
259 -- estmts1
260 -- end;
261 -- goto L3; -- marked Exception_Junk
263 -- <<L2>> -- marked Exception_Junk
264 -- begin -- marked Exception_Junk
265 -- estmts2
266 -- end;
267 -- goto L3; -- marked Exception_Junk
268 -- <<L3>> -- marked Exception_Junk
269 -- end;
271 -- Note: the reason we wrap the original statement sequence in an
272 -- inner block is that there may be raise statements within the
273 -- sequence of statements in the handlers, and we must ensure that
274 -- these are properly handled, and in particular, such raise statements
275 -- must not reenter the same exception handlers.
277 -- If the restriction No_Exception_Propagation is in effect, then we
278 -- can omit the exception handlers.
280 -- begin
281 -- L1 : label; -- marked Exception_Junk
282 -- L2 : label; -- marked Exception_Junk
283 -- L3 : label; -- marked Exception_Junk
285 -- begin -- marked Exception_Junk
286 -- ...
287 -- local_raise (excep1'address); -- was raise excep1
288 -- goto L1;
289 -- ...
290 -- local_raise (excep2'address); -- was raise excep2
291 -- goto L2;
292 -- ...
293 -- end;
295 -- goto L3; -- skip handler if no raise, marked Exception_Junk
297 -- <<L1>> -- local excep target label, marked Exception_Junk
298 -- begin -- marked Exception_Junk
299 -- estmts1
300 -- end;
301 -- goto L3; -- marked Exception_Junk
303 -- <<L2>> -- marked Exception_Junk
304 -- begin -- marked Exception_Junk
305 -- estmts2
306 -- end;
308 -- <<L3>> -- marked Exception_Junk
309 -- end;
311 -- The second case is for exceptions generated by the back end in one
312 -- of three situations:
314 -- 1. Front end generates N_Raise_xxx_Error node
315 -- 2. Front end sets Do_xxx_Check flag in subexpression node
316 -- 3. Back end detects a situation where an exception is appropriate
318 -- In all these cases, the current processing in gigi is to generate a
319 -- call to the appropriate Rcheck_xx routine (where xx encodes both the
320 -- exception message and the exception to be raised, Constraint_Error,
321 -- Program_Error, or Storage_Error.
323 -- We could handle some subcases of 1 using the same front end expansion
324 -- into gotos, but even for case 1, we can't handle all cases, since
325 -- generating gotos in the middle of expressions is not possible (it's
326 -- possible at the gigi/gcc level, but not at the level of the GNAT
327 -- tree).
329 -- In any case, it seems easier to have a scheme which handles all three
330 -- cases in a uniform manner. So here is how we proceed in this case.
332 -- This procedure detects all handlers for these three exceptions,
333 -- Constraint_Error, Program_Error and Storage_Error (including WHEN
334 -- OTHERS handlers that cover one or more of these cases).
336 -- If the handler meets the requirements for being the target of a local
337 -- raise, then the front end does the expansion described previously,
338 -- creating a label to be used as a goto target to raise the exception.
339 -- However, no attempt is made in the front end to convert any related
340 -- raise statements into gotos, e.g. all N_Raise_xxx_Error nodes are
341 -- left unchanged and passed to the back end.
343 -- Instead, the front end generates three nodes
345 -- N_Push_Constraint_Error_Label
346 -- N_Push_Program_Error_Label
347 -- N_Push_Storage_Error_Label
349 -- The Push node is generated at the start of the statements
350 -- covered by the handler, and has as a parameter the label to be
351 -- used as the raise target.
353 -- N_Pop_Constraint_Error_Label
354 -- N_Pop_Program_Error_Label
355 -- N_Pop_Storage_Error_Label
357 -- The Pop node is generated at the end of the covered statements
358 -- and undoes the effect of the preceding corresponding Push node.
360 -- In the case where the handler does NOT meet the requirements, the
361 -- front end will still generate the Push and Pop nodes, but the label
362 -- field in the Push node will be empty signifying that for this region
363 -- of code, no optimization is possible.
365 -- These Push/Pop nodes are inhibited if No_Exception_Handlers is set
366 -- since they are useless in this case, and in CodePeer mode, where
367 -- they serve no purpose and can intefere with the analysis.
369 -- The back end must maintain three stacks, one for each exception case,
370 -- the Push node pushes an entry onto the corresponding stack, and Pop
371 -- node pops off the entry. Then instead of calling Rcheck_nn, if the
372 -- corresponding top stack entry has an non-empty label, a goto is
373 -- generated. This goto should be preceded by a call to Local_Raise as
374 -- described above.
376 -- An example of this transformation is as follows, given:
378 -- declare
379 -- A : Integer range 1 .. 10;
380 -- begin
381 -- A := B + C;
382 -- exception
383 -- when Constraint_Error =>
384 -- estmts
385 -- end;
387 -- gets transformed to:
389 -- declare
390 -- A : Integer range 1 .. 10;
392 -- begin
393 -- L1 : label;
394 -- L2 : label;
396 -- begin
397 -- %push_constraint_error_label (L1)
398 -- R1b : constant long_long_integer := long_long_integer?(b) +
399 -- long_long_integer?(c);
400 -- [constraint_error when
401 -- not (R1b in -16#8000_0000# .. 16#7FFF_FFFF#)
402 -- "overflow check failed"]
403 -- a := integer?(R1b);
404 -- %pop_constraint_error_Label
406 -- exception
407 -- ...
408 -- when constraint_error =>
409 -- goto L1;
410 -- end;
412 -- goto L2; -- skip handler when exception not raised
413 -- <<L1>> -- target label for local exception
414 -- estmts
415 -- <<L2>>
416 -- end;
418 -- Note: the generated labels and goto statements all have the flag
419 -- Exception_Junk set True, so that Sem_Ch6.Check_Returns will ignore
420 -- this generated exception stuff when checking for missing return
421 -- statements (see circuitry in Check_Statement_Sequence).
423 -- Note: All of the processing described above occurs only if
424 -- restriction No_Exception_Propagation applies or debug flag .g is
425 -- enabled.
427 CE_Locally_Handled : Boolean := False;
428 SE_Locally_Handled : Boolean := False;
429 PE_Locally_Handled : Boolean := False;
430 -- These three flags indicate whether a handler for the corresponding
431 -- exception (CE=Constraint_Error, SE=Storage_Error, PE=Program_Error)
432 -- is present. If so the switch is set to True, the Exception_Label
433 -- field of the corresponding handler is set, and appropriate Push
434 -- and Pop nodes are inserted into the code.
436 Local_Expansion_Required : Boolean := False;
437 -- Set True if we have at least one handler requiring local raise
438 -- expansion as described above.
440 procedure Expand_Local_Exception_Handlers is
442 procedure Add_Exception_Label (H : Node_Id);
443 -- H is an exception handler. First check for an Exception_Label
444 -- already allocated for H. If none, allocate one, set the field in
445 -- the handler node, add the label declaration, and set the flag
446 -- Local_Expansion_Required. Note: if Local_Raise_Not_OK is set
447 -- the call has no effect and Exception_Label is left empty.
449 procedure Add_Label_Declaration (L : Entity_Id);
450 -- Add an implicit declaration of the given label to the declaration
451 -- list in the parent of the current sequence of handled statements.
453 generic
454 Exc_Locally_Handled : in out Boolean;
455 -- Flag indicating whether a local handler for this exception
456 -- has already been generated.
458 with function Make_Push_Label (Loc : Source_Ptr) return Node_Id;
459 -- Function to create a Push_xxx_Label node
461 with function Make_Pop_Label (Loc : Source_Ptr) return Node_Id;
462 -- Function to create a Pop_xxx_Label node
464 procedure Generate_Push_Pop (H : Node_Id);
465 -- Common code for Generate_Push_Pop_xxx below, used to generate an
466 -- exception label and Push/Pop nodes for Constraint_Error,
467 -- Program_Error, or Storage_Error.
469 -------------------------
470 -- Add_Exception_Label --
471 -------------------------
473 procedure Add_Exception_Label (H : Node_Id) is
474 begin
475 if No (Exception_Label (H))
476 and then not Local_Raise_Not_OK (H)
477 and then not Special_Exception_Package_Used
478 then
479 Local_Expansion_Required := True;
481 declare
482 L : constant Entity_Id := Make_Temporary (Sloc (H), 'L');
483 begin
484 Set_Exception_Label (H, L);
485 Add_Label_Declaration (L);
486 end;
487 end if;
488 end Add_Exception_Label;
490 ---------------------------
491 -- Add_Label_Declaration --
492 ---------------------------
494 procedure Add_Label_Declaration (L : Entity_Id) is
495 P : constant Node_Id := Parent (HSS);
497 Decl_L : constant Node_Id :=
498 Make_Implicit_Label_Declaration (Loc,
499 Defining_Identifier => L);
501 begin
502 if Declarations (P) = No_List then
503 Set_Declarations (P, Empty_List);
504 end if;
506 Append (Decl_L, Declarations (P));
507 Analyze (Decl_L);
508 end Add_Label_Declaration;
510 -----------------------
511 -- Generate_Push_Pop --
512 -----------------------
514 procedure Generate_Push_Pop (H : Node_Id) is
515 begin
516 if Restriction_Active (No_Exception_Handlers)
517 or else CodePeer_Mode
518 then
519 return;
520 end if;
522 if Exc_Locally_Handled then
523 return;
524 else
525 Exc_Locally_Handled := True;
526 end if;
528 Add_Exception_Label (H);
530 declare
531 F : constant Node_Id := First (Statements (HSS));
532 L : constant Node_Id := Last (Statements (HSS));
534 Push : constant Node_Id := Make_Push_Label (Sloc (F));
535 Pop : constant Node_Id := Make_Pop_Label (Sloc (L));
537 begin
538 -- We make sure that a call to Get_Local_Raise_Call_Entity is
539 -- made during front end processing, so that when we need it
540 -- in the back end, it will already be available and loaded.
542 Discard_Node (Get_Local_Raise_Call_Entity);
544 -- Prepare and insert Push and Pop nodes
546 Set_Exception_Label (Push, Exception_Label (H));
547 Insert_Before (F, Push);
548 Set_Analyzed (Push);
550 Insert_After (L, Pop);
551 Set_Analyzed (Pop);
552 end;
553 end Generate_Push_Pop;
555 -- Local declarations
557 Loc : constant Source_Ptr := Sloc (HSS);
558 Stmts : List_Id := No_List;
559 Choice : Node_Id;
560 Excep : Entity_Id;
562 procedure Generate_Push_Pop_For_Constraint_Error is
563 new Generate_Push_Pop
564 (Exc_Locally_Handled => CE_Locally_Handled,
565 Make_Push_Label => Make_Push_Constraint_Error_Label,
566 Make_Pop_Label => Make_Pop_Constraint_Error_Label);
567 -- If no Push/Pop has been generated for CE yet, then set the flag
568 -- CE_Locally_Handled, allocate an Exception_Label for handler H (if
569 -- not already done), and generate Push/Pop nodes for the exception
570 -- label at the start and end of the statements of HSS.
572 procedure Generate_Push_Pop_For_Program_Error is
573 new Generate_Push_Pop
574 (Exc_Locally_Handled => PE_Locally_Handled,
575 Make_Push_Label => Make_Push_Program_Error_Label,
576 Make_Pop_Label => Make_Pop_Program_Error_Label);
577 -- If no Push/Pop has been generated for PE yet, then set the flag
578 -- PE_Locally_Handled, allocate an Exception_Label for handler H (if
579 -- not already done), and generate Push/Pop nodes for the exception
580 -- label at the start and end of the statements of HSS.
582 procedure Generate_Push_Pop_For_Storage_Error is
583 new Generate_Push_Pop
584 (Exc_Locally_Handled => SE_Locally_Handled,
585 Make_Push_Label => Make_Push_Storage_Error_Label,
586 Make_Pop_Label => Make_Pop_Storage_Error_Label);
587 -- If no Push/Pop has been generated for SE yet, then set the flag
588 -- SE_Locally_Handled, allocate an Exception_Label for handler H (if
589 -- not already done), and generate Push/Pop nodes for the exception
590 -- label at the start and end of the statements of HSS.
592 -- Start of processing for Expand_Local_Exception_Handlers
594 begin
595 -- No processing if all exception handlers will get removed
597 if Debug_Flag_Dot_X then
598 return;
599 end if;
601 -- See for each handler if we have any local raises to expand
603 Handler := First_Non_Pragma (Handlrs);
604 while Present (Handler) loop
606 -- Note, we do not test Local_Raise_Not_OK here, because in the
607 -- case of Push/Pop generation we want to generate push with a
608 -- null label. The Add_Exception_Label routine has no effect if
609 -- Local_Raise_Not_OK is set, so this works as required.
611 if Present (Local_Raise_Statements (Handler)) then
612 Add_Exception_Label (Handler);
613 end if;
615 -- If we are doing local raise to goto optimization (restriction
616 -- No_Exception_Propagation set or debug flag .g set), then check
617 -- to see if handler handles CE, PE, SE and if so generate the
618 -- appropriate push/pop sequence for the back end.
620 if (Debug_Flag_Dot_G
621 or else Restriction_Active (No_Exception_Propagation))
622 and then Has_Local_Raise (Handler)
623 then
624 Choice := First (Exception_Choices (Handler));
625 while Present (Choice) loop
626 if Nkind (Choice) = N_Others_Choice
627 and then not All_Others (Choice)
628 then
629 Generate_Push_Pop_For_Constraint_Error (Handler);
630 Generate_Push_Pop_For_Program_Error (Handler);
631 Generate_Push_Pop_For_Storage_Error (Handler);
633 elsif Is_Entity_Name (Choice) then
634 Excep := Get_Renamed_Entity (Entity (Choice));
636 if Excep = Standard_Constraint_Error then
637 Generate_Push_Pop_For_Constraint_Error (Handler);
638 elsif Excep = Standard_Program_Error then
639 Generate_Push_Pop_For_Program_Error (Handler);
640 elsif Excep = Standard_Storage_Error then
641 Generate_Push_Pop_For_Storage_Error (Handler);
642 end if;
643 end if;
645 Next (Choice);
646 end loop;
647 end if;
649 Next_Non_Pragma (Handler);
650 end loop;
652 -- Nothing to do if no handlers requiring the goto transformation
654 if not (Local_Expansion_Required) then
655 return;
656 end if;
658 -- Prepare to do the transformation
660 declare
661 -- L3 is the label to exit the HSS
663 L3_Dent : constant Entity_Id := Make_Temporary (Loc, 'L');
665 Labl_L3 : constant Node_Id :=
666 Make_Label (Loc,
667 Identifier => New_Occurrence_Of (L3_Dent, Loc));
669 Blk_Stm : Node_Id;
670 Relmt : Elmt_Id;
672 begin
673 Set_Exception_Junk (Labl_L3);
674 Add_Label_Declaration (L3_Dent);
676 -- Wrap existing statements and handlers in an inner block
678 Blk_Stm :=
679 Make_Block_Statement (Loc,
680 Handled_Statement_Sequence => Relocate_Node (HSS));
681 Set_Exception_Junk (Blk_Stm);
683 Rewrite (HSS,
684 Make_Handled_Sequence_Of_Statements (Loc,
685 Statements => New_List (Blk_Stm),
686 End_Label => Relocate_Node (End_Label (HSS))));
688 -- Set block statement as analyzed, we don't want to actually call
689 -- Analyze on this block, it would cause a recursion in exception
690 -- handler processing which would mess things up.
692 Set_Analyzed (Blk_Stm);
694 -- Now loop through the exception handlers to deal with those that
695 -- are targets of local raise statements.
697 Handler := First_Non_Pragma (Handlrs);
698 while Present (Handler) loop
699 if Present (Exception_Label (Handler)) then
701 -- This handler needs the goto expansion
703 declare
704 Loc : constant Source_Ptr := Sloc (Handler);
706 -- L1 is the start label for this handler
708 L1_Dent : constant Entity_Id := Exception_Label (Handler);
710 Labl_L1 : constant Node_Id :=
711 Make_Label (Loc,
712 Identifier =>
713 New_Occurrence_Of (L1_Dent, Loc));
715 -- Jump to L1 to be used as replacement for the original
716 -- handler (used in the case where exception propagation
717 -- may still occur).
719 Name_L1 : constant Node_Id :=
720 New_Occurrence_Of (L1_Dent, Loc);
722 Goto_L1 : constant Node_Id :=
723 Make_Goto_Statement (Loc,
724 Name => Name_L1);
726 -- Jump to L3 to be used at the end of handler
728 Name_L3 : constant Node_Id :=
729 New_Occurrence_Of (L3_Dent, Loc);
731 Goto_L3 : constant Node_Id :=
732 Make_Goto_Statement (Loc,
733 Name => Name_L3);
735 H_Stmts : constant List_Id := Statements (Handler);
737 begin
738 Set_Exception_Junk (Labl_L1);
739 Set_Exception_Junk (Goto_L3);
741 -- Note: we do NOT set Exception_Junk in Goto_L1, since
742 -- this is a real transfer of control that we want the
743 -- Sem_Ch6.Check_Returns procedure to recognize properly.
745 -- Replace handler by a goto L1. We can mark this as
746 -- analyzed since it is fully formed, and we don't
747 -- want it going through any further checks. We save
748 -- the last statement location in the goto L1 node for
749 -- the benefit of Sem_Ch6.Check_Returns.
751 Set_Statements (Handler, New_List (Goto_L1));
752 Set_Analyzed (Goto_L1);
753 Set_Etype (Name_L1, Standard_Void_Type);
755 -- Now replace all the raise statements by goto L1
757 if Present (Local_Raise_Statements (Handler)) then
758 Relmt := First_Elmt (Local_Raise_Statements (Handler));
759 while Present (Relmt) loop
760 declare
761 Raise_S : constant Node_Id := Node (Relmt);
762 RLoc : constant Source_Ptr := Sloc (Raise_S);
763 Name_L1 : constant Node_Id :=
764 New_Occurrence_Of (L1_Dent, Loc);
765 Goto_L1 : constant Node_Id :=
766 Make_Goto_Statement (RLoc,
767 Name => Name_L1);
769 begin
770 -- Replace raise by goto L1
772 Set_Analyzed (Goto_L1);
773 Set_Etype (Name_L1, Standard_Void_Type);
774 Replace_Raise_By_Goto (Raise_S, Goto_L1);
775 end;
777 Next_Elmt (Relmt);
778 end loop;
779 end if;
781 -- Add a goto L3 at end of statement list in block. The
782 -- first time, this is what skips over the exception
783 -- handlers in the normal case. Subsequent times, it
784 -- terminates the execution of the previous handler code,
785 -- and skips subsequent handlers.
787 Stmts := Statements (HSS);
789 Insert_After (Last (Stmts), Goto_L3);
790 Set_Analyzed (Goto_L3);
791 Set_Etype (Name_L3, Standard_Void_Type);
793 -- Now we drop the label that marks the handler start,
794 -- followed by the statements of the handler.
796 Set_Etype (Identifier (Labl_L1), Standard_Void_Type);
798 Insert_After_And_Analyze (Last (Stmts), Labl_L1);
800 declare
801 Loc : constant Source_Ptr := Sloc (First (H_Stmts));
802 Blk : constant Node_Id :=
803 Make_Block_Statement (Loc,
804 Handled_Statement_Sequence =>
805 Make_Handled_Sequence_Of_Statements (Loc,
806 Statements => H_Stmts));
807 begin
808 Set_Exception_Junk (Blk);
809 Insert_After_And_Analyze (Last (Stmts), Blk);
810 end;
811 end;
813 -- Here if we have local raise statements but the handler is
814 -- not suitable for processing with a local raise. In this
815 -- case we have to generate possible diagnostics.
817 elsif Has_Local_Raise (Handler)
818 and then Local_Raise_Statements (Handler) /= No_Elist
819 then
820 Relmt := First_Elmt (Local_Raise_Statements (Handler));
821 while Present (Relmt) loop
822 Warn_If_No_Propagation (Node (Relmt));
823 Next_Elmt (Relmt);
824 end loop;
825 end if;
827 Next (Handler);
828 end loop;
830 -- Only remaining step is to drop the L3 label and we are done
832 Set_Etype (Identifier (Labl_L3), Standard_Void_Type);
834 -- If we had at least one handler, then we drop the label after
835 -- the last statement of that handler.
837 if Stmts /= No_List then
838 Insert_After_And_Analyze (Last (Stmts), Labl_L3);
840 -- Otherwise we have removed all the handlers (this results from
841 -- use of pragma Restrictions (No_Exception_Propagation), and we
842 -- drop the label at the end of the statements of the HSS.
844 else
845 Insert_After_And_Analyze (Last (Statements (HSS)), Labl_L3);
846 end if;
848 return;
849 end;
850 end Expand_Local_Exception_Handlers;
852 -----------------------------
853 -- Prepend_Call_To_Handler --
854 -----------------------------
856 procedure Prepend_Call_To_Handler
857 (Proc : RE_Id;
858 Args : List_Id := No_List)
860 Ent : constant Entity_Id := RTE (Proc);
862 begin
863 -- If we have no Entity, then we are probably in no run time mode or
864 -- some weird error has occurred. In either case do nothing. Note use
865 -- of No_Location to hide this code from the debugger, so single
866 -- stepping doesn't jump back and forth.
868 if Present (Ent) then
869 declare
870 Call : constant Node_Id :=
871 Make_Procedure_Call_Statement (No_Location,
872 Name => New_Occurrence_Of (RTE (Proc), No_Location),
873 Parameter_Associations => Args);
875 begin
876 Prepend_To (Statements (Handler), Call);
877 Analyze (Call, Suppress => All_Checks);
878 end;
879 end if;
880 end Prepend_Call_To_Handler;
882 ---------------------------
883 -- Replace_Raise_By_Goto --
884 ---------------------------
886 procedure Replace_Raise_By_Goto (Raise_S : Node_Id; Goto_L1 : Node_Id) is
887 Loc : constant Source_Ptr := Sloc (Raise_S);
888 Excep : Entity_Id;
889 LR : Node_Id;
890 Cond : Node_Id;
891 Orig : Node_Id;
893 begin
894 -- If we have a null statement, it means that there is no replacement
895 -- needed (typically this results from a suppressed check).
897 if Nkind (Raise_S) = N_Null_Statement then
898 return;
900 -- Test for Raise_xxx_Error
902 elsif Nkind (Raise_S) = N_Raise_Constraint_Error then
903 Excep := Standard_Constraint_Error;
904 Cond := Condition (Raise_S);
906 elsif Nkind (Raise_S) = N_Raise_Storage_Error then
907 Excep := Standard_Storage_Error;
908 Cond := Condition (Raise_S);
910 elsif Nkind (Raise_S) = N_Raise_Program_Error then
911 Excep := Standard_Program_Error;
912 Cond := Condition (Raise_S);
914 -- The only other possibility is a node that is or used to be a
915 -- simple raise statement.
917 else
918 Orig := Original_Node (Raise_S);
919 pragma Assert (Nkind (Orig) = N_Raise_Statement
920 and then Present (Name (Orig))
921 and then No (Expression (Orig)));
922 Excep := Entity (Name (Orig));
923 Cond := Empty;
924 end if;
926 -- Here Excep is the exception to raise, and Cond is the condition
927 -- First prepare the call to Local_Raise (excep'address).
929 if RTE_Available (RE_Local_Raise) then
930 LR :=
931 Make_Procedure_Call_Statement (Loc,
932 Name => New_Occurrence_Of (RTE (RE_Local_Raise), Loc),
933 Parameter_Associations => New_List (
934 Unchecked_Convert_To (RTE (RE_Address),
935 Make_Attribute_Reference (Loc,
936 Prefix => New_Occurrence_Of (Excep, Loc),
937 Attribute_Name => Name_Identity))));
939 -- Use null statement if Local_Raise not available
941 else
942 LR :=
943 Make_Null_Statement (Loc);
944 end if;
946 -- If there is no condition, we rewrite as
948 -- begin
949 -- Local_Raise (excep'Identity);
950 -- goto L1;
951 -- end;
953 if No (Cond) then
954 Rewrite (Raise_S,
955 Make_Block_Statement (Loc,
956 Handled_Statement_Sequence =>
957 Make_Handled_Sequence_Of_Statements (Loc,
958 Statements => New_List (LR, Goto_L1))));
959 Set_Exception_Junk (Raise_S);
961 -- If there is a condition, we rewrite as
963 -- if condition then
964 -- Local_Raise (excep'Identity);
965 -- goto L1;
966 -- end if;
968 else
969 Rewrite (Raise_S,
970 Make_If_Statement (Loc,
971 Condition => Cond,
972 Then_Statements => New_List (LR, Goto_L1)));
973 end if;
975 Analyze (Raise_S);
976 end Replace_Raise_By_Goto;
978 -- Start of processing for Expand_Exception_Handlers
980 begin
981 Expand_Local_Exception_Handlers;
983 -- Loop through handlers
985 Handler := First_Non_Pragma (Handlrs);
986 Handler_Loop : while Present (Handler) loop
987 Process_Statements_For_Controlled_Objects (Handler);
989 Next_Handler := Next_Non_Pragma (Handler);
991 -- Remove source handler if gnat debug flag .x is set
993 if Debug_Flag_Dot_X and then Comes_From_Source (Handler) then
994 Remove (Handler);
996 -- Remove handler if no exception propagation, generating a warning
997 -- if a source generated handler was not the target of a local raise.
999 else
1000 if Restriction_Active (No_Exception_Propagation)
1001 and then not Has_Local_Raise (Handler)
1002 and then Comes_From_Source (Handler)
1003 and then Warn_On_Non_Local_Exception
1004 then
1005 Warn_No_Exception_Propagation_Active (Handler);
1006 Error_Msg_N
1007 ("\?X?this handler can never be entered, "
1008 & "and has been removed", Handler);
1009 end if;
1011 if No_Exception_Propagation_Active then
1012 Remove (Handler);
1014 -- Exception handler is active and retained and must be processed
1016 else
1017 -- If an exception occurrence is present, then we must declare
1018 -- it and initialize it from the value stored in the TSD
1020 -- declare
1021 -- name : Exception_Occurrence;
1022 -- begin
1023 -- Save_Occurrence (name, Get_Current_Excep.all)
1024 -- ...
1025 -- end;
1027 -- This expansion is not performed when using GCC ZCX. Gigi
1028 -- will insert a call to initialize the choice parameter.
1030 if Present (Choice_Parameter (Handler))
1031 and then (Exception_Mechanism /= Back_End_Exceptions
1032 or else CodePeer_Mode)
1033 then
1034 declare
1035 Cparm : constant Entity_Id := Choice_Parameter (Handler);
1036 Cloc : constant Source_Ptr := Sloc (Cparm);
1037 Hloc : constant Source_Ptr := Sloc (Handler);
1038 Save : Node_Id;
1040 begin
1041 -- Note: No_Location used to hide code from the debugger,
1042 -- so single stepping doesn't jump back and forth.
1044 Save :=
1045 Make_Procedure_Call_Statement (No_Location,
1046 Name =>
1047 New_Occurrence_Of
1048 (RTE (RE_Save_Occurrence), No_Location),
1049 Parameter_Associations => New_List (
1050 New_Occurrence_Of (Cparm, No_Location),
1051 Make_Explicit_Dereference (No_Location,
1052 Prefix =>
1053 Make_Function_Call (No_Location,
1054 Name =>
1055 Make_Explicit_Dereference (No_Location,
1056 Prefix =>
1057 New_Occurrence_Of
1058 (RTE (RE_Get_Current_Excep),
1059 No_Location))))));
1061 Mark_Rewrite_Insertion (Save);
1062 Prepend (Save, Statements (Handler));
1064 Obj_Decl :=
1065 Make_Object_Declaration (Cloc,
1066 Defining_Identifier => Cparm,
1067 Object_Definition =>
1068 New_Occurrence_Of
1069 (RTE (RE_Exception_Occurrence), Cloc));
1070 Set_No_Initialization (Obj_Decl, True);
1072 Rewrite (Handler,
1073 Make_Exception_Handler (Hloc,
1074 Choice_Parameter => Empty,
1075 Exception_Choices => Exception_Choices (Handler),
1076 Statements => New_List (
1077 Make_Block_Statement (Hloc,
1078 Declarations => New_List (Obj_Decl),
1079 Handled_Statement_Sequence =>
1080 Make_Handled_Sequence_Of_Statements (Hloc,
1081 Statements => Statements (Handler))))));
1083 -- Local raise statements can't occur, since exception
1084 -- handlers with choice parameters are not allowed when
1085 -- No_Exception_Propagation applies, so set attributes
1086 -- accordingly.
1088 Set_Local_Raise_Statements (Handler, No_Elist);
1089 Set_Local_Raise_Not_OK (Handler);
1091 Analyze_List
1092 (Statements (Handler), Suppress => All_Checks);
1093 end;
1094 end if;
1096 -- The processing at this point is rather different for the JVM
1097 -- case, so we completely separate the processing.
1099 -- For the VM case, we unconditionally call Update_Exception,
1100 -- passing a call to the intrinsic Current_Target_Exception
1101 -- (see JVM/.NET versions of Ada.Exceptions for details).
1103 if VM_Target /= No_VM then
1104 declare
1105 Arg : constant Node_Id :=
1106 Make_Function_Call (Loc,
1107 Name =>
1108 New_Occurrence_Of
1109 (RTE (RE_Current_Target_Exception), Loc));
1110 begin
1111 Prepend_Call_To_Handler
1112 (RE_Update_Exception, New_List (Arg));
1113 end;
1115 -- For the normal case, we have to worry about the state of
1116 -- abort deferral. Generally, we defer abort during runtime
1117 -- handling of exceptions. When control is passed to the
1118 -- handler, then in the normal case we undefer aborts. In
1119 -- any case this entire handling is relevant only if aborts
1120 -- are allowed.
1122 elsif Abort_Allowed
1123 and then Exception_Mechanism /= Back_End_Exceptions
1124 then
1125 -- There are some special cases in which we do not do the
1126 -- undefer. In particular a finalization (AT END) handler
1127 -- wants to operate with aborts still deferred.
1129 -- We also suppress the call if this is the special handler
1130 -- for Abort_Signal, since if we are aborting, we want to
1131 -- keep aborts deferred (one abort is enough).
1133 -- If abort really needs to be deferred the expander must
1134 -- add this call explicitly, see
1135 -- Expand_N_Asynchronous_Select.
1137 Others_Choice :=
1138 Nkind (First (Exception_Choices (Handler))) =
1139 N_Others_Choice;
1141 if (Others_Choice
1142 or else Entity (First (Exception_Choices (Handler))) /=
1143 Stand.Abort_Signal)
1144 and then not
1145 (Others_Choice
1146 and then
1147 All_Others (First (Exception_Choices (Handler))))
1148 then
1149 Prepend_Call_To_Handler (RE_Abort_Undefer);
1150 end if;
1151 end if;
1152 end if;
1153 end if;
1155 Handler := Next_Handler;
1156 end loop Handler_Loop;
1158 -- If all handlers got removed, then remove the list. Note we cannot
1159 -- reference HSS here, since expanding local handlers may have buried
1160 -- the handlers in an inner block.
1162 if Is_Empty_List (Handlrs) then
1163 Set_Exception_Handlers (Parent (Handlrs), No_List);
1164 end if;
1165 end Expand_Exception_Handlers;
1167 ------------------------------------
1168 -- Expand_N_Exception_Declaration --
1169 ------------------------------------
1171 -- Generates:
1172 -- exceptE : constant String := "A.B.EXCEP"; -- static data
1173 -- except : exception_data :=
1174 -- (Handled_By_Other => False,
1175 -- Lang => 'A',
1176 -- Name_Length => exceptE'Length,
1177 -- Full_Name => exceptE'Address,
1178 -- HTable_Ptr => null,
1179 -- Foreign_Data => null,
1180 -- Raise_Hook => null);
1182 -- (protecting test only needed if not at library level)
1184 -- exceptF : Boolean := True -- static data
1185 -- if exceptF then
1186 -- exceptF := False;
1187 -- Register_Exception (except'Unchecked_Access);
1188 -- end if;
1190 procedure Expand_N_Exception_Declaration (N : Node_Id) is
1191 Loc : constant Source_Ptr := Sloc (N);
1192 Id : constant Entity_Id := Defining_Identifier (N);
1193 L : List_Id := New_List;
1194 Flag_Id : Entity_Id;
1196 Name_Exname : constant Name_Id := New_External_Name (Chars (Id), 'E');
1197 Exname : constant Node_Id :=
1198 Make_Defining_Identifier (Loc, Name_Exname);
1200 procedure Force_Static_Allocation_Of_Referenced_Objects
1201 (Aggregate : Node_Id);
1202 -- A specialized solution to one particular case of an ugly problem
1204 -- The given aggregate includes an Unchecked_Conversion as one of the
1205 -- component values. The call to Analyze_And_Resolve below ends up
1206 -- calling Exp_Ch4.Expand_N_Unchecked_Type_Conversion, which may decide
1207 -- to introduce a (constant) temporary and then obtain the component
1208 -- value by evaluating the temporary.
1210 -- In the case of an exception declared within a subprogram (or any
1211 -- other dynamic scope), this is a bad transformation. The exception
1212 -- object is marked as being Statically_Allocated but the temporary is
1213 -- not. If the initial value of a Statically_Allocated declaration
1214 -- references a dynamically allocated object, this prevents static
1215 -- initialization of the object.
1217 -- We cope with this here by marking the temporary Statically_Allocated.
1218 -- It might seem cleaner to generalize this utility and then use it to
1219 -- enforce a rule that the entities referenced in the declaration of any
1220 -- "hoisted" (i.e., Is_Statically_Allocated and not Is_Library_Level)
1221 -- entity must also be either Library_Level or hoisted. It turns out
1222 -- that this would be incompatible with the current treatment of an
1223 -- object which is local to a subprogram, subject to an Export pragma,
1224 -- not subject to an address clause, and whose declaration contains
1225 -- references to other local (non-hoisted) objects (e.g., in the initial
1226 -- value expression).
1228 ---------------------------------------------------
1229 -- Force_Static_Allocation_Of_Referenced_Objects --
1230 ---------------------------------------------------
1232 procedure Force_Static_Allocation_Of_Referenced_Objects
1233 (Aggregate : Node_Id)
1235 function Fixup_Node (N : Node_Id) return Traverse_Result;
1236 -- If the given node references a dynamically allocated object, then
1237 -- correct the declaration of the object.
1239 ----------------
1240 -- Fixup_Node --
1241 ----------------
1243 function Fixup_Node (N : Node_Id) return Traverse_Result is
1244 begin
1245 if Nkind (N) in N_Has_Entity
1246 and then Present (Entity (N))
1247 and then not Is_Library_Level_Entity (Entity (N))
1249 -- Note: the following test is not needed but it seems cleaner
1250 -- to do this test (this would be more important if procedure
1251 -- Force_Static_Allocation_Of_Referenced_Objects recursively
1252 -- traversed the declaration of an entity after marking it as
1253 -- statically allocated).
1255 and then not Is_Statically_Allocated (Entity (N))
1256 then
1257 Set_Is_Statically_Allocated (Entity (N));
1258 end if;
1260 return OK;
1261 end Fixup_Node;
1263 procedure Fixup_Tree is new Traverse_Proc (Fixup_Node);
1265 -- Start of processing for Force_Static_Allocation_Of_Referenced_Objects
1267 begin
1268 Fixup_Tree (Aggregate);
1269 end Force_Static_Allocation_Of_Referenced_Objects;
1271 -- Start of processing for Expand_N_Exception_Declaration
1273 begin
1274 -- There is no expansion needed when compiling for the JVM since the
1275 -- JVM has a built-in exception mechanism. See cil/gnatlib/a-except.ads
1276 -- for details.
1278 if VM_Target /= No_VM then
1279 return;
1280 end if;
1282 -- Definition of the external name: nam : constant String := "A.B.NAME";
1284 Insert_Action (N,
1285 Make_Object_Declaration (Loc,
1286 Defining_Identifier => Exname,
1287 Constant_Present => True,
1288 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1289 Expression =>
1290 Make_String_Literal (Loc,
1291 Strval => Fully_Qualified_Name_String (Id))));
1293 Set_Is_Statically_Allocated (Exname);
1295 -- Create the aggregate list for type Standard.Exception_Type:
1296 -- Handled_By_Other component: False
1298 Append_To (L, New_Occurrence_Of (Standard_False, Loc));
1300 -- Lang component: 'A'
1302 Append_To (L,
1303 Make_Character_Literal (Loc,
1304 Chars => Name_uA,
1305 Char_Literal_Value => UI_From_Int (Character'Pos ('A'))));
1307 -- Name_Length component: Nam'Length
1309 Append_To (L,
1310 Make_Attribute_Reference (Loc,
1311 Prefix => New_Occurrence_Of (Exname, Loc),
1312 Attribute_Name => Name_Length));
1314 -- Full_Name component: Standard.A_Char!(Nam'Address)
1316 Append_To (L, Unchecked_Convert_To (Standard_A_Char,
1317 Make_Attribute_Reference (Loc,
1318 Prefix => New_Occurrence_Of (Exname, Loc),
1319 Attribute_Name => Name_Address)));
1321 -- HTable_Ptr component: null
1323 Append_To (L, Make_Null (Loc));
1325 -- Foreign_Data component: null
1327 Append_To (L, Make_Null (Loc));
1329 -- Raise_Hook component: null
1331 Append_To (L, Make_Null (Loc));
1333 Set_Expression (N, Make_Aggregate (Loc, Expressions => L));
1334 Analyze_And_Resolve (Expression (N), Etype (Id));
1336 Force_Static_Allocation_Of_Referenced_Objects (Expression (N));
1338 -- Register_Exception (except'Unchecked_Access);
1340 if not No_Exception_Handlers_Set
1341 and then not Restriction_Active (No_Exception_Registration)
1342 then
1343 L := New_List (
1344 Make_Procedure_Call_Statement (Loc,
1345 Name => New_Occurrence_Of (RTE (RE_Register_Exception), Loc),
1346 Parameter_Associations => New_List (
1347 Unchecked_Convert_To (RTE (RE_Exception_Data_Ptr),
1348 Make_Attribute_Reference (Loc,
1349 Prefix => New_Occurrence_Of (Id, Loc),
1350 Attribute_Name => Name_Unrestricted_Access)))));
1352 Set_Register_Exception_Call (Id, First (L));
1354 if not Is_Library_Level_Entity (Id) then
1355 Flag_Id := Make_Defining_Identifier (Loc,
1356 New_External_Name (Chars (Id), 'F'));
1358 Insert_Action (N,
1359 Make_Object_Declaration (Loc,
1360 Defining_Identifier => Flag_Id,
1361 Object_Definition =>
1362 New_Occurrence_Of (Standard_Boolean, Loc),
1363 Expression =>
1364 New_Occurrence_Of (Standard_True, Loc)));
1366 Set_Is_Statically_Allocated (Flag_Id);
1368 Append_To (L,
1369 Make_Assignment_Statement (Loc,
1370 Name => New_Occurrence_Of (Flag_Id, Loc),
1371 Expression => New_Occurrence_Of (Standard_False, Loc)));
1373 Insert_After_And_Analyze (N,
1374 Make_Implicit_If_Statement (N,
1375 Condition => New_Occurrence_Of (Flag_Id, Loc),
1376 Then_Statements => L));
1378 else
1379 Insert_List_After_And_Analyze (N, L);
1380 end if;
1381 end if;
1382 end Expand_N_Exception_Declaration;
1384 ---------------------------------------------
1385 -- Expand_N_Handled_Sequence_Of_Statements --
1386 ---------------------------------------------
1388 procedure Expand_N_Handled_Sequence_Of_Statements (N : Node_Id) is
1389 begin
1390 -- Expand exception handlers
1392 if Present (Exception_Handlers (N))
1393 and then not Restriction_Active (No_Exception_Handlers)
1394 then
1395 Expand_Exception_Handlers (N);
1396 end if;
1398 -- If local exceptions are being expanded, the previous call will
1399 -- have rewritten the construct as a block and reanalyzed it. No
1400 -- further expansion is needed.
1402 if Analyzed (N) then
1403 return;
1404 end if;
1406 -- Add clean up actions if required
1408 if not Nkind_In (Parent (N), N_Package_Body,
1409 N_Accept_Statement,
1410 N_Extended_Return_Statement)
1411 and then not Delay_Cleanups (Current_Scope)
1413 -- No cleanup action needed in thunks associated with interfaces
1414 -- because they only displace the pointer to the object.
1416 and then not Is_Thunk (Current_Scope)
1417 then
1418 Expand_Cleanup_Actions (Parent (N));
1419 else
1420 Set_First_Real_Statement (N, First (Statements (N)));
1421 end if;
1422 end Expand_N_Handled_Sequence_Of_Statements;
1424 -------------------------------------
1425 -- Expand_N_Raise_Constraint_Error --
1426 -------------------------------------
1428 procedure Expand_N_Raise_Constraint_Error (N : Node_Id) is
1429 begin
1430 -- We adjust the condition to deal with the C/Fortran boolean case. This
1431 -- may well not be necessary, as all such conditions are generated by
1432 -- the expander and probably are all standard boolean, but who knows
1433 -- what strange optimization in future may require this adjustment.
1435 Adjust_Condition (Condition (N));
1437 -- Now deal with possible local raise handling
1439 Possible_Local_Raise (N, Standard_Constraint_Error);
1440 end Expand_N_Raise_Constraint_Error;
1442 -------------------------------
1443 -- Expand_N_Raise_Expression --
1444 -------------------------------
1446 procedure Expand_N_Raise_Expression (N : Node_Id) is
1447 Loc : constant Source_Ptr := Sloc (N);
1448 Typ : constant Entity_Id := Etype (N);
1449 RCE : Node_Id;
1451 begin
1452 Possible_Local_Raise (N, Entity (Name (N)));
1454 -- Later we must teach the back end/gigi how to deal with this, but
1455 -- for now we will assume the type is Standard_Boolean and transform
1456 -- the node to:
1458 -- do
1459 -- raise X [with string]
1460 -- in
1461 -- raise Constraint_Error;
1463 -- unless the flag Convert_To_Return_False is set, in which case
1464 -- the transformation is to:
1466 -- do
1467 -- return False;
1468 -- in
1469 -- raise Constraint_Error;
1471 -- The raise constraint error can never be executed. It is just a dummy
1472 -- node that can be labeled with an arbitrary type.
1474 RCE := Make_Raise_Constraint_Error (Loc, Reason => CE_Explicit_Raise);
1475 Set_Etype (RCE, Typ);
1477 if Convert_To_Return_False (N) then
1478 Rewrite (N,
1479 Make_Expression_With_Actions (Loc,
1480 Actions => New_List (
1481 Make_Simple_Return_Statement (Loc,
1482 Expression => New_Occurrence_Of (Standard_False, Loc))),
1483 Expression => RCE));
1485 else
1486 Rewrite (N,
1487 Make_Expression_With_Actions (Loc,
1488 Actions => New_List (
1489 Make_Raise_Statement (Loc,
1490 Name => Name (N),
1491 Expression => Expression (N))),
1492 Expression => RCE));
1493 end if;
1495 Analyze_And_Resolve (N, Typ);
1496 end Expand_N_Raise_Expression;
1498 ----------------------------------
1499 -- Expand_N_Raise_Program_Error --
1500 ----------------------------------
1502 procedure Expand_N_Raise_Program_Error (N : Node_Id) is
1503 begin
1504 -- We adjust the condition to deal with the C/Fortran boolean case. This
1505 -- may well not be necessary, as all such conditions are generated by
1506 -- the expander and probably are all standard boolean, but who knows
1507 -- what strange optimization in future may require this adjustment.
1509 Adjust_Condition (Condition (N));
1511 -- Now deal with possible local raise handling
1513 Possible_Local_Raise (N, Standard_Program_Error);
1514 end Expand_N_Raise_Program_Error;
1516 ------------------------------
1517 -- Expand_N_Raise_Statement --
1518 ------------------------------
1520 procedure Expand_N_Raise_Statement (N : Node_Id) is
1521 Loc : constant Source_Ptr := Sloc (N);
1522 Ehand : Node_Id;
1523 E : Entity_Id;
1524 Str : String_Id;
1525 H : Node_Id;
1526 Src : Boolean;
1528 begin
1529 -- Processing for locally handled exception (exclude reraise case)
1531 if Present (Name (N)) and then Nkind (Name (N)) = N_Identifier then
1532 if Debug_Flag_Dot_G
1533 or else Restriction_Active (No_Exception_Propagation)
1534 then
1535 -- If we have a local handler, then note that this is potentially
1536 -- able to be transformed into a goto statement.
1538 H := Find_Local_Handler (Entity (Name (N)), N);
1540 if Present (H) then
1541 if Local_Raise_Statements (H) = No_Elist then
1542 Set_Local_Raise_Statements (H, New_Elmt_List);
1543 end if;
1545 -- Append the new entry if it is not there already. Sometimes
1546 -- we have situations where due to reexpansion, the same node
1547 -- is analyzed twice and would otherwise be added twice.
1549 Append_Unique_Elmt (N, Local_Raise_Statements (H));
1550 Set_Has_Local_Raise (H);
1552 -- If no local handler, then generate no propagation warning
1554 else
1555 Warn_If_No_Propagation (N);
1556 end if;
1558 end if;
1559 end if;
1561 -- If a string expression is present, then the raise statement is
1562 -- converted to a call:
1563 -- Raise_Exception (exception-name'Identity, string);
1564 -- and there is nothing else to do.
1566 if Present (Expression (N)) then
1568 -- Avoid passing exception-name'identity in runtimes in which this
1569 -- argument is not used. This avoids generating undefined references
1570 -- to these exceptions when compiling with no optimization
1572 if Configurable_Run_Time_On_Target
1573 and then (Restriction_Active (No_Exception_Handlers)
1574 or else
1575 Restriction_Active (No_Exception_Propagation))
1576 then
1577 Rewrite (N,
1578 Make_Procedure_Call_Statement (Loc,
1579 Name => New_Occurrence_Of (RTE (RE_Raise_Exception), Loc),
1580 Parameter_Associations => New_List (
1581 New_Occurrence_Of (RTE (RE_Null_Id), Loc),
1582 Expression (N))));
1583 else
1584 Rewrite (N,
1585 Make_Procedure_Call_Statement (Loc,
1586 Name => New_Occurrence_Of (RTE (RE_Raise_Exception), Loc),
1587 Parameter_Associations => New_List (
1588 Make_Attribute_Reference (Loc,
1589 Prefix => Name (N),
1590 Attribute_Name => Name_Identity),
1591 Expression (N))));
1592 end if;
1594 Analyze (N);
1595 return;
1596 end if;
1598 -- Remaining processing is for the case where no string expression is
1599 -- present.
1601 -- Don't expand a raise statement that does not come from source if we
1602 -- have already had configurable run-time violations, since most likely
1603 -- it will be junk cascaded nonsense.
1605 if Configurable_Run_Time_Violations > 0
1606 and then not Comes_From_Source (N)
1607 then
1608 return;
1609 end if;
1611 -- Convert explicit raise of Program_Error, Constraint_Error, and
1612 -- Storage_Error into the corresponding raise (in High_Integrity_Mode
1613 -- all other raises will get normal expansion and be disallowed,
1614 -- but this is also faster in all modes). Propagate Comes_From_Source
1615 -- flag to the new node.
1617 if Present (Name (N)) and then Nkind (Name (N)) = N_Identifier then
1618 Src := Comes_From_Source (N);
1620 if Entity (Name (N)) = Standard_Constraint_Error then
1621 Rewrite (N,
1622 Make_Raise_Constraint_Error (Loc, Reason => CE_Explicit_Raise));
1623 Set_Comes_From_Source (N, Src);
1624 Analyze (N);
1625 return;
1627 elsif Entity (Name (N)) = Standard_Program_Error then
1628 Rewrite (N,
1629 Make_Raise_Program_Error (Loc, Reason => PE_Explicit_Raise));
1630 Set_Comes_From_Source (N, Src);
1631 Analyze (N);
1632 return;
1634 elsif Entity (Name (N)) = Standard_Storage_Error then
1635 Rewrite (N,
1636 Make_Raise_Storage_Error (Loc, Reason => SE_Explicit_Raise));
1637 Set_Comes_From_Source (N, Src);
1638 Analyze (N);
1639 return;
1640 end if;
1641 end if;
1643 -- Case of name present, in this case we expand raise name to
1645 -- Raise_Exception (name'Identity, location_string);
1647 -- where location_string identifies the file/line of the raise
1649 if Present (Name (N)) then
1650 declare
1651 Id : Entity_Id := Entity (Name (N));
1653 begin
1654 Name_Len := 0;
1655 Build_Location_String (Loc);
1657 -- If the exception is a renaming, use the exception that it
1658 -- renames (which might be a predefined exception, e.g.).
1660 if Present (Renamed_Object (Id)) then
1661 Id := Renamed_Object (Id);
1662 end if;
1664 -- Build a C-compatible string in case of no exception handlers,
1665 -- since this is what the last chance handler is expecting.
1667 if No_Exception_Handlers_Set then
1669 -- Generate an empty message if configuration pragma
1670 -- Suppress_Exception_Locations is set for this unit.
1672 if Opt.Exception_Locations_Suppressed then
1673 Name_Len := 1;
1674 else
1675 Name_Len := Name_Len + 1;
1676 end if;
1678 Name_Buffer (Name_Len) := ASCII.NUL;
1679 end if;
1681 if Opt.Exception_Locations_Suppressed then
1682 Name_Len := 0;
1683 end if;
1685 Str := String_From_Name_Buffer;
1687 -- Convert raise to call to the Raise_Exception routine
1689 Rewrite (N,
1690 Make_Procedure_Call_Statement (Loc,
1691 Name =>
1692 New_Occurrence_Of (RTE (RE_Raise_Exception), Loc),
1693 Parameter_Associations => New_List (
1694 Make_Attribute_Reference (Loc,
1695 Prefix => Name (N),
1696 Attribute_Name => Name_Identity),
1697 Make_String_Literal (Loc, Strval => Str))));
1698 end;
1700 -- Case of no name present (reraise). We rewrite the raise to:
1702 -- Reraise_Occurrence_Always (EO);
1704 -- where EO is the current exception occurrence. If the current handler
1705 -- does not have a choice parameter specification, then we provide one.
1707 else
1708 -- Bypass expansion to a run-time call when back-end exception
1709 -- handling is active, unless the target is a VM, CodePeer or
1710 -- GNATprove. In CodePeer, raising an exception is treated as an
1711 -- error, while in GNATprove all code with exceptions falls outside
1712 -- the subset of code which can be formally analyzed.
1714 if VM_Target = No_VM
1715 and then not CodePeer_Mode
1716 and then Exception_Mechanism = Back_End_Exceptions
1717 then
1718 return;
1719 end if;
1721 -- Find innermost enclosing exception handler (there must be one,
1722 -- since the semantics has already verified that this raise statement
1723 -- is valid, and a raise with no arguments is only permitted in the
1724 -- context of an exception handler.
1726 Ehand := Parent (N);
1727 while Nkind (Ehand) /= N_Exception_Handler loop
1728 Ehand := Parent (Ehand);
1729 end loop;
1731 -- Make exception choice parameter if none present. Note that we do
1732 -- not need to put the entity on the entity chain, since no one will
1733 -- be referencing this entity by normal visibility methods.
1735 if No (Choice_Parameter (Ehand)) then
1736 E := Make_Temporary (Loc, 'E');
1737 Set_Choice_Parameter (Ehand, E);
1738 Set_Ekind (E, E_Variable);
1739 Set_Etype (E, RTE (RE_Exception_Occurrence));
1740 Set_Scope (E, Current_Scope);
1741 end if;
1743 -- Now rewrite the raise as a call to Reraise. A special case arises
1744 -- if this raise statement occurs in the context of a handler for
1745 -- all others (i.e. an at end handler). in this case we avoid
1746 -- the call to defer abort, cleanup routines are expected to be
1747 -- called in this case with aborts deferred.
1749 declare
1750 Ech : constant Node_Id := First (Exception_Choices (Ehand));
1751 Ent : Entity_Id;
1753 begin
1754 if Nkind (Ech) = N_Others_Choice
1755 and then All_Others (Ech)
1756 then
1757 Ent := RTE (RE_Reraise_Occurrence_No_Defer);
1758 else
1759 Ent := RTE (RE_Reraise_Occurrence_Always);
1760 end if;
1762 Rewrite (N,
1763 Make_Procedure_Call_Statement (Loc,
1764 Name => New_Occurrence_Of (Ent, Loc),
1765 Parameter_Associations => New_List (
1766 New_Occurrence_Of (Choice_Parameter (Ehand), Loc))));
1767 end;
1768 end if;
1770 Analyze (N);
1771 end Expand_N_Raise_Statement;
1773 ----------------------------------
1774 -- Expand_N_Raise_Storage_Error --
1775 ----------------------------------
1777 procedure Expand_N_Raise_Storage_Error (N : Node_Id) is
1778 begin
1779 -- We adjust the condition to deal with the C/Fortran boolean case. This
1780 -- may well not be necessary, as all such conditions are generated by
1781 -- the expander and probably are all standard boolean, but who knows
1782 -- what strange optimization in future may require this adjustment.
1784 Adjust_Condition (Condition (N));
1786 -- Now deal with possible local raise handling
1788 Possible_Local_Raise (N, Standard_Storage_Error);
1789 end Expand_N_Raise_Storage_Error;
1791 --------------------------
1792 -- Possible_Local_Raise --
1793 --------------------------
1795 procedure Possible_Local_Raise (N : Node_Id; E : Entity_Id) is
1796 begin
1797 -- Nothing to do if local raise optimization not active
1799 if not Debug_Flag_Dot_G
1800 and then not Restriction_Active (No_Exception_Propagation)
1801 then
1802 return;
1803 end if;
1805 -- Nothing to do if original node was an explicit raise, because in
1806 -- that case, we already generated the required warning for the raise.
1808 if Nkind (Original_Node (N)) = N_Raise_Statement then
1809 return;
1810 end if;
1812 -- Otherwise see if we have a local handler for the exception
1814 declare
1815 H : constant Node_Id := Find_Local_Handler (E, N);
1817 begin
1818 -- If so, mark that it has a local raise
1820 if Present (H) then
1821 Set_Has_Local_Raise (H, True);
1823 -- Otherwise, if the No_Exception_Propagation restriction is active
1824 -- and the warning is enabled, generate the appropriate warnings.
1826 elsif Warn_On_Non_Local_Exception
1827 and then Restriction_Active (No_Exception_Propagation)
1828 then
1829 Warn_No_Exception_Propagation_Active (N);
1831 if Configurable_Run_Time_Mode then
1832 Error_Msg_NE
1833 ("\?X?& may call Last_Chance_Handler", N, E);
1834 else
1835 Error_Msg_NE
1836 ("\?X?& may result in unhandled exception", N, E);
1837 end if;
1838 end if;
1839 end;
1840 end Possible_Local_Raise;
1842 ------------------------
1843 -- Find_Local_Handler --
1844 ------------------------
1846 function Find_Local_Handler
1847 (Ename : Entity_Id;
1848 Nod : Node_Id) return Node_Id
1850 N : Node_Id;
1851 P : Node_Id;
1852 H : Node_Id;
1853 C : Node_Id;
1855 SSE : Scope_Stack_Entry renames Scope_Stack.Table (Scope_Stack.Last);
1856 -- This is used to test for wrapped actions below
1858 ERaise : Entity_Id;
1859 EHandle : Entity_Id;
1860 -- The entity Id's for the exception we are raising and handling, using
1861 -- the renamed exception if a Renamed_Entity is present.
1863 begin
1864 -- Never any local handler if all handlers removed
1866 if Debug_Flag_Dot_X then
1867 return Empty;
1868 end if;
1870 -- Get the exception we are raising, allowing for renaming
1872 ERaise := Get_Renamed_Entity (Ename);
1874 -- We need to check if the node we are looking at is contained in
1877 -- Loop to search up the tree
1879 N := Nod;
1880 loop
1881 P := Parent (N);
1883 -- If we get to the top of the tree, or to a subprogram, task, entry,
1884 -- protected body, or accept statement without having found a
1885 -- matching handler, then there is no local handler.
1887 if No (P)
1888 or else Nkind (P) = N_Subprogram_Body
1889 or else Nkind (P) = N_Task_Body
1890 or else Nkind (P) = N_Protected_Body
1891 or else Nkind (P) = N_Entry_Body
1892 or else Nkind (P) = N_Accept_Statement
1893 then
1894 return Empty;
1896 -- Test for handled sequence of statements with at least one
1897 -- exception handler which might be the one we are looking for.
1899 elsif Nkind (P) = N_Handled_Sequence_Of_Statements
1900 and then Present (Exception_Handlers (P))
1901 then
1902 -- Before we proceed we need to check if the node N is covered
1903 -- by the statement part of P rather than one of its exception
1904 -- handlers (an exception handler obviously does not cover its
1905 -- own statements).
1907 -- This test is more delicate than might be thought. It is not
1908 -- just a matter of checking the Statements (P), because the node
1909 -- might be waiting to be wrapped in a transient scope, in which
1910 -- case it will end up in the block statements, even though it
1911 -- is not there now.
1913 if Is_List_Member (N) then
1914 declare
1915 LCN : constant List_Id := List_Containing (N);
1917 begin
1918 if LCN = Statements (P)
1919 or else
1920 LCN = SSE.Actions_To_Be_Wrapped (Before)
1921 or else
1922 LCN = SSE.Actions_To_Be_Wrapped (After)
1923 or else
1924 LCN = SSE.Actions_To_Be_Wrapped (Cleanup)
1925 then
1926 -- Loop through exception handlers
1928 H := First (Exception_Handlers (P));
1929 while Present (H) loop
1931 -- Guard against other constructs appearing in the
1932 -- list of exception handlers.
1934 if Nkind (H) = N_Exception_Handler then
1936 -- Loop through choices in one handler
1938 C := First (Exception_Choices (H));
1939 while Present (C) loop
1941 -- Deal with others case
1943 if Nkind (C) = N_Others_Choice then
1945 -- Matching others handler, but we need
1946 -- to ensure there is no choice parameter.
1947 -- If there is, then we don't have a local
1948 -- handler after all (since we do not allow
1949 -- choice parameters for local handlers).
1951 if No (Choice_Parameter (H)) then
1952 return H;
1953 else
1954 return Empty;
1955 end if;
1957 -- If not others must be entity name
1959 elsif Nkind (C) /= N_Others_Choice then
1960 pragma Assert (Is_Entity_Name (C));
1961 pragma Assert (Present (Entity (C)));
1963 -- Get exception being handled, dealing with
1964 -- renaming.
1966 EHandle := Get_Renamed_Entity (Entity (C));
1968 -- If match, then check choice parameter
1970 if ERaise = EHandle then
1971 if No (Choice_Parameter (H)) then
1972 return H;
1973 else
1974 return Empty;
1975 end if;
1976 end if;
1977 end if;
1979 Next (C);
1980 end loop;
1981 end if;
1983 Next (H);
1984 end loop;
1985 end if;
1986 end;
1987 end if;
1988 end if;
1990 N := P;
1991 end loop;
1992 end Find_Local_Handler;
1994 ---------------------------------
1995 -- Get_Local_Raise_Call_Entity --
1996 ---------------------------------
1998 -- Note: this is primary provided for use by the back end in generating
1999 -- calls to Local_Raise. But it would be too late in the back end to call
2000 -- RTE if this actually caused a load/analyze of the unit. So what we do
2001 -- is to ensure there is a dummy call to this function during front end
2002 -- processing so that the unit gets loaded then, and not later.
2004 Local_Raise_Call_Entity : Entity_Id;
2005 Local_Raise_Call_Entity_Set : Boolean := False;
2007 function Get_Local_Raise_Call_Entity return Entity_Id is
2008 begin
2009 if not Local_Raise_Call_Entity_Set then
2010 Local_Raise_Call_Entity_Set := True;
2012 if RTE_Available (RE_Local_Raise) then
2013 Local_Raise_Call_Entity := RTE (RE_Local_Raise);
2014 else
2015 Local_Raise_Call_Entity := Empty;
2016 end if;
2017 end if;
2019 return Local_Raise_Call_Entity;
2020 end Get_Local_Raise_Call_Entity;
2022 -----------------------------
2023 -- Get_RT_Exception_Entity --
2024 -----------------------------
2026 function Get_RT_Exception_Entity (R : RT_Exception_Code) return Entity_Id is
2027 begin
2028 case Rkind (R) is
2029 when CE_Reason => return Standard_Constraint_Error;
2030 when PE_Reason => return Standard_Program_Error;
2031 when SE_Reason => return Standard_Storage_Error;
2032 end case;
2033 end Get_RT_Exception_Entity;
2035 ---------------------------
2036 -- Get_RT_Exception_Name --
2037 ---------------------------
2039 procedure Get_RT_Exception_Name (Code : RT_Exception_Code) is
2040 begin
2041 case Code is
2042 when CE_Access_Check_Failed =>
2043 Add_Str_To_Name_Buffer ("CE_Access_Check");
2044 when CE_Access_Parameter_Is_Null =>
2045 Add_Str_To_Name_Buffer ("CE_Null_Access_Parameter");
2046 when CE_Discriminant_Check_Failed =>
2047 Add_Str_To_Name_Buffer ("CE_Discriminant_Check");
2048 when CE_Divide_By_Zero =>
2049 Add_Str_To_Name_Buffer ("CE_Divide_By_Zero");
2050 when CE_Explicit_Raise =>
2051 Add_Str_To_Name_Buffer ("CE_Explicit_Raise");
2052 when CE_Index_Check_Failed =>
2053 Add_Str_To_Name_Buffer ("CE_Index_Check");
2054 when CE_Invalid_Data =>
2055 Add_Str_To_Name_Buffer ("CE_Invalid_Data");
2056 when CE_Length_Check_Failed =>
2057 Add_Str_To_Name_Buffer ("CE_Length_Check");
2058 when CE_Null_Exception_Id =>
2059 Add_Str_To_Name_Buffer ("CE_Null_Exception_Id");
2060 when CE_Null_Not_Allowed =>
2061 Add_Str_To_Name_Buffer ("CE_Null_Not_Allowed");
2062 when CE_Overflow_Check_Failed =>
2063 Add_Str_To_Name_Buffer ("CE_Overflow_Check");
2064 when CE_Partition_Check_Failed =>
2065 Add_Str_To_Name_Buffer ("CE_Partition_Check");
2066 when CE_Range_Check_Failed =>
2067 Add_Str_To_Name_Buffer ("CE_Range_Check");
2068 when CE_Tag_Check_Failed =>
2069 Add_Str_To_Name_Buffer ("CE_Tag_Check");
2071 when PE_Access_Before_Elaboration =>
2072 Add_Str_To_Name_Buffer ("PE_Access_Before_Elaboration");
2073 when PE_Accessibility_Check_Failed =>
2074 Add_Str_To_Name_Buffer ("PE_Accessibility_Check");
2075 when PE_Address_Of_Intrinsic =>
2076 Add_Str_To_Name_Buffer ("PE_Address_Of_Intrinsic");
2077 when PE_Aliased_Parameters =>
2078 Add_Str_To_Name_Buffer ("PE_Aliased_Parameters");
2079 when PE_All_Guards_Closed =>
2080 Add_Str_To_Name_Buffer ("PE_All_Guards_Closed");
2081 when PE_Bad_Predicated_Generic_Type =>
2082 Add_Str_To_Name_Buffer ("PE_Bad_Predicated_Generic_Type");
2083 when PE_Current_Task_In_Entry_Body =>
2084 Add_Str_To_Name_Buffer ("PE_Current_Task_In_Entry_Body");
2085 when PE_Duplicated_Entry_Address =>
2086 Add_Str_To_Name_Buffer ("PE_Duplicated_Entry_Address");
2087 when PE_Explicit_Raise =>
2088 Add_Str_To_Name_Buffer ("PE_Explicit_Raise");
2089 when PE_Finalize_Raised_Exception =>
2090 Add_Str_To_Name_Buffer ("PE_Finalize_Raised_Exception");
2091 when PE_Implicit_Return =>
2092 Add_Str_To_Name_Buffer ("PE_Implicit_Return");
2093 when PE_Misaligned_Address_Value =>
2094 Add_Str_To_Name_Buffer ("PE_Misaligned_Address_Value");
2095 when PE_Missing_Return =>
2096 Add_Str_To_Name_Buffer ("PE_Missing_Return");
2097 when PE_Non_Transportable_Actual =>
2098 Add_Str_To_Name_Buffer ("PE_Non_Transportable_Actual");
2099 when PE_Overlaid_Controlled_Object =>
2100 Add_Str_To_Name_Buffer ("PE_Overlaid_Controlled_Object");
2101 when PE_Potentially_Blocking_Operation =>
2102 Add_Str_To_Name_Buffer ("PE_Potentially_Blocking_Operation");
2103 when PE_Stream_Operation_Not_Allowed =>
2104 Add_Str_To_Name_Buffer ("PE_Stream_Operation_Not_Allowed");
2105 when PE_Stubbed_Subprogram_Called =>
2106 Add_Str_To_Name_Buffer ("PE_Stubbed_Subprogram_Called");
2107 when PE_Unchecked_Union_Restriction =>
2108 Add_Str_To_Name_Buffer ("PE_Unchecked_Union_Restriction");
2110 when SE_Empty_Storage_Pool =>
2111 Add_Str_To_Name_Buffer ("SE_Empty_Storage_Pool");
2112 when SE_Explicit_Raise =>
2113 Add_Str_To_Name_Buffer ("SE_Explicit_Raise");
2114 when SE_Infinite_Recursion =>
2115 Add_Str_To_Name_Buffer ("SE_Infinite_Recursion");
2116 when SE_Object_Too_Large =>
2117 Add_Str_To_Name_Buffer ("SE_Object_Too_Large");
2118 end case;
2119 end Get_RT_Exception_Name;
2121 ----------------------------
2122 -- Warn_If_No_Propagation --
2123 ----------------------------
2125 procedure Warn_If_No_Propagation (N : Node_Id) is
2126 begin
2127 if Restriction_Check_Required (No_Exception_Propagation)
2128 and then Warn_On_Non_Local_Exception
2129 then
2130 Warn_No_Exception_Propagation_Active (N);
2132 if Configurable_Run_Time_Mode then
2133 Error_Msg_N
2134 ("\?X?Last_Chance_Handler will be called on exception", N);
2135 else
2136 Error_Msg_N
2137 ("\?X?execution may raise unhandled exception", N);
2138 end if;
2139 end if;
2140 end Warn_If_No_Propagation;
2142 ------------------------------------------
2143 -- Warn_No_Exception_Propagation_Active --
2144 ------------------------------------------
2146 procedure Warn_No_Exception_Propagation_Active (N : Node_Id) is
2147 begin
2148 Error_Msg_N
2149 ("?X?pragma Restrictions (No_Exception_Propagation) in effect", N);
2150 end Warn_No_Exception_Propagation_Active;
2152 end Exp_Ch11;