[RS6000] Don't be too clever with dg-do run and dg-do compile
[official-gcc.git] / gcc / ada / exp_prag.adb
blob53e2d97cd7559ffb9aca275156d0314c1d2bcde9
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- E X P _ P R A G --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2020, 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 Checks; use Checks;
29 with Debug; use Debug;
30 with Einfo; use Einfo;
31 with Elists; use Elists;
32 with Errout; use Errout;
33 with Exp_Ch11; use Exp_Ch11;
34 with Exp_Util; use Exp_Util;
35 with Expander; use Expander;
36 with Inline; use Inline;
37 with Lib; use Lib;
38 with Namet; use Namet;
39 with Nlists; use Nlists;
40 with Nmake; use Nmake;
41 with Opt; use Opt;
42 with Restrict; use Restrict;
43 with Rident; use Rident;
44 with Rtsfind; use Rtsfind;
45 with Sem; use Sem;
46 with Sem_Aux; use Sem_Aux;
47 with Sem_Ch8; use Sem_Ch8;
48 with Sem_Prag; use Sem_Prag;
49 with Sem_Util; use Sem_Util;
50 with Sinfo; use Sinfo;
51 with Sinput; use Sinput;
52 with Snames; use Snames;
53 with Stringt; use Stringt;
54 with Stand; use Stand;
55 with Tbuild; use Tbuild;
56 with Uintp; use Uintp;
57 with Validsw; use Validsw;
59 package body Exp_Prag is
61 -----------------------
62 -- Local Subprograms --
63 -----------------------
65 function Arg_N (N : Node_Id; Arg_Number : Positive) return Node_Id;
66 -- Obtain specified pragma argument expression
68 procedure Expand_Pragma_Abort_Defer (N : Node_Id);
69 procedure Expand_Pragma_Check (N : Node_Id);
70 procedure Expand_Pragma_Common_Object (N : Node_Id);
71 procedure Expand_Pragma_CUDA_Execute (N : Node_Id);
72 procedure Expand_Pragma_Import_Or_Interface (N : Node_Id);
73 procedure Expand_Pragma_Inspection_Point (N : Node_Id);
74 procedure Expand_Pragma_Interrupt_Priority (N : Node_Id);
75 procedure Expand_Pragma_Loop_Variant (N : Node_Id);
76 procedure Expand_Pragma_Psect_Object (N : Node_Id);
77 procedure Expand_Pragma_Relative_Deadline (N : Node_Id);
78 procedure Expand_Pragma_Suppress_Initialization (N : Node_Id);
80 procedure Undo_Initialization (Def_Id : Entity_Id; N : Node_Id);
81 -- This procedure is used to undo initialization already done for Def_Id,
82 -- which is always an E_Variable, in response to the occurrence of the
83 -- pragma N, a pragma Interface, Import, or Suppress_Initialization. In all
84 -- these cases we want no initialization to occur, but we have already done
85 -- the initialization by the time we see the pragma, so we have to undo it.
87 -----------
88 -- Arg_N --
89 -----------
91 function Arg_N (N : Node_Id; Arg_Number : Positive) return Node_Id is
92 Arg : Node_Id := First (Pragma_Argument_Associations (N));
93 begin
94 if No (Arg) then
95 return Empty;
96 end if;
98 for J in 2 .. Arg_Number loop
99 Next (Arg);
100 if No (Arg) then
101 return Empty;
102 end if;
103 end loop;
105 if Present (Arg)
106 and then Nkind (Arg) = N_Pragma_Argument_Association
107 then
108 return Expression (Arg);
109 else
110 return Arg;
111 end if;
112 end Arg_N;
114 ---------------------
115 -- Expand_N_Pragma --
116 ---------------------
118 procedure Expand_N_Pragma (N : Node_Id) is
119 Pname : constant Name_Id := Pragma_Name (N);
120 Prag_Id : constant Pragma_Id := Get_Pragma_Id (Pname);
122 begin
123 -- Suppress the expansion of an ignored assertion pragma. Such a pragma
124 -- should not be transformed into a null statment because:
126 -- * The pragma may be part of the rep item chain of a type, in which
127 -- case rewriting it will destroy the chain.
129 -- * The analysis of the pragma may involve two parts (see routines
130 -- Analyze_xxx_In_Decl_Part). The second part of the analysis will
131 -- not happen if the pragma is rewritten.
133 if Assertion_Expression_Pragma (Prag_Id) and then Is_Ignored (N) then
134 return;
136 -- Rewrite the pragma into a null statement when it is ignored using
137 -- pragma Ignore_Pragma, or denotes Default_Scalar_Storage_Order and
138 -- compilation switch -gnatI is in effect.
140 elsif Should_Ignore_Pragma_Sem (N)
141 or else (Prag_Id = Pragma_Default_Scalar_Storage_Order
142 and then Ignore_Rep_Clauses)
143 then
144 Rewrite (N, Make_Null_Statement (Sloc (N)));
145 return;
146 end if;
148 case Prag_Id is
150 -- Pragmas requiring special expander action
152 when Pragma_Abort_Defer =>
153 Expand_Pragma_Abort_Defer (N);
155 when Pragma_Check =>
156 Expand_Pragma_Check (N);
158 when Pragma_Common_Object =>
159 Expand_Pragma_Common_Object (N);
161 when Pragma_CUDA_Execute =>
162 Expand_Pragma_CUDA_Execute (N);
164 when Pragma_Import =>
165 Expand_Pragma_Import_Or_Interface (N);
167 when Pragma_Inspection_Point =>
168 Expand_Pragma_Inspection_Point (N);
170 when Pragma_Interface =>
171 Expand_Pragma_Import_Or_Interface (N);
173 when Pragma_Interrupt_Priority =>
174 Expand_Pragma_Interrupt_Priority (N);
176 when Pragma_Loop_Variant =>
177 Expand_Pragma_Loop_Variant (N);
179 when Pragma_Psect_Object =>
180 Expand_Pragma_Psect_Object (N);
182 when Pragma_Relative_Deadline =>
183 Expand_Pragma_Relative_Deadline (N);
185 when Pragma_Suppress_Initialization =>
186 Expand_Pragma_Suppress_Initialization (N);
188 -- All other pragmas need no expander action (includes
189 -- Unknown_Pragma).
191 when others => null;
192 end case;
193 end Expand_N_Pragma;
195 -------------------------------
196 -- Expand_Pragma_Abort_Defer --
197 -------------------------------
199 -- An Abort_Defer pragma appears as the first statement in a handled
200 -- statement sequence (right after the begin). It defers aborts for
201 -- the entire statement sequence, but not for any declarations or
202 -- handlers (if any) associated with this statement sequence.
204 -- The transformation is to transform
206 -- pragma Abort_Defer;
207 -- statements;
209 -- into
211 -- begin
212 -- Abort_Defer.all;
213 -- statements
214 -- exception
215 -- when all others =>
216 -- Abort_Undefer.all;
217 -- raise;
218 -- at end
219 -- Abort_Undefer_Direct;
220 -- end;
222 procedure Expand_Pragma_Abort_Defer (N : Node_Id) is
223 begin
224 -- Abort_Defer has no useful effect if Abort's are not allowed
226 if not Abort_Allowed then
227 return;
228 end if;
230 -- Normal case where abort is possible
232 declare
233 Loc : constant Source_Ptr := Sloc (N);
234 Stm : Node_Id;
235 Stms : List_Id;
236 HSS : Node_Id;
237 Blk : constant Entity_Id :=
238 New_Internal_Entity (E_Block, Current_Scope, Sloc (N), 'B');
239 AUD : constant Entity_Id := RTE (RE_Abort_Undefer_Direct);
241 begin
242 Stms := New_List (Build_Runtime_Call (Loc, RE_Abort_Defer));
243 loop
244 Stm := Remove_Next (N);
245 exit when No (Stm);
246 Append (Stm, Stms);
247 end loop;
249 HSS :=
250 Make_Handled_Sequence_Of_Statements (Loc,
251 Statements => Stms,
252 At_End_Proc => New_Occurrence_Of (AUD, Loc));
254 -- Present the Abort_Undefer_Direct function to the backend so that
255 -- it can inline the call to the function.
257 Add_Inlined_Body (AUD, N);
259 Rewrite (N,
260 Make_Block_Statement (Loc, Handled_Statement_Sequence => HSS));
262 Set_Scope (Blk, Current_Scope);
263 Set_Etype (Blk, Standard_Void_Type);
264 Set_Identifier (N, New_Occurrence_Of (Blk, Sloc (N)));
265 Expand_At_End_Handler (HSS, Blk);
266 Analyze (N);
267 end;
268 end Expand_Pragma_Abort_Defer;
270 --------------------------
271 -- Expand_Pragma_Check --
272 --------------------------
274 procedure Expand_Pragma_Check (N : Node_Id) is
275 Cond : constant Node_Id := Arg_N (N, 2);
276 Nam : constant Name_Id := Chars (Arg_N (N, 1));
277 Msg : Node_Id;
279 Loc : constant Source_Ptr := Sloc (First_Node (Cond));
280 -- Source location used in the case of a failed assertion: point to the
281 -- failing condition, not Loc. Note that the source location of the
282 -- expression is not usually the best choice here, because it points to
283 -- the location of the topmost tree node, which may be an operator in
284 -- the middle of the source text of the expression. For example, it gets
285 -- located on the last AND keyword in a chain of boolean expressiond
286 -- AND'ed together. It is best to put the message on the first character
287 -- of the condition, which is the effect of the First_Node call here.
288 -- This source location is used to build the default exception message,
289 -- and also as the sloc of the call to the runtime subprogram raising
290 -- Assert_Failure, so that coverage analysis tools can relate the
291 -- call to the failed check.
293 procedure Replace_Discriminals_Of_Protected_Op (Expr : Node_Id);
294 -- Discriminants of the enclosing protected object may be referenced
295 -- in the expression of a precondition of a protected operation.
296 -- In the body of the operation these references must be replaced by
297 -- the discriminal created for them, which are renamings of the
298 -- discriminants of the object that is the target of the operation.
299 -- This replacement is done by visibility when the references appear
300 -- in the subprogram body, but in the case of a condition which appears
301 -- on the specification of the subprogram it has be done separately
302 -- because the condition has been replaced by a Check pragma and
303 -- analyzed earlier, before the creation of the discriminal renaming
304 -- declarations that are added to the subprogram body.
306 ------------------------------------------
307 -- Replace_Discriminals_Of_Protected_Op --
308 ------------------------------------------
310 procedure Replace_Discriminals_Of_Protected_Op (Expr : Node_Id) is
311 function Find_Corresponding_Discriminal
312 (E : Entity_Id) return Entity_Id;
313 -- Find the local entity that renames a discriminant of the enclosing
314 -- protected type, and has a matching name.
316 function Replace_Discr_Ref (N : Node_Id) return Traverse_Result;
317 -- Replace a reference to a discriminant of the original protected
318 -- type by the local renaming declaration of the discriminant of
319 -- the target object.
321 ------------------------------------
322 -- Find_Corresponding_Discriminal --
323 ------------------------------------
325 function Find_Corresponding_Discriminal
326 (E : Entity_Id) return Entity_Id
328 R : Entity_Id;
330 begin
331 R := First_Entity (Current_Scope);
333 while Present (R) loop
334 if Nkind (Parent (R)) = N_Object_Renaming_Declaration
335 and then Present (Discriminal_Link (R))
336 and then Chars (Discriminal_Link (R)) = Chars (E)
337 then
338 return R;
339 end if;
341 Next_Entity (R);
342 end loop;
344 return Empty;
345 end Find_Corresponding_Discriminal;
347 -----------------------
348 -- Replace_Discr_Ref --
349 -----------------------
351 function Replace_Discr_Ref (N : Node_Id) return Traverse_Result is
352 R : Entity_Id;
354 begin
355 if Is_Entity_Name (N)
356 and then Present (Discriminal_Link (Entity (N)))
357 then
358 R := Find_Corresponding_Discriminal (Entity (N));
359 Rewrite (N, New_Occurrence_Of (R, Sloc (N)));
360 end if;
362 return OK;
363 end Replace_Discr_Ref;
365 procedure Replace_Discriminant_References is
366 new Traverse_Proc (Replace_Discr_Ref);
368 -- Start of processing for Replace_Discriminals_Of_Protected_Op
370 begin
371 Replace_Discriminant_References (Expr);
372 end Replace_Discriminals_Of_Protected_Op;
374 -- Start of processing for Expand_Pragma_Check
376 begin
377 -- Nothing to do if pragma is ignored
379 if Is_Ignored (N) then
380 return;
381 end if;
383 -- Since this check is active, rewrite the pragma into a corresponding
384 -- if statement, and then analyze the statement.
386 -- The normal case expansion transforms:
388 -- pragma Check (name, condition [,message]);
390 -- into
392 -- if not condition then
393 -- System.Assertions.Raise_Assert_Failure (Str);
394 -- end if;
396 -- where Str is the message if one is present, or the default of
397 -- name failed at file:line if no message is given (the "name failed
398 -- at" is omitted for name = Assertion, since it is redundant, given
399 -- that the name of the exception is Assert_Failure.)
401 -- Also, instead of "XXX failed at", we generate slightly
402 -- different messages for some of the contract assertions (see
403 -- code below for details).
405 -- An alternative expansion is used when the No_Exception_Propagation
406 -- restriction is active and there is a local Assert_Failure handler.
407 -- This is not a common combination of circumstances, but it occurs in
408 -- the context of Aunit and the zero footprint profile. In this case we
409 -- generate:
411 -- if not condition then
412 -- raise Assert_Failure;
413 -- end if;
415 -- This will then be transformed into a goto, and the local handler will
416 -- be able to handle the assert error (which would not be the case if a
417 -- call is made to the Raise_Assert_Failure procedure).
419 -- We also generate the direct raise if the Suppress_Exception_Locations
420 -- is active, since we don't want to generate messages in this case.
422 -- Note that the reason we do not always generate a direct raise is that
423 -- the form in which the procedure is called allows for more efficient
424 -- breakpointing of assertion errors.
426 -- Generate the appropriate if statement. Note that we consider this to
427 -- be an explicit conditional in the source, not an implicit if, so we
428 -- do not call Make_Implicit_If_Statement.
430 -- Case where we generate a direct raise
432 if ((Debug_Flag_Dot_G
433 or else Restriction_Active (No_Exception_Propagation))
434 and then Present (Find_Local_Handler (RTE (RE_Assert_Failure), N)))
435 or else (Opt.Exception_Locations_Suppressed and then No (Arg_N (N, 3)))
436 then
437 Rewrite (N,
438 Make_If_Statement (Loc,
439 Condition => Make_Op_Not (Loc, Right_Opnd => Cond),
440 Then_Statements => New_List (
441 Make_Raise_Statement (Loc,
442 Name => New_Occurrence_Of (RTE (RE_Assert_Failure), Loc)))));
444 -- Case where we call the procedure
446 else
447 -- If we have a message given, use it
449 if Present (Arg_N (N, 3)) then
450 Msg := Get_Pragma_Arg (Arg_N (N, 3));
452 -- Here we have no string, so prepare one
454 else
455 declare
456 Loc_Str : constant String := Build_Location_String (Loc);
458 begin
459 Name_Len := 0;
461 -- For Assert, we just use the location
463 if Nam = Name_Assert then
464 null;
466 -- For predicate, we generate the string "predicate failed at
467 -- yyy". We prefer all lower case for predicate.
469 elsif Nam = Name_Predicate then
470 Add_Str_To_Name_Buffer ("predicate failed at ");
472 -- For special case of Precondition/Postcondition the string is
473 -- "failed xx from yy" where xx is precondition/postcondition
474 -- in all lower case. The reason for this different wording is
475 -- that the failure is not at the point of occurrence of the
476 -- pragma, unlike the other Check cases.
478 elsif Nam in Name_Precondition | Name_Postcondition then
479 Get_Name_String (Nam);
480 Insert_Str_In_Name_Buffer ("failed ", 1);
481 Add_Str_To_Name_Buffer (" from ");
483 -- For special case of Invariant, the string is "failed
484 -- invariant from yy", to be consistent with the string that is
485 -- generated for the aspect case (the code later on checks for
486 -- this specific string to modify it in some cases, so this is
487 -- functionally important).
489 elsif Nam = Name_Invariant then
490 Add_Str_To_Name_Buffer ("failed invariant from ");
492 -- For all other checks, the string is "xxx failed at yyy"
493 -- where xxx is the check name with appropriate casing.
495 else
496 Get_Name_String (Nam);
497 Set_Casing
498 (Identifier_Casing (Source_Index (Current_Sem_Unit)));
499 Add_Str_To_Name_Buffer (" failed at ");
500 end if;
502 -- In all cases, add location string
504 Add_Str_To_Name_Buffer (Loc_Str);
506 -- Build the message
508 Msg := Make_String_Literal (Loc, Name_Buffer (1 .. Name_Len));
509 end;
510 end if;
512 -- For a precondition, replace references to discriminants of a
513 -- protected type with the local discriminals.
515 if Is_Protected_Type (Scope (Current_Scope))
516 and then Has_Discriminants (Scope (Current_Scope))
517 and then From_Aspect_Specification (N)
518 then
519 Replace_Discriminals_Of_Protected_Op (Cond);
520 end if;
522 -- Now rewrite as an if statement
524 Rewrite (N,
525 Make_If_Statement (Loc,
526 Condition => Make_Op_Not (Loc, Right_Opnd => Cond),
527 Then_Statements => New_List (
528 Make_Procedure_Call_Statement (Loc,
529 Name =>
530 New_Occurrence_Of (RTE (RE_Raise_Assert_Failure), Loc),
531 Parameter_Associations => New_List (Relocate_Node (Msg))))));
532 end if;
534 Analyze (N);
536 -- If new condition is always false, give a warning
538 if Warn_On_Assertion_Failure
539 and then Nkind (N) = N_Procedure_Call_Statement
540 and then Is_RTE (Entity (Name (N)), RE_Raise_Assert_Failure)
541 then
542 -- If original condition was a Standard.False, we assume that this is
543 -- indeed intended to raise assert error and no warning is required.
545 if Is_Entity_Name (Original_Node (Cond))
546 and then Entity (Original_Node (Cond)) = Standard_False
547 then
548 null;
550 elsif Nam = Name_Assert then
551 Error_Msg_N ("?A?assertion will fail at run time", N);
552 else
553 Error_Msg_N ("?A?check will fail at run time", N);
554 end if;
555 end if;
556 end Expand_Pragma_Check;
558 ---------------------------------
559 -- Expand_Pragma_Common_Object --
560 ---------------------------------
562 -- Use a machine attribute to replicate semantic effect in DEC Ada
564 -- pragma Machine_Attribute (intern_name, "common_object", extern_name);
566 -- For now we do nothing with the size attribute ???
568 -- Note: Psect_Object shares this processing
570 procedure Expand_Pragma_Common_Object (N : Node_Id) is
571 Loc : constant Source_Ptr := Sloc (N);
573 Internal : constant Node_Id := Arg_N (N, 1);
574 External : constant Node_Id := Arg_N (N, 2);
576 Psect : Node_Id;
577 -- Psect value upper cased as string literal
579 Iloc : constant Source_Ptr := Sloc (Internal);
580 Eloc : constant Source_Ptr := Sloc (External);
581 Ploc : Source_Ptr;
583 begin
584 -- Acquire Psect value and fold to upper case
586 if Present (External) then
587 if Nkind (External) = N_String_Literal then
588 String_To_Name_Buffer (Strval (External));
589 else
590 Get_Name_String (Chars (External));
591 end if;
593 Set_All_Upper_Case;
595 Psect :=
596 Make_String_Literal (Eloc, Strval => String_From_Name_Buffer);
598 else
599 Get_Name_String (Chars (Internal));
600 Set_All_Upper_Case;
601 Psect :=
602 Make_String_Literal (Iloc, Strval => String_From_Name_Buffer);
603 end if;
605 Ploc := Sloc (Psect);
607 -- Insert the pragma
609 Insert_After_And_Analyze (N,
610 Make_Pragma (Loc,
611 Chars => Name_Machine_Attribute,
612 Pragma_Argument_Associations => New_List (
613 Make_Pragma_Argument_Association (Iloc,
614 Expression => New_Copy_Tree (Internal)),
615 Make_Pragma_Argument_Association (Eloc,
616 Expression =>
617 Make_String_Literal (Sloc => Ploc, Strval => "common_object")),
618 Make_Pragma_Argument_Association (Ploc,
619 Expression => New_Copy_Tree (Psect)))));
620 end Expand_Pragma_Common_Object;
622 --------------------------------
623 -- Expand_Pragma_CUDA_Execute --
624 --------------------------------
626 -- Pragma CUDA_Execute is expanded in the following manner:
628 -- Original Code
630 -- pragma CUDA_Execute (My_Proc (X, Y), Blocks, Grids, Mem, Stream)
632 -- Expanded Code
634 -- declare
635 -- Blocks_Id : CUDA.Vector_Types.Dim3 := Blocks;
636 -- Grids_Id : CUDA.Vector_Types.Dim3 := Grids;
637 -- Mem_Id : Integer := <Mem or 0>;
638 -- Stream_Id : CUDA.Driver_Types.Stream_T := <Stream or null>;
639 -- X_Id : <Type of X> := X;
640 -- Y_Id : <Type of Y> := Y;
641 -- Arg_Id : Array (1..2) of System.Address :=
642 -- (X'Address,_Id Y'Address);_Id
643 -- begin
644 -- CUDA.Internal.Push_Call_Configuration (
645 -- Grids_Id,
646 -- Blocks_Id,
647 -- Mem_Id,
648 -- Stream_Id);
649 -- CUDA.Internal.Pop_Call_Configuration (
650 -- Grids_Id'address,
651 -- Blocks_Id'address,
652 -- Mem_Id'address,
653 -- Stream_Id'address),
654 -- CUDA.Runtime_Api.Launch_Kernel (
655 -- My_Proc'Address,
656 -- Blocks_Id,
657 -- Grids_Id,
658 -- Arg_Id'Address,
659 -- Mem_Id,
660 -- Stream_Id);
661 -- end;
663 procedure Expand_Pragma_CUDA_Execute (N : Node_Id) is
665 Loc : constant Source_Ptr := Sloc (N);
667 procedure Append_Copies
668 (Params : List_Id;
669 Decls : List_Id;
670 Copies : Elist_Id);
671 -- For each parameter in list Params, create an object declaration of
672 -- the followinng form:
674 -- Copy_Id : Param_Typ := Param_Val;
676 -- Param_Typ is the type of the parameter. Param_Val is the initial
677 -- value of the parameter. The declarations are stored in Decls, the
678 -- entities of the new objects are collected in list Copies.
680 function Build_Dim3_Declaration
681 (Decl_Id : Entity_Id;
682 Init_Val : Node_Id) return Node_Id;
683 -- Build an object declaration of the form
685 -- Decl_Id : CUDA.Internal.Dim3 := Val;
687 -- Val depends on the nature of Init_Val, as follows:
689 -- * If Init_Val is of type CUDA.Vector_Types.Dim3, then Val has the
690 -- following form:
692 -- (Interfaces.C.Unsigned (Val.X),
693 -- Interfaces.C.Unsigned (Val.Y),
694 -- Interfaces.C.Unsigned (Val.Z))
696 -- * If Init_Val is a single Integer, Val has the following form:
698 -- (Interfaces.C.Unsigned (Init_Val),
699 -- Interfaces.C.Unsigned (1),
700 -- Interfaces.C.Unsigned (1))
702 -- * If Init_Val is an aggregate of three values, Val has the
703 -- following form:
705 -- (Interfaces.C.Unsigned (Val_1),
706 -- Interfaces.C.Unsigned (Val_2),
707 -- Interfaces.C.Unsigned (Val_3))
709 function Build_Kernel_Args_Declaration
710 (Kernel_Arg : Entity_Id;
711 Var_Ids : Elist_Id) return Node_Id;
712 -- Given a list of variables, return an object declaration of the
713 -- following form:
715 -- Kernel_Arg : ... := (Var_1'Address, ..., Var_N'Address);
717 function Build_Launch_Kernel_Call
718 (Proc : Entity_Id;
719 Grid_Dims : Entity_Id;
720 Block_Dims : Entity_Id;
721 Kernel_Arg : Entity_Id;
722 Memory : Entity_Id;
723 Stream : Entity_Id) return Node_Id;
724 -- Builds and returns a call to CUDA.Launch_Kernel using the given
725 -- arguments. Proc is the entity of the procedure passed to the
726 -- CUDA_Execute pragma. Grid_Dims and Block_Dims are entities of the
727 -- generated declarations that hold the kernel's dimensions. Args is the
728 -- entity of the temporary array that holds the arguments of the kernel.
729 -- Memory and Stream are the entities of the temporaries that hold the
730 -- fourth and fith arguments of CUDA_Execute or their default values.
732 function Build_Shared_Memory_Declaration
733 (Decl_Id : Entity_Id;
734 Init_Val : Node_Id) return Node_Id;
735 -- Builds a declaration the Defining_Identifier of which is Decl_Id, the
736 -- type of which is inferred from CUDA.Internal.Launch_Kernel and the
737 -- value of which is Init_Val if present or null if not.
739 function Build_Simple_Declaration_With_Default
740 (Decl_Id : Entity_Id;
741 Init_Val : Entity_Id;
742 Typ : Entity_Id;
743 Default_Val : Entity_Id) return Node_Id;
744 -- Build a declaration the Defining_Identifier of which is Decl_Id, the
745 -- Object_Definition of which is Typ, the value of which is Init_Val if
746 -- present or Default otherwise.
748 function Build_Stream_Declaration
749 (Decl_Id : Entity_Id;
750 Init_Val : Node_Id) return Node_Id;
751 -- Build a declaration the Defining_Identifier of which is Decl_Id, the
752 -- type of which is Integer, the value of which is Init_Val if present
753 -- and 0 otherwise.
755 function Etype_Or_Dim3 (N : Node_Id) return Node_Id;
756 -- If N is an aggregate whose type is unknown, return a new occurrence
757 -- of the public Dim3 type. Otherwise, return a new occurrence of N's
758 -- type.
760 function Get_Nth_Arg_Type
761 (Subprogram : Entity_Id;
762 N : Positive) return Entity_Id;
763 -- Returns the type of the Nth argument of Subprogram.
765 function To_Addresses (Elmts : Elist_Id) return List_Id;
766 -- Returns a new list containing each element of Elmts wrapped in an
767 -- 'address attribute reference. When passed No_Elist, returns an empty
768 -- list.
770 -------------------
771 -- Append_Copies --
772 -------------------
774 procedure Append_Copies
775 (Params : List_Id;
776 Decls : List_Id;
777 Copies : Elist_Id)
779 Copy : Entity_Id;
780 Param : Node_Id;
781 Expr : Node_Id;
782 begin
783 Param := First (Params);
784 while Present (Param) loop
785 Copy := Make_Temporary (Loc, 'C');
787 if Nkind (Param) = N_Parameter_Association then
788 Expr := Explicit_Actual_Parameter (Param);
789 else
790 Expr := Param;
791 end if;
793 Append_To (Decls,
794 Make_Object_Declaration (Loc,
795 Defining_Identifier => Copy,
796 Object_Definition => New_Occurrence_Of (Etype (Expr), Loc),
797 Expression => New_Copy_Tree (Expr)));
799 Append_Elmt (Copy, Copies);
800 Next (Param);
801 end loop;
802 end Append_Copies;
804 ----------------------------
805 -- Build_Dim3_Declaration --
806 ----------------------------
808 function Build_Dim3_Declaration
809 (Decl_Id : Entity_Id;
810 Init_Val : Node_Id) return Node_Id
812 -- Expressions for each component of the returned Dim3
813 Dim_X : Node_Id;
814 Dim_Y : Node_Id;
815 Dim_Z : Node_Id;
817 -- Type of CUDA.Internal.Dim3 - inferred from
818 -- RE_Push_Call_Configuration to avoid needing changes in GNAT when
819 -- the CUDA bindings change (this happens frequently).
820 Internal_Dim3 : constant Entity_Id :=
821 Get_Nth_Arg_Type (RTE (RE_Push_Call_Configuration), 1);
823 -- Entities for each component of external and internal Dim3
824 First_Component : Entity_Id := First_Entity (RTE (RE_Dim3));
825 Second_Component : Entity_Id := Next_Entity (First_Component);
826 Third_Component : Entity_Id := Next_Entity (Second_Component);
827 begin
829 -- Sem_prag.adb ensured that Init_Val is either a Dim3, an
830 -- aggregate of three Any_Integers or Any_Integer.
832 -- If Init_Val is a Dim3, use each of its components.
834 if Etype (Init_Val) = RTE (RE_Dim3) then
835 Dim_X := Make_Selected_Component (Loc,
836 Prefix => New_Occurrence_Of (Entity (Init_Val), Loc),
837 Selector_Name => New_Occurrence_Of (First_Component, Loc));
839 Dim_Y := Make_Selected_Component (Loc,
840 Prefix => New_Occurrence_Of (Entity (Init_Val), Loc),
841 Selector_Name => New_Occurrence_Of (Second_Component, Loc));
843 Dim_Z := Make_Selected_Component (Loc,
844 Prefix => New_Occurrence_Of (Entity (Init_Val), Loc),
845 Selector_Name => New_Occurrence_Of (Third_Component, Loc));
846 else
847 -- If Init_Val is an aggregate, use each of its arguments
849 if Nkind (Init_Val) = N_Aggregate then
850 Dim_X := First (Expressions (Init_Val));
851 Dim_Y := Next (Dim_X);
852 Dim_Z := Next (Dim_Y);
854 -- Otherwise, we know it is an integer and the rest defaults to 1.
856 else
857 Dim_X := Init_Val;
858 Dim_Y := Make_Integer_Literal (Loc, 1);
859 Dim_Z := Make_Integer_Literal (Loc, 1);
860 end if;
861 end if;
863 First_Component := First_Entity (Internal_Dim3);
864 Second_Component := Next_Entity (First_Component);
865 Third_Component := Next_Entity (Second_Component);
867 -- Finally return the CUDA.Internal.Dim3 declaration with an
868 -- aggregate initialization expression.
870 return Make_Object_Declaration (Loc,
871 Defining_Identifier => Decl_Id,
872 Object_Definition => New_Occurrence_Of (Internal_Dim3, Loc),
873 Expression => Make_Aggregate (Loc,
874 Expressions => New_List (
875 Make_Type_Conversion (Loc,
876 Subtype_Mark =>
877 New_Occurrence_Of (Etype (First_Component), Loc),
878 Expression => New_Copy_Tree (Dim_X)),
879 Make_Type_Conversion (Loc,
880 Subtype_Mark =>
881 New_Occurrence_Of (Etype (Second_Component), Loc),
882 Expression => New_Copy_Tree (Dim_Y)),
883 Make_Type_Conversion (Loc,
884 Subtype_Mark =>
885 New_Occurrence_Of (Etype (Third_Component), Loc),
886 Expression => New_Copy_Tree (Dim_Z)))));
887 end Build_Dim3_Declaration;
889 -----------------------------------
890 -- Build_Kernel_Args_Declaration --
891 -----------------------------------
893 function Build_Kernel_Args_Declaration
894 (Kernel_Arg : Entity_Id;
895 Var_Ids : Elist_Id) return Node_Id
897 Vals : constant List_Id := To_Addresses (Var_Ids);
898 begin
899 return
900 Make_Object_Declaration (Loc,
901 Defining_Identifier => Kernel_Arg,
902 Object_Definition =>
903 Make_Constrained_Array_Definition (Loc,
904 Discrete_Subtype_Definitions => New_List (
905 Make_Range (Loc,
906 Low_Bound => Make_Integer_Literal (Loc, 1),
907 High_Bound =>
908 Make_Integer_Literal (Loc, List_Length (Vals)))),
909 Component_Definition =>
910 Make_Component_Definition (Loc,
911 Subtype_Indication =>
912 New_Occurrence_Of (Etype (RTE (RE_Address)), Loc))),
913 Expression => Make_Aggregate (Loc, Vals));
914 end Build_Kernel_Args_Declaration;
916 -------------------------------
917 -- Build_Launch_Kernel_Call --
918 -------------------------------
920 function Build_Launch_Kernel_Call
921 (Proc : Entity_Id;
922 Grid_Dims : Entity_Id;
923 Block_Dims : Entity_Id;
924 Kernel_Arg : Entity_Id;
925 Memory : Entity_Id;
926 Stream : Entity_Id) return Node_Id is
927 begin
928 return
929 Make_Procedure_Call_Statement (Loc,
930 Name =>
931 New_Occurrence_Of (RTE (RE_Launch_Kernel), Loc),
932 Parameter_Associations => New_List (
933 Make_Attribute_Reference (Loc,
934 Prefix => New_Occurrence_Of (Proc, Loc),
935 Attribute_Name => Name_Address),
936 New_Occurrence_Of (Grid_Dims, Loc),
937 New_Occurrence_Of (Block_Dims, Loc),
938 Make_Attribute_Reference (Loc,
939 Prefix => New_Occurrence_Of (Kernel_Arg, Loc),
940 Attribute_Name => Name_Address),
941 New_Occurrence_Of (Memory, Loc),
942 New_Occurrence_Of (Stream, Loc)));
943 end Build_Launch_Kernel_Call;
945 -------------------------------------
946 -- Build_Shared_Memory_Declaration --
947 -------------------------------------
949 function Build_Shared_Memory_Declaration
950 (Decl_Id : Entity_Id;
951 Init_Val : Node_Id) return Node_Id
953 begin
954 return Build_Simple_Declaration_With_Default
955 (Decl_Id => Decl_Id,
956 Init_Val => Init_Val,
957 Typ =>
958 New_Occurrence_Of
959 (Get_Nth_Arg_Type (RTE (RE_Launch_Kernel), 5), Loc),
960 Default_Val => Make_Integer_Literal (Loc, 0));
961 end Build_Shared_Memory_Declaration;
963 -------------------------------------------
964 -- Build_Simple_Declaration_With_Default --
965 -------------------------------------------
967 function Build_Simple_Declaration_With_Default
968 (Decl_Id : Entity_Id;
969 Init_Val : Node_Id;
970 Typ : Entity_Id;
971 Default_Val : Node_Id) return Node_Id
973 Value : Node_Id := Init_Val;
974 begin
975 if No (Value) then
976 Value := Default_Val;
977 end if;
979 return Make_Object_Declaration (Loc,
980 Defining_Identifier => Decl_Id,
981 Object_Definition => Typ,
982 Expression => Value);
983 end Build_Simple_Declaration_With_Default;
985 ------------------------------
986 -- Build_Stream_Declaration --
987 ------------------------------
989 function Build_Stream_Declaration
990 (Decl_Id : Entity_Id;
991 Init_Val : Node_Id) return Node_Id
993 begin
994 return Build_Simple_Declaration_With_Default
995 (Decl_Id => Decl_Id,
996 Init_Val => Init_Val,
997 Typ =>
998 New_Occurrence_Of
999 (Get_Nth_Arg_Type (RTE (RE_Launch_Kernel), 6), Loc),
1000 Default_Val => Make_Null (Loc));
1001 end Build_Stream_Declaration;
1003 ------------------------
1004 -- Etype_Or_Dim3 --
1005 ------------------------
1007 function Etype_Or_Dim3 (N : Node_Id) return Node_Id is
1008 begin
1009 if Nkind (N) = N_Aggregate and then Is_Composite_Type (Etype (N))
1010 then
1011 return New_Occurrence_Of (RTE (RE_Dim3), Sloc (N));
1012 end if;
1014 return New_Occurrence_Of (Etype (N), Loc);
1015 end Etype_Or_Dim3;
1017 ----------------------
1018 -- Get_Nth_Arg_Type --
1019 ----------------------
1021 function Get_Nth_Arg_Type
1022 (Subprogram : Entity_Id;
1023 N : Positive) return Entity_Id
1025 Argument : Entity_Id := First_Entity (Subprogram);
1026 begin
1027 for J in 2 .. N loop
1028 Argument := Next_Entity (Argument);
1029 end loop;
1031 return Etype (Argument);
1032 end Get_Nth_Arg_Type;
1034 ------------------
1035 -- To_Addresses --
1036 ------------------
1038 function To_Addresses (Elmts : Elist_Id) return List_Id is
1039 Result : constant List_Id := New_List;
1040 Elmt : Elmt_Id;
1041 begin
1042 if Elmts = No_Elist then
1043 return Result;
1044 end if;
1046 Elmt := First_Elmt (Elmts);
1047 while Present (Elmt) loop
1048 Append_To (Result,
1049 Make_Attribute_Reference (Loc,
1050 Prefix => New_Occurrence_Of (Node (Elmt), Loc),
1051 Attribute_Name => Name_Address));
1052 Next_Elmt (Elmt);
1053 end loop;
1055 return Result;
1056 end To_Addresses;
1058 -- Local variables
1060 -- Pragma arguments
1062 Procedure_Call : constant Node_Id := Get_Pragma_Arg (Arg_N (N, 1));
1063 Grid_Dimensions : constant Node_Id := Get_Pragma_Arg (Arg_N (N, 2));
1064 Block_Dimensions : constant Node_Id := Get_Pragma_Arg (Arg_N (N, 3));
1065 Shared_Memory : constant Node_Id := Get_Pragma_Arg (Arg_N (N, 4));
1066 CUDA_Stream : constant Node_Id := Get_Pragma_Arg (Arg_N (N, 5));
1068 -- Entities of objects that will be overwritten by calls to cuda runtime
1069 Grids_Id : constant Entity_Id := Make_Temporary (Loc, 'C');
1070 Blocks_Id : constant Entity_Id := Make_Temporary (Loc, 'C');
1071 Memory_Id : constant Entity_Id := Make_Temporary (Loc, 'C');
1072 Stream_Id : constant Entity_Id := Make_Temporary (Loc, 'C');
1074 -- Entities of objects that capture the value of pragma arguments
1075 Temp_Grid : constant Entity_Id := Make_Temporary (Loc, 'C');
1076 Temp_Block : constant Entity_Id := Make_Temporary (Loc, 'C');
1078 -- Declarations for temporary block and grids. These needs to be stored
1079 -- in temporary declarations as the expressions will need to be
1080 -- referenced multiple times but could have side effects.
1081 Temp_Grid_Decl : constant Node_Id := Make_Object_Declaration (Loc,
1082 Defining_Identifier => Temp_Grid,
1083 Object_Definition => Etype_Or_Dim3 (Grid_Dimensions),
1084 Expression => Grid_Dimensions);
1085 Temp_Block_Decl : constant Node_Id := Make_Object_Declaration (Loc,
1086 Defining_Identifier => Temp_Block,
1087 Object_Definition => Etype_Or_Dim3 (Block_Dimensions),
1088 Expression => Block_Dimensions);
1090 -- List holding the entities of the copies of Procedure_Call's
1091 -- arguments.
1093 Kernel_Arg_Copies : constant Elist_Id := New_Elmt_List;
1095 -- Entity of the array that contains the address of each of the kernel's
1096 -- arguments.
1098 Kernel_Args_Id : constant Entity_Id := Make_Temporary (Loc, 'C');
1100 -- Calls to the CUDA runtime API.
1102 Launch_Kernel_Call : Node_Id;
1103 Pop_Call : Node_Id;
1104 Push_Call : Node_Id;
1106 -- Declaration of all temporaries required for CUDA API Calls.
1108 Blk_Decls : constant List_Id := New_List;
1110 -- Start of processing for CUDA_Execute
1112 begin
1113 -- Append temporary declarations
1115 Append_To (Blk_Decls, Temp_Grid_Decl);
1116 Analyze (Temp_Grid_Decl);
1118 Append_To (Blk_Decls, Temp_Block_Decl);
1119 Analyze (Temp_Block_Decl);
1121 -- Build parameter declarations for CUDA API calls
1123 Append_To
1124 (Blk_Decls,
1125 Build_Dim3_Declaration
1126 (Grids_Id, New_Occurrence_Of (Temp_Grid, Loc)));
1128 Append_To
1129 (Blk_Decls,
1130 Build_Dim3_Declaration
1131 (Blocks_Id, New_Occurrence_Of (Temp_Block, Loc)));
1133 Append_To
1134 (Blk_Decls,
1135 Build_Shared_Memory_Declaration (Memory_Id, Shared_Memory));
1137 Append_To
1138 (Blk_Decls, Build_Stream_Declaration (Stream_Id, CUDA_Stream));
1140 Append_Copies
1141 (Parameter_Associations (Procedure_Call),
1142 Blk_Decls,
1143 Kernel_Arg_Copies);
1145 Append_To
1146 (Blk_Decls,
1147 Build_Kernel_Args_Declaration
1148 (Kernel_Args_Id, Kernel_Arg_Copies));
1150 -- Build calls to the CUDA API
1152 Push_Call :=
1153 Make_Procedure_Call_Statement (Loc,
1154 Name =>
1155 New_Occurrence_Of (RTE (RE_Push_Call_Configuration), Loc),
1156 Parameter_Associations => New_List (
1157 New_Occurrence_Of (Grids_Id, Loc),
1158 New_Occurrence_Of (Blocks_Id, Loc),
1159 New_Occurrence_Of (Memory_Id, Loc),
1160 New_Occurrence_Of (Stream_Id, Loc)));
1162 Pop_Call :=
1163 Make_Procedure_Call_Statement (Loc,
1164 Name =>
1165 New_Occurrence_Of (RTE (RE_Pop_Call_Configuration), Loc),
1166 Parameter_Associations => To_Addresses
1167 (New_Elmt_List
1168 (Grids_Id,
1169 Blocks_Id,
1170 Memory_Id,
1171 Stream_Id)));
1173 Launch_Kernel_Call := Build_Launch_Kernel_Call
1174 (Proc => Entity (Name (Procedure_Call)),
1175 Grid_Dims => Grids_Id,
1176 Block_Dims => Blocks_Id,
1177 Kernel_Arg => Kernel_Args_Id,
1178 Memory => Memory_Id,
1179 Stream => Stream_Id);
1181 -- Finally make the block that holds declarations and calls
1183 Rewrite (N,
1184 Make_Block_Statement (Loc,
1185 Declarations => Blk_Decls,
1186 Handled_Statement_Sequence =>
1187 Make_Handled_Sequence_Of_Statements (Loc,
1188 Statements => New_List (
1189 Push_Call,
1190 Pop_Call,
1191 Launch_Kernel_Call))));
1192 Analyze (N);
1193 end Expand_Pragma_CUDA_Execute;
1195 ----------------------------------
1196 -- Expand_Pragma_Contract_Cases --
1197 ----------------------------------
1199 -- Pragma Contract_Cases is expanded in the following manner:
1201 -- subprogram S is
1202 -- Count : Natural := 0;
1203 -- Flag_1 : Boolean := False;
1204 -- . . .
1205 -- Flag_N : Boolean := False;
1206 -- Flag_N+1 : Boolean := False; -- when "others" present
1207 -- Pref_1 : ...;
1208 -- . . .
1209 -- Pref_M : ...;
1211 -- <preconditions (if any)>
1213 -- -- Evaluate all case guards
1215 -- if Case_Guard_1 then
1216 -- Flag_1 := True;
1217 -- Count := Count + 1;
1218 -- end if;
1219 -- . . .
1220 -- if Case_Guard_N then
1221 -- Flag_N := True;
1222 -- Count := Count + 1;
1223 -- end if;
1225 -- -- Emit errors depending on the number of case guards that
1226 -- -- evaluated to True.
1228 -- if Count = 0 then
1229 -- raise Assertion_Error with "xxx contract cases incomplete";
1230 -- <or>
1231 -- Flag_N+1 := True; -- when "others" present
1233 -- elsif Count > 1 then
1234 -- declare
1235 -- Str0 : constant String :=
1236 -- "contract cases overlap for subprogram ABC";
1237 -- Str1 : constant String :=
1238 -- (if Flag_1 then
1239 -- Str0 & "case guard at xxx evaluates to True"
1240 -- else Str0);
1241 -- StrN : constant String :=
1242 -- (if Flag_N then
1243 -- StrN-1 & "case guard at xxx evaluates to True"
1244 -- else StrN-1);
1245 -- begin
1246 -- raise Assertion_Error with StrN;
1247 -- end;
1248 -- end if;
1250 -- -- Evaluate all attribute 'Old prefixes found in the selected
1251 -- -- consequence.
1253 -- if Flag_1 then
1254 -- Pref_1 := <prefix of 'Old found in Consequence_1>
1255 -- . . .
1256 -- elsif Flag_N then
1257 -- Pref_M := <prefix of 'Old found in Consequence_N>
1258 -- end if;
1260 -- procedure _Postconditions is
1261 -- begin
1262 -- <postconditions (if any)>
1264 -- if Flag_1 and then not Consequence_1 then
1265 -- raise Assertion_Error with "failed contract case at xxx";
1266 -- end if;
1267 -- . . .
1268 -- if Flag_N[+1] and then not Consequence_N[+1] then
1269 -- raise Assertion_Error with "failed contract case at xxx";
1270 -- end if;
1271 -- end _Postconditions;
1272 -- begin
1273 -- . . .
1274 -- end S;
1276 procedure Expand_Pragma_Contract_Cases
1277 (CCs : Node_Id;
1278 Subp_Id : Entity_Id;
1279 Decls : List_Id;
1280 Stmts : in out List_Id)
1282 Loc : constant Source_Ptr := Sloc (CCs);
1284 procedure Case_Guard_Error
1285 (Decls : List_Id;
1286 Flag : Entity_Id;
1287 Error_Loc : Source_Ptr;
1288 Msg : in out Entity_Id);
1289 -- Given a declarative list Decls, status flag Flag, the location of the
1290 -- error and a string Msg, construct the following check:
1291 -- Msg : constant String :=
1292 -- (if Flag then
1293 -- Msg & "case guard at Error_Loc evaluates to True"
1294 -- else Msg);
1295 -- The resulting code is added to Decls
1297 procedure Consequence_Error
1298 (Checks : in out Node_Id;
1299 Flag : Entity_Id;
1300 Conseq : Node_Id);
1301 -- Given an if statement Checks, status flag Flag and a consequence
1302 -- Conseq, construct the following check:
1303 -- [els]if Flag and then not Conseq then
1304 -- raise Assertion_Error
1305 -- with "failed contract case at Sloc (Conseq)";
1306 -- [end if;]
1307 -- The resulting code is added to Checks
1309 function Declaration_Of (Id : Entity_Id) return Node_Id;
1310 -- Given the entity Id of a boolean flag, generate:
1311 -- Id : Boolean := False;
1313 procedure Expand_Attributes_In_Consequence
1314 (Decls : List_Id;
1315 Evals : in out Node_Id;
1316 Flag : Entity_Id;
1317 Conseq : Node_Id);
1318 -- Perform specialized expansion of all attribute 'Old references found
1319 -- in consequence Conseq such that at runtime only prefixes coming from
1320 -- the selected consequence are evaluated. Similarly expand attribute
1321 -- 'Result references by replacing them with identifier _result which
1322 -- resolves to the sole formal parameter of procedure _Postconditions.
1323 -- Any temporaries generated in the process are added to declarations
1324 -- Decls. Evals is a complex if statement tasked with the evaluation of
1325 -- all prefixes coming from a single selected consequence. Flag is the
1326 -- corresponding case guard flag. Conseq is the consequence expression.
1328 function Increment (Id : Entity_Id) return Node_Id;
1329 -- Given the entity Id of a numerical variable, generate:
1330 -- Id := Id + 1;
1332 function Set (Id : Entity_Id) return Node_Id;
1333 -- Given the entity Id of a boolean variable, generate:
1334 -- Id := True;
1336 ----------------------
1337 -- Case_Guard_Error --
1338 ----------------------
1340 procedure Case_Guard_Error
1341 (Decls : List_Id;
1342 Flag : Entity_Id;
1343 Error_Loc : Source_Ptr;
1344 Msg : in out Entity_Id)
1346 New_Line : constant Character := Character'Val (10);
1347 New_Msg : constant Entity_Id := Make_Temporary (Loc, 'S');
1349 begin
1350 Start_String;
1351 Store_String_Char (New_Line);
1352 Store_String_Chars (" case guard at ");
1353 Store_String_Chars (Build_Location_String (Error_Loc));
1354 Store_String_Chars (" evaluates to True");
1356 -- Generate:
1357 -- New_Msg : constant String :=
1358 -- (if Flag then
1359 -- Msg & "case guard at Error_Loc evaluates to True"
1360 -- else Msg);
1362 Append_To (Decls,
1363 Make_Object_Declaration (Loc,
1364 Defining_Identifier => New_Msg,
1365 Constant_Present => True,
1366 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1367 Expression =>
1368 Make_If_Expression (Loc,
1369 Expressions => New_List (
1370 New_Occurrence_Of (Flag, Loc),
1372 Make_Op_Concat (Loc,
1373 Left_Opnd => New_Occurrence_Of (Msg, Loc),
1374 Right_Opnd => Make_String_Literal (Loc, End_String)),
1376 New_Occurrence_Of (Msg, Loc)))));
1378 Msg := New_Msg;
1379 end Case_Guard_Error;
1381 -----------------------
1382 -- Consequence_Error --
1383 -----------------------
1385 procedure Consequence_Error
1386 (Checks : in out Node_Id;
1387 Flag : Entity_Id;
1388 Conseq : Node_Id)
1390 Cond : Node_Id;
1391 Error : Node_Id;
1393 begin
1394 -- Generate:
1395 -- Flag and then not Conseq
1397 Cond :=
1398 Make_And_Then (Loc,
1399 Left_Opnd => New_Occurrence_Of (Flag, Loc),
1400 Right_Opnd =>
1401 Make_Op_Not (Loc,
1402 Right_Opnd => Relocate_Node (Conseq)));
1404 -- Generate:
1405 -- raise Assertion_Error
1406 -- with "failed contract case at Sloc (Conseq)";
1408 Start_String;
1409 Store_String_Chars ("failed contract case at ");
1410 Store_String_Chars (Build_Location_String (Sloc (Conseq)));
1412 Error :=
1413 Make_Procedure_Call_Statement (Loc,
1414 Name =>
1415 New_Occurrence_Of (RTE (RE_Raise_Assert_Failure), Loc),
1416 Parameter_Associations => New_List (
1417 Make_String_Literal (Loc, End_String)));
1419 if No (Checks) then
1420 Checks :=
1421 Make_Implicit_If_Statement (CCs,
1422 Condition => Cond,
1423 Then_Statements => New_List (Error));
1425 else
1426 if No (Elsif_Parts (Checks)) then
1427 Set_Elsif_Parts (Checks, New_List);
1428 end if;
1430 Append_To (Elsif_Parts (Checks),
1431 Make_Elsif_Part (Loc,
1432 Condition => Cond,
1433 Then_Statements => New_List (Error)));
1434 end if;
1435 end Consequence_Error;
1437 --------------------
1438 -- Declaration_Of --
1439 --------------------
1441 function Declaration_Of (Id : Entity_Id) return Node_Id is
1442 begin
1443 return
1444 Make_Object_Declaration (Loc,
1445 Defining_Identifier => Id,
1446 Object_Definition => New_Occurrence_Of (Standard_Boolean, Loc),
1447 Expression => New_Occurrence_Of (Standard_False, Loc));
1448 end Declaration_Of;
1450 --------------------------------------
1451 -- Expand_Attributes_In_Consequence --
1452 --------------------------------------
1454 procedure Expand_Attributes_In_Consequence
1455 (Decls : List_Id;
1456 Evals : in out Node_Id;
1457 Flag : Entity_Id;
1458 Conseq : Node_Id)
1460 Eval_Stmts : List_Id := No_List;
1461 -- The evaluation sequence expressed as assignment statements of all
1462 -- prefixes of attribute 'Old found in the current consequence.
1464 function Expand_Attributes (N : Node_Id) return Traverse_Result;
1465 -- Determine whether an arbitrary node denotes attribute 'Old or
1466 -- 'Result and if it does, perform all expansion-related actions.
1468 -----------------------
1469 -- Expand_Attributes --
1470 -----------------------
1472 function Expand_Attributes (N : Node_Id) return Traverse_Result is
1473 Decl : Node_Id;
1474 Pref : Node_Id;
1475 Temp : Entity_Id;
1476 Indirect : Boolean := False;
1478 use Sem_Util.Old_Attr_Util.Indirect_Temps;
1480 procedure Append_For_Indirect_Temp
1481 (N : Node_Id; Is_Eval_Stmt : Boolean);
1483 -- Append either a declaration (which is to be elaborated
1484 -- unconditionally) or an evaluation statement (which is
1485 -- to be executed conditionally).
1487 -------------------------------
1488 -- Append_For_Indirect_Temp --
1489 -------------------------------
1491 procedure Append_For_Indirect_Temp
1492 (N : Node_Id; Is_Eval_Stmt : Boolean)
1494 begin
1495 if Is_Eval_Stmt then
1496 Append_To (Eval_Stmts, N);
1497 else
1498 Prepend_To (Decls, N);
1499 -- This use of Prepend (as opposed to Append) is why
1500 -- we have the Append_Decls_In_Reverse_Order parameter.
1501 end if;
1502 end Append_For_Indirect_Temp;
1504 procedure Declare_Indirect_Temporary is new
1505 Declare_Indirect_Temp (
1506 Append_Item => Append_For_Indirect_Temp,
1507 Append_Decls_In_Reverse_Order => True);
1509 -- Start of processing for Expand_Attributes
1511 begin
1512 -- Attribute 'Old
1514 if Nkind (N) = N_Attribute_Reference
1515 and then Attribute_Name (N) = Name_Old
1516 then
1517 Pref := Prefix (N);
1519 Indirect := Indirect_Temp_Needed (Etype (Pref));
1521 if Indirect then
1522 if No (Eval_Stmts) then
1523 Eval_Stmts := New_List;
1524 end if;
1526 Declare_Indirect_Temporary
1527 (Attr_Prefix => Pref,
1528 Indirect_Temp => Temp);
1530 -- Declare a temporary of the prefix type with no explicit
1531 -- initial value. If the appropriate contract case is selected
1532 -- at run time, then the temporary will be initialized via an
1533 -- assignment statement.
1535 else
1536 Temp := Make_Temporary (Loc, 'T', Pref);
1537 Set_Etype (Temp, Etype (Pref));
1539 -- Generate a temporary to capture the value of the prefix:
1540 -- Temp : <Pref type>;
1542 Decl :=
1543 Make_Object_Declaration (Loc,
1544 Defining_Identifier => Temp,
1545 Object_Definition =>
1546 New_Occurrence_Of (Etype (Pref), Loc));
1548 -- Place that temporary at the beginning of declarations, to
1549 -- prevent anomalies in the GNATprove flow-analysis pass in
1550 -- the precondition procedure that follows.
1552 Prepend_To (Decls, Decl);
1554 -- Initially Temp is uninitialized (which is required for
1555 -- correctness if default initialization might have side
1556 -- effects). Assign prefix value to temp on Eval_Statement
1557 -- list, so assignment will be executed conditionally.
1559 Set_Ekind (Temp, E_Variable);
1560 Set_Suppress_Initialization (Temp);
1561 Analyze (Decl);
1563 if No (Eval_Stmts) then
1564 Eval_Stmts := New_List;
1565 end if;
1567 Append_To (Eval_Stmts,
1568 Make_Assignment_Statement (Loc,
1569 Name => New_Occurrence_Of (Temp, Loc),
1570 Expression => Pref));
1571 end if;
1573 -- Ensure that the prefix is valid
1575 if Validity_Checks_On and then Validity_Check_Operands then
1576 Ensure_Valid (Pref);
1577 end if;
1579 -- Replace the original attribute 'Old by a reference to the
1580 -- generated temporary.
1582 if Indirect then
1583 Rewrite (N,
1584 Indirect_Temp_Value
1585 (Temp => Temp, Typ => Etype (Pref), Loc => Loc));
1586 else
1587 Rewrite (N, New_Occurrence_Of (Temp, Loc));
1588 end if;
1590 -- Attribute 'Result
1592 elsif Is_Attribute_Result (N) then
1593 Rewrite (N, Make_Identifier (Loc, Name_uResult));
1594 end if;
1596 return OK;
1597 end Expand_Attributes;
1599 procedure Expand_Attributes_In is
1600 new Traverse_Proc (Expand_Attributes);
1602 -- Start of processing for Expand_Attributes_In_Consequence
1604 begin
1605 -- Inspect the consequence and expand any attribute 'Old and 'Result
1606 -- references found within.
1608 Expand_Attributes_In (Conseq);
1610 -- The consequence does not contain any attribute 'Old references
1612 if No (Eval_Stmts) then
1613 return;
1614 end if;
1616 -- Augment the machinery to trigger the evaluation of all prefixes
1617 -- found in the step above. If Eval is empty, then this is the first
1618 -- consequence to yield expansion of 'Old. Generate:
1620 -- if Flag then
1621 -- <evaluation statements>
1622 -- end if;
1624 if No (Evals) then
1625 Evals :=
1626 Make_Implicit_If_Statement (CCs,
1627 Condition => New_Occurrence_Of (Flag, Loc),
1628 Then_Statements => Eval_Stmts);
1630 -- Otherwise generate:
1631 -- elsif Flag then
1632 -- <evaluation statements>
1633 -- end if;
1635 else
1636 if No (Elsif_Parts (Evals)) then
1637 Set_Elsif_Parts (Evals, New_List);
1638 end if;
1640 Append_To (Elsif_Parts (Evals),
1641 Make_Elsif_Part (Loc,
1642 Condition => New_Occurrence_Of (Flag, Loc),
1643 Then_Statements => Eval_Stmts));
1644 end if;
1645 end Expand_Attributes_In_Consequence;
1647 ---------------
1648 -- Increment --
1649 ---------------
1651 function Increment (Id : Entity_Id) return Node_Id is
1652 begin
1653 return
1654 Make_Assignment_Statement (Loc,
1655 Name => New_Occurrence_Of (Id, Loc),
1656 Expression =>
1657 Make_Op_Add (Loc,
1658 Left_Opnd => New_Occurrence_Of (Id, Loc),
1659 Right_Opnd => Make_Integer_Literal (Loc, 1)));
1660 end Increment;
1662 ---------
1663 -- Set --
1664 ---------
1666 function Set (Id : Entity_Id) return Node_Id is
1667 begin
1668 return
1669 Make_Assignment_Statement (Loc,
1670 Name => New_Occurrence_Of (Id, Loc),
1671 Expression => New_Occurrence_Of (Standard_True, Loc));
1672 end Set;
1674 -- Local variables
1676 Aggr : constant Node_Id :=
1677 Expression (First (Pragma_Argument_Associations (CCs)));
1679 Case_Guard : Node_Id;
1680 CG_Checks : Node_Id;
1681 CG_Stmts : List_Id;
1682 Conseq : Node_Id;
1683 Conseq_Checks : Node_Id := Empty;
1684 Count : Entity_Id;
1685 Count_Decl : Node_Id;
1686 Error_Decls : List_Id := No_List; -- init to avoid warning
1687 Flag : Entity_Id;
1688 Flag_Decl : Node_Id;
1689 If_Stmt : Node_Id;
1690 Msg_Str : Entity_Id := Empty;
1691 Multiple_PCs : Boolean;
1692 Old_Evals : Node_Id := Empty;
1693 Others_Decl : Node_Id;
1694 Others_Flag : Entity_Id := Empty;
1695 Post_Case : Node_Id;
1697 -- Start of processing for Expand_Pragma_Contract_Cases
1699 begin
1700 -- Do nothing if pragma is not enabled. If pragma is disabled, it has
1701 -- already been rewritten as a Null statement.
1703 if Is_Ignored (CCs) then
1704 return;
1706 -- Guard against malformed contract cases
1708 elsif Nkind (Aggr) /= N_Aggregate then
1709 return;
1710 end if;
1712 -- The expansion of contract cases is quite distributed as it produces
1713 -- various statements to evaluate the case guards and consequences. To
1714 -- preserve the original context, set the Is_Assertion_Expr flag. This
1715 -- aids the Ghost legality checks when verifying the placement of a
1716 -- reference to a Ghost entity.
1718 In_Assertion_Expr := In_Assertion_Expr + 1;
1720 Multiple_PCs := List_Length (Component_Associations (Aggr)) > 1;
1722 -- Create the counter which tracks the number of case guards that
1723 -- evaluate to True.
1725 -- Count : Natural := 0;
1727 Count := Make_Temporary (Loc, 'C');
1728 Count_Decl :=
1729 Make_Object_Declaration (Loc,
1730 Defining_Identifier => Count,
1731 Object_Definition => New_Occurrence_Of (Standard_Natural, Loc),
1732 Expression => Make_Integer_Literal (Loc, 0));
1734 Prepend_To (Decls, Count_Decl);
1735 Analyze (Count_Decl);
1737 -- Create the base error message for multiple overlapping case guards
1739 -- Msg_Str : constant String :=
1740 -- "contract cases overlap for subprogram Subp_Id";
1742 if Multiple_PCs then
1743 Msg_Str := Make_Temporary (Loc, 'S');
1745 Start_String;
1746 Store_String_Chars ("contract cases overlap for subprogram ");
1747 Store_String_Chars (Get_Name_String (Chars (Subp_Id)));
1749 Error_Decls := New_List (
1750 Make_Object_Declaration (Loc,
1751 Defining_Identifier => Msg_Str,
1752 Constant_Present => True,
1753 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1754 Expression => Make_String_Literal (Loc, End_String)));
1755 end if;
1757 -- Process individual post cases
1759 Post_Case := First (Component_Associations (Aggr));
1760 while Present (Post_Case) loop
1761 Case_Guard := First (Choices (Post_Case));
1762 Conseq := Expression (Post_Case);
1764 -- The "others" choice requires special processing
1766 if Nkind (Case_Guard) = N_Others_Choice then
1767 Others_Flag := Make_Temporary (Loc, 'F');
1768 Others_Decl := Declaration_Of (Others_Flag);
1770 Prepend_To (Decls, Others_Decl);
1771 Analyze (Others_Decl);
1773 -- Check possible overlap between a case guard and "others"
1775 if Multiple_PCs and Exception_Extra_Info then
1776 Case_Guard_Error
1777 (Decls => Error_Decls,
1778 Flag => Others_Flag,
1779 Error_Loc => Sloc (Case_Guard),
1780 Msg => Msg_Str);
1781 end if;
1783 -- Inspect the consequence and perform special expansion of any
1784 -- attribute 'Old and 'Result references found within.
1786 Expand_Attributes_In_Consequence
1787 (Decls => Decls,
1788 Evals => Old_Evals,
1789 Flag => Others_Flag,
1790 Conseq => Conseq);
1792 -- Check the corresponding consequence of "others"
1794 Consequence_Error
1795 (Checks => Conseq_Checks,
1796 Flag => Others_Flag,
1797 Conseq => Conseq);
1799 -- Regular post case
1801 else
1802 -- Create the flag which tracks the state of its associated case
1803 -- guard.
1805 Flag := Make_Temporary (Loc, 'F');
1806 Flag_Decl := Declaration_Of (Flag);
1808 Prepend_To (Decls, Flag_Decl);
1809 Analyze (Flag_Decl);
1811 -- The flag is set when the case guard is evaluated to True
1812 -- if Case_Guard then
1813 -- Flag := True;
1814 -- Count := Count + 1;
1815 -- end if;
1817 If_Stmt :=
1818 Make_Implicit_If_Statement (CCs,
1819 Condition => Relocate_Node (Case_Guard),
1820 Then_Statements => New_List (
1821 Set (Flag),
1822 Increment (Count)));
1824 Append_To (Decls, If_Stmt);
1825 Analyze (If_Stmt);
1827 -- Check whether this case guard overlaps with another one
1829 if Multiple_PCs and Exception_Extra_Info then
1830 Case_Guard_Error
1831 (Decls => Error_Decls,
1832 Flag => Flag,
1833 Error_Loc => Sloc (Case_Guard),
1834 Msg => Msg_Str);
1835 end if;
1837 -- Inspect the consequence and perform special expansion of any
1838 -- attribute 'Old and 'Result references found within.
1840 Expand_Attributes_In_Consequence
1841 (Decls => Decls,
1842 Evals => Old_Evals,
1843 Flag => Flag,
1844 Conseq => Conseq);
1846 -- The corresponding consequence of the case guard which evaluated
1847 -- to True must hold on exit from the subprogram.
1849 Consequence_Error
1850 (Checks => Conseq_Checks,
1851 Flag => Flag,
1852 Conseq => Conseq);
1853 end if;
1855 Next (Post_Case);
1856 end loop;
1858 -- Raise Assertion_Error when none of the case guards evaluate to True.
1859 -- The only exception is when we have "others", in which case there is
1860 -- no error because "others" acts as a default True.
1862 -- Generate:
1863 -- Flag := True;
1865 if Present (Others_Flag) then
1866 CG_Stmts := New_List (Set (Others_Flag));
1868 -- Generate:
1869 -- raise Assertion_Error with "xxx contract cases incomplete";
1871 else
1872 Start_String;
1873 Store_String_Chars (Build_Location_String (Loc));
1874 Store_String_Chars (" contract cases incomplete");
1876 CG_Stmts := New_List (
1877 Make_Procedure_Call_Statement (Loc,
1878 Name =>
1879 New_Occurrence_Of (RTE (RE_Raise_Assert_Failure), Loc),
1880 Parameter_Associations => New_List (
1881 Make_String_Literal (Loc, End_String))));
1882 end if;
1884 CG_Checks :=
1885 Make_Implicit_If_Statement (CCs,
1886 Condition =>
1887 Make_Op_Eq (Loc,
1888 Left_Opnd => New_Occurrence_Of (Count, Loc),
1889 Right_Opnd => Make_Integer_Literal (Loc, 0)),
1890 Then_Statements => CG_Stmts);
1892 -- Detect a possible failure due to several case guards evaluating to
1893 -- True.
1895 -- Generate:
1896 -- elsif Count > 0 then
1897 -- declare
1898 -- <Error_Decls>
1899 -- begin
1900 -- raise Assertion_Error with <Msg_Str>;
1901 -- end if;
1903 if Multiple_PCs then
1904 Set_Elsif_Parts (CG_Checks, New_List (
1905 Make_Elsif_Part (Loc,
1906 Condition =>
1907 Make_Op_Gt (Loc,
1908 Left_Opnd => New_Occurrence_Of (Count, Loc),
1909 Right_Opnd => Make_Integer_Literal (Loc, 1)),
1911 Then_Statements => New_List (
1912 Make_Block_Statement (Loc,
1913 Declarations => Error_Decls,
1914 Handled_Statement_Sequence =>
1915 Make_Handled_Sequence_Of_Statements (Loc,
1916 Statements => New_List (
1917 Make_Procedure_Call_Statement (Loc,
1918 Name =>
1919 New_Occurrence_Of
1920 (RTE (RE_Raise_Assert_Failure), Loc),
1921 Parameter_Associations => New_List (
1922 New_Occurrence_Of (Msg_Str, Loc))))))))));
1923 end if;
1925 Append_To (Decls, CG_Checks);
1926 Analyze (CG_Checks);
1928 -- Once all case guards are evaluated and checked, evaluate any prefixes
1929 -- of attribute 'Old founds in the selected consequence.
1931 if Present (Old_Evals) then
1932 Append_To (Decls, Old_Evals);
1933 Analyze (Old_Evals);
1934 end if;
1936 -- Raise Assertion_Error when the corresponding consequence of a case
1937 -- guard that evaluated to True fails.
1939 Append_New_To (Stmts, Conseq_Checks);
1941 In_Assertion_Expr := In_Assertion_Expr - 1;
1942 end Expand_Pragma_Contract_Cases;
1944 ---------------------------------------
1945 -- Expand_Pragma_Import_Or_Interface --
1946 ---------------------------------------
1948 procedure Expand_Pragma_Import_Or_Interface (N : Node_Id) is
1949 Def_Id : Entity_Id;
1951 begin
1952 -- In Relaxed_RM_Semantics, support old Ada 83 style:
1953 -- pragma Import (Entity, "external name");
1955 if Relaxed_RM_Semantics
1956 and then List_Length (Pragma_Argument_Associations (N)) = 2
1957 and then Pragma_Name (N) = Name_Import
1958 and then Nkind (Arg_N (N, 2)) = N_String_Literal
1959 then
1960 Def_Id := Entity (Arg_N (N, 1));
1961 else
1962 Def_Id := Entity (Arg_N (N, 2));
1963 end if;
1965 -- Variable case (we have to undo any initialization already done)
1967 if Ekind (Def_Id) = E_Variable then
1968 Undo_Initialization (Def_Id, N);
1970 -- Case of exception with convention C++
1972 elsif Ekind (Def_Id) = E_Exception
1973 and then Convention (Def_Id) = Convention_CPP
1974 then
1975 -- Import a C++ convention
1977 declare
1978 Loc : constant Source_Ptr := Sloc (N);
1979 Rtti_Name : constant Node_Id := Arg_N (N, 3);
1980 Dum : constant Entity_Id := Make_Temporary (Loc, 'D');
1981 Exdata : List_Id;
1982 Lang_Char : Node_Id;
1983 Foreign_Data : Node_Id;
1985 begin
1986 Exdata := Component_Associations (Expression (Parent (Def_Id)));
1988 Lang_Char := Next (First (Exdata));
1990 -- Change the one-character language designator to 'C'
1992 Rewrite (Expression (Lang_Char),
1993 Make_Character_Literal (Loc,
1994 Chars => Name_uC,
1995 Char_Literal_Value => UI_From_Int (Character'Pos ('C'))));
1996 Analyze (Expression (Lang_Char));
1998 -- Change the value of Foreign_Data
2000 Foreign_Data := Next (Next (Next (Next (Lang_Char))));
2002 Insert_Actions (Def_Id, New_List (
2003 Make_Object_Declaration (Loc,
2004 Defining_Identifier => Dum,
2005 Object_Definition =>
2006 New_Occurrence_Of (Standard_Character, Loc)),
2008 Make_Pragma (Loc,
2009 Chars => Name_Import,
2010 Pragma_Argument_Associations => New_List (
2011 Make_Pragma_Argument_Association (Loc,
2012 Expression => Make_Identifier (Loc, Name_Ada)),
2014 Make_Pragma_Argument_Association (Loc,
2015 Expression => Make_Identifier (Loc, Chars (Dum))),
2017 Make_Pragma_Argument_Association (Loc,
2018 Chars => Name_External_Name,
2019 Expression => Relocate_Node (Rtti_Name))))));
2021 Rewrite (Expression (Foreign_Data),
2022 Unchecked_Convert_To (Standard_A_Char,
2023 Make_Attribute_Reference (Loc,
2024 Prefix => Make_Identifier (Loc, Chars (Dum)),
2025 Attribute_Name => Name_Address)));
2026 Analyze (Expression (Foreign_Data));
2027 end;
2029 -- No special expansion required for any other case
2031 else
2032 null;
2033 end if;
2034 end Expand_Pragma_Import_Or_Interface;
2036 -------------------------------------
2037 -- Expand_Pragma_Initial_Condition --
2038 -------------------------------------
2040 procedure Expand_Pragma_Initial_Condition
2041 (Pack_Id : Entity_Id;
2042 N : Node_Id)
2044 procedure Extract_Package_Body_Lists
2045 (Pack_Body : Node_Id;
2046 Body_List : out List_Id;
2047 Call_List : out List_Id;
2048 Spec_List : out List_Id);
2049 -- Obtain the various declarative and statement lists of package body
2050 -- Pack_Body needed to insert the initial condition procedure and the
2051 -- call to it. The lists are as follows:
2053 -- * Body_List - used to insert the initial condition procedure body
2055 -- * Call_List - used to insert the call to the initial condition
2056 -- procedure.
2058 -- * Spec_List - used to insert the initial condition procedure spec
2060 procedure Extract_Package_Declaration_Lists
2061 (Pack_Decl : Node_Id;
2062 Body_List : out List_Id;
2063 Call_List : out List_Id;
2064 Spec_List : out List_Id);
2065 -- Obtain the various declarative lists of package declaration Pack_Decl
2066 -- needed to insert the initial condition procedure and the call to it.
2067 -- The lists are as follows:
2069 -- * Body_List - used to insert the initial condition procedure body
2071 -- * Call_List - used to insert the call to the initial condition
2072 -- procedure.
2074 -- * Spec_List - used to insert the initial condition procedure spec
2076 --------------------------------
2077 -- Extract_Package_Body_Lists --
2078 --------------------------------
2080 procedure Extract_Package_Body_Lists
2081 (Pack_Body : Node_Id;
2082 Body_List : out List_Id;
2083 Call_List : out List_Id;
2084 Spec_List : out List_Id)
2086 Pack_Spec : constant Entity_Id := Corresponding_Spec (Pack_Body);
2088 Dummy_1 : List_Id;
2089 Dummy_2 : List_Id;
2090 HSS : Node_Id;
2092 begin
2093 pragma Assert (Present (Pack_Spec));
2095 -- The different parts of the invariant procedure are inserted as
2096 -- follows:
2098 -- package Pack is package body Pack is
2099 -- <IC spec> <IC body>
2100 -- private begin
2101 -- ... <IC call>
2102 -- end Pack; end Pack;
2104 -- The initial condition procedure spec is inserted in the visible
2105 -- declaration of the corresponding package spec.
2107 Extract_Package_Declaration_Lists
2108 (Pack_Decl => Unit_Declaration_Node (Pack_Spec),
2109 Body_List => Dummy_1,
2110 Call_List => Dummy_2,
2111 Spec_List => Spec_List);
2113 -- The initial condition procedure body is added to the declarations
2114 -- of the package body.
2116 Body_List := Declarations (Pack_Body);
2118 if No (Body_List) then
2119 Body_List := New_List;
2120 Set_Declarations (Pack_Body, Body_List);
2121 end if;
2123 -- The call to the initial condition procedure is inserted in the
2124 -- statements of the package body.
2126 HSS := Handled_Statement_Sequence (Pack_Body);
2128 if No (HSS) then
2129 HSS :=
2130 Make_Handled_Sequence_Of_Statements (Sloc (Pack_Body),
2131 Statements => New_List);
2132 Set_Handled_Statement_Sequence (Pack_Body, HSS);
2133 end if;
2135 Call_List := Statements (HSS);
2136 end Extract_Package_Body_Lists;
2138 ---------------------------------------
2139 -- Extract_Package_Declaration_Lists --
2140 ---------------------------------------
2142 procedure Extract_Package_Declaration_Lists
2143 (Pack_Decl : Node_Id;
2144 Body_List : out List_Id;
2145 Call_List : out List_Id;
2146 Spec_List : out List_Id)
2148 Pack_Spec : constant Node_Id := Specification (Pack_Decl);
2150 begin
2151 -- The different parts of the invariant procedure are inserted as
2152 -- follows:
2154 -- package Pack is
2155 -- <IC spec>
2156 -- <IC body>
2157 -- private
2158 -- <IC call>
2159 -- end Pack;
2161 -- The initial condition procedure spec and body are inserted in the
2162 -- visible declarations of the package spec.
2164 Body_List := Visible_Declarations (Pack_Spec);
2166 if No (Body_List) then
2167 Body_List := New_List;
2168 Set_Visible_Declarations (Pack_Spec, Body_List);
2169 end if;
2171 Spec_List := Body_List;
2173 -- The call to the initial procedure is inserted in the private
2174 -- declarations of the package spec.
2176 Call_List := Private_Declarations (Pack_Spec);
2178 if No (Call_List) then
2179 Call_List := New_List;
2180 Set_Private_Declarations (Pack_Spec, Call_List);
2181 end if;
2182 end Extract_Package_Declaration_Lists;
2184 -- Local variables
2186 IC_Prag : constant Node_Id :=
2187 Get_Pragma (Pack_Id, Pragma_Initial_Condition);
2189 Body_List : List_Id;
2190 Call : Node_Id;
2191 Call_List : List_Id;
2192 Call_Loc : Source_Ptr;
2193 Expr : Node_Id;
2194 Loc : Source_Ptr;
2195 Proc_Body : Node_Id;
2196 Proc_Body_Id : Entity_Id;
2197 Proc_Decl : Node_Id;
2198 Proc_Id : Entity_Id;
2199 Spec_List : List_Id;
2201 -- Start of processing for Expand_Pragma_Initial_Condition
2203 begin
2204 -- Nothing to do when the package is not subject to an Initial_Condition
2205 -- pragma.
2207 if No (IC_Prag) then
2208 return;
2209 end if;
2211 Expr := Get_Pragma_Arg (First (Pragma_Argument_Associations (IC_Prag)));
2212 Loc := Sloc (IC_Prag);
2214 -- Nothing to do when the pragma is ignored because its semantics are
2215 -- suppressed.
2217 if Is_Ignored (IC_Prag) then
2218 return;
2220 -- Nothing to do when the pragma or its argument are illegal because
2221 -- there is no valid expression to check.
2223 elsif Error_Posted (IC_Prag) or else Error_Posted (Expr) then
2224 return;
2225 end if;
2227 -- Obtain the various lists of the context where the individual pieces
2228 -- of the initial condition procedure are to be inserted.
2230 if Nkind (N) = N_Package_Body then
2231 Extract_Package_Body_Lists
2232 (Pack_Body => N,
2233 Body_List => Body_List,
2234 Call_List => Call_List,
2235 Spec_List => Spec_List);
2237 elsif Nkind (N) = N_Package_Declaration then
2238 Extract_Package_Declaration_Lists
2239 (Pack_Decl => N,
2240 Body_List => Body_List,
2241 Call_List => Call_List,
2242 Spec_List => Spec_List);
2244 -- This routine should not be used on anything other than packages
2246 else
2247 pragma Assert (False);
2248 return;
2249 end if;
2251 Proc_Id :=
2252 Make_Defining_Identifier (Loc,
2253 Chars => New_External_Name (Chars (Pack_Id), "Initial_Condition"));
2255 Set_Ekind (Proc_Id, E_Procedure);
2256 Set_Is_Initial_Condition_Procedure (Proc_Id);
2258 -- Generate:
2259 -- procedure <Pack_Id>Initial_Condition;
2261 Proc_Decl :=
2262 Make_Subprogram_Declaration (Loc,
2263 Make_Procedure_Specification (Loc,
2264 Defining_Unit_Name => Proc_Id));
2266 Append_To (Spec_List, Proc_Decl);
2268 -- The initial condition procedure requires debug info when initial
2269 -- condition is subject to Source Coverage Obligations.
2271 if Generate_SCO then
2272 Set_Debug_Info_Needed (Proc_Id);
2273 end if;
2275 -- Generate:
2276 -- procedure <Pack_Id>Initial_Condition is
2277 -- begin
2278 -- pragma Check (Initial_Condition, <Expr>);
2279 -- end <Pack_Id>Initial_Condition;
2281 Proc_Body :=
2282 Make_Subprogram_Body (Loc,
2283 Specification =>
2284 Copy_Subprogram_Spec (Specification (Proc_Decl)),
2285 Declarations => Empty_List,
2286 Handled_Statement_Sequence =>
2287 Make_Handled_Sequence_Of_Statements (Loc,
2288 Statements => New_List (
2289 Make_Pragma (Loc,
2290 Chars => Name_Check,
2291 Pragma_Argument_Associations => New_List (
2292 Make_Pragma_Argument_Association (Loc,
2293 Expression =>
2294 Make_Identifier (Loc, Name_Initial_Condition)),
2295 Make_Pragma_Argument_Association (Loc,
2296 Expression => New_Copy_Tree (Expr)))))));
2298 Append_To (Body_List, Proc_Body);
2300 -- The initial condition procedure requires debug info when initial
2301 -- condition is subject to Source Coverage Obligations.
2303 Proc_Body_Id := Defining_Entity (Proc_Body);
2305 if Generate_SCO then
2306 Set_Debug_Info_Needed (Proc_Body_Id);
2307 end if;
2309 -- The location of the initial condition procedure call must be as close
2310 -- as possible to the intended semantic location of the check because
2311 -- the ABE mechanism relies heavily on accurate locations.
2313 Call_Loc := End_Keyword_Location (N);
2315 -- Generate:
2316 -- <Pack_Id>Initial_Condition;
2318 Call :=
2319 Make_Procedure_Call_Statement (Call_Loc,
2320 Name => New_Occurrence_Of (Proc_Id, Call_Loc));
2322 Append_To (Call_List, Call);
2324 Analyze (Proc_Decl);
2325 Analyze (Proc_Body);
2326 Analyze (Call);
2327 end Expand_Pragma_Initial_Condition;
2329 ------------------------------------
2330 -- Expand_Pragma_Inspection_Point --
2331 ------------------------------------
2333 -- If no argument is given, then we supply a default argument list that
2334 -- includes all objects declared at the source level in all subprograms
2335 -- that enclose the inspection point pragma.
2337 procedure Expand_Pragma_Inspection_Point (N : Node_Id) is
2338 Loc : constant Source_Ptr := Sloc (N);
2339 A : List_Id;
2340 Assoc : Node_Id;
2341 S : Entity_Id;
2342 E : Entity_Id;
2344 begin
2345 if No (Pragma_Argument_Associations (N)) then
2346 A := New_List;
2347 S := Current_Scope;
2349 while S /= Standard_Standard loop
2350 E := First_Entity (S);
2351 while Present (E) loop
2352 if Comes_From_Source (E)
2353 and then Is_Object (E)
2354 and then not Is_Entry_Formal (E)
2355 and then Ekind (E) /= E_Component
2356 and then Ekind (E) /= E_Discriminant
2357 and then Ekind (E) /= E_Generic_In_Parameter
2358 and then Ekind (E) /= E_Generic_In_Out_Parameter
2359 then
2360 Append_To (A,
2361 Make_Pragma_Argument_Association (Loc,
2362 Expression => New_Occurrence_Of (E, Loc)));
2363 end if;
2365 Next_Entity (E);
2366 end loop;
2368 S := Scope (S);
2369 end loop;
2371 Set_Pragma_Argument_Associations (N, A);
2372 end if;
2374 -- Expand the arguments of the pragma. Expanding an entity reference
2375 -- is a noop, except in a protected operation, where a reference may
2376 -- have to be transformed into a reference to the corresponding prival.
2377 -- Are there other pragmas that may require this ???
2379 Assoc := First (Pragma_Argument_Associations (N));
2380 while Present (Assoc) loop
2381 Expand (Expression (Assoc));
2382 Next (Assoc);
2383 end loop;
2384 end Expand_Pragma_Inspection_Point;
2386 --------------------------------------
2387 -- Expand_Pragma_Interrupt_Priority --
2388 --------------------------------------
2390 -- Supply default argument if none exists (System.Interrupt_Priority'Last)
2392 procedure Expand_Pragma_Interrupt_Priority (N : Node_Id) is
2393 Loc : constant Source_Ptr := Sloc (N);
2394 begin
2395 if No (Pragma_Argument_Associations (N)) then
2396 Set_Pragma_Argument_Associations (N, New_List (
2397 Make_Pragma_Argument_Association (Loc,
2398 Expression =>
2399 Make_Attribute_Reference (Loc,
2400 Prefix =>
2401 New_Occurrence_Of (RTE (RE_Interrupt_Priority), Loc),
2402 Attribute_Name => Name_Last))));
2403 end if;
2404 end Expand_Pragma_Interrupt_Priority;
2406 --------------------------------
2407 -- Expand_Pragma_Loop_Variant --
2408 --------------------------------
2410 -- Pragma Loop_Variant is expanded in the following manner:
2412 -- Original code
2414 -- for | while ... loop
2415 -- <preceding source statements>
2416 -- pragma Loop_Variant
2417 -- (Increases => Incr_Expr,
2418 -- Decreases => Decr_Expr);
2419 -- <succeeding source statements>
2420 -- end loop;
2422 -- Expanded code
2424 -- Curr_1 : <type of Incr_Expr>;
2425 -- Curr_2 : <type of Decr_Expr>;
2426 -- Old_1 : <type of Incr_Expr>;
2427 -- Old_2 : <type of Decr_Expr>;
2428 -- Flag : Boolean := False;
2430 -- for | while ... loop
2431 -- <preceding source statements>
2433 -- if Flag then
2434 -- Old_1 := Curr_1;
2435 -- Old_2 := Curr_2;
2436 -- end if;
2438 -- Curr_1 := <Incr_Expr>;
2439 -- Curr_2 := <Decr_Expr>;
2441 -- if Flag then
2442 -- if Curr_1 /= Old_1 then
2443 -- pragma Check (Loop_Variant, Curr_1 > Old_1);
2444 -- else
2445 -- pragma Check (Loop_Variant, Curr_2 < Old_2);
2446 -- end if;
2447 -- else
2448 -- Flag := True;
2449 -- end if;
2451 -- <succeeding source statements>
2452 -- end loop;
2454 procedure Expand_Pragma_Loop_Variant (N : Node_Id) is
2455 Loc : constant Source_Ptr := Sloc (N);
2456 Last_Var : constant Node_Id :=
2457 Last (Pragma_Argument_Associations (N));
2459 Curr_Assign : List_Id := No_List;
2460 Flag_Id : Entity_Id := Empty;
2461 If_Stmt : Node_Id := Empty;
2462 Old_Assign : List_Id := No_List;
2463 Loop_Scop : Entity_Id;
2464 Loop_Stmt : Node_Id;
2465 Variant : Node_Id;
2467 procedure Process_Variant (Variant : Node_Id; Is_Last : Boolean);
2468 -- Process a single increasing / decreasing termination variant. Flag
2469 -- Is_Last should be set when processing the last variant.
2471 ---------------------
2472 -- Process_Variant --
2473 ---------------------
2475 procedure Process_Variant (Variant : Node_Id; Is_Last : Boolean) is
2476 Expr : constant Node_Id := Expression (Variant);
2477 Expr_Typ : constant Entity_Id := Etype (Expr);
2478 Loc : constant Source_Ptr := Sloc (Expr);
2479 Loop_Loc : constant Source_Ptr := Sloc (Loop_Stmt);
2480 Curr_Id : Entity_Id;
2481 Old_Id : Entity_Id;
2482 Prag : Node_Id;
2484 begin
2485 -- All temporaries generated in this routine must be inserted before
2486 -- the related loop statement. Ensure that the proper scope is on the
2487 -- stack when analyzing the temporaries. Note that we also use the
2488 -- Sloc of the related loop.
2490 Push_Scope (Scope (Loop_Scop));
2492 -- Step 1: Create the declaration of the flag which controls the
2493 -- behavior of the assertion on the first iteration of the loop.
2495 if No (Flag_Id) then
2497 -- Generate:
2498 -- Flag : Boolean := False;
2500 Flag_Id := Make_Temporary (Loop_Loc, 'F');
2502 Insert_Action (Loop_Stmt,
2503 Make_Object_Declaration (Loop_Loc,
2504 Defining_Identifier => Flag_Id,
2505 Object_Definition =>
2506 New_Occurrence_Of (Standard_Boolean, Loop_Loc),
2507 Expression =>
2508 New_Occurrence_Of (Standard_False, Loop_Loc)));
2510 -- Prevent an unwanted optimization where the Current_Value of
2511 -- the flag eliminates the if statement which stores the variant
2512 -- values coming from the previous iteration.
2514 -- Flag : Boolean := False;
2515 -- loop
2516 -- if Flag then -- condition rewritten to False
2517 -- Old_N := Curr_N; -- and if statement eliminated
2518 -- end if;
2519 -- . . .
2520 -- Flag := True;
2521 -- end loop;
2523 Set_Current_Value (Flag_Id, Empty);
2524 end if;
2526 -- Step 2: Create the temporaries which store the old and current
2527 -- values of the associated expression.
2529 -- Generate:
2530 -- Curr : <type of Expr>;
2532 Curr_Id := Make_Temporary (Loc, 'C');
2534 Insert_Action (Loop_Stmt,
2535 Make_Object_Declaration (Loop_Loc,
2536 Defining_Identifier => Curr_Id,
2537 Object_Definition => New_Occurrence_Of (Expr_Typ, Loop_Loc)));
2539 -- Generate:
2540 -- Old : <type of Expr>;
2542 Old_Id := Make_Temporary (Loc, 'P');
2544 Insert_Action (Loop_Stmt,
2545 Make_Object_Declaration (Loop_Loc,
2546 Defining_Identifier => Old_Id,
2547 Object_Definition => New_Occurrence_Of (Expr_Typ, Loop_Loc)));
2549 -- Restore original scope after all temporaries have been analyzed
2551 Pop_Scope;
2553 -- Step 3: Store value of the expression from the previous iteration
2555 -- Generate:
2556 -- Old := Curr;
2558 Append_New_To (Old_Assign,
2559 Make_Assignment_Statement (Loc,
2560 Name => New_Occurrence_Of (Old_Id, Loc),
2561 Expression => New_Occurrence_Of (Curr_Id, Loc)));
2563 -- Step 4: Store the current value of the expression
2565 -- Generate:
2566 -- Curr := <Expr>;
2568 Append_New_To (Curr_Assign,
2569 Make_Assignment_Statement (Loc,
2570 Name => New_Occurrence_Of (Curr_Id, Loc),
2571 Expression => Relocate_Node (Expr)));
2573 -- Step 5: Create corresponding assertion to verify change of value
2575 -- Generate:
2576 -- pragma Check (Loop_Variant, Curr <|> Old);
2578 Prag :=
2579 Make_Pragma (Loc,
2580 Chars => Name_Check,
2581 Pragma_Argument_Associations => New_List (
2582 Make_Pragma_Argument_Association (Loc,
2583 Expression => Make_Identifier (Loc, Name_Loop_Variant)),
2584 Make_Pragma_Argument_Association (Loc,
2585 Expression =>
2586 Make_Variant_Comparison (Loc,
2587 Mode => Chars (Variant),
2588 Curr_Val => New_Occurrence_Of (Curr_Id, Loc),
2589 Old_Val => New_Occurrence_Of (Old_Id, Loc)))));
2591 -- Generate:
2592 -- if Curr /= Old then
2593 -- <Prag>;
2595 if No (If_Stmt) then
2597 -- When there is just one termination variant, do not compare the
2598 -- old and current value for equality, just check the pragma.
2600 if Is_Last then
2601 If_Stmt := Prag;
2602 else
2603 If_Stmt :=
2604 Make_If_Statement (Loc,
2605 Condition =>
2606 Make_Op_Ne (Loc,
2607 Left_Opnd => New_Occurrence_Of (Curr_Id, Loc),
2608 Right_Opnd => New_Occurrence_Of (Old_Id, Loc)),
2609 Then_Statements => New_List (Prag));
2610 end if;
2612 -- Generate:
2613 -- else
2614 -- <Prag>;
2615 -- end if;
2617 elsif Is_Last then
2618 Set_Else_Statements (If_Stmt, New_List (Prag));
2620 -- Generate:
2621 -- elsif Curr /= Old then
2622 -- <Prag>;
2624 else
2625 if Elsif_Parts (If_Stmt) = No_List then
2626 Set_Elsif_Parts (If_Stmt, New_List);
2627 end if;
2629 Append_To (Elsif_Parts (If_Stmt),
2630 Make_Elsif_Part (Loc,
2631 Condition =>
2632 Make_Op_Ne (Loc,
2633 Left_Opnd => New_Occurrence_Of (Curr_Id, Loc),
2634 Right_Opnd => New_Occurrence_Of (Old_Id, Loc)),
2635 Then_Statements => New_List (Prag)));
2636 end if;
2637 end Process_Variant;
2639 -- Start of processing for Expand_Pragma_Loop_Variant
2641 begin
2642 -- If pragma is not enabled, rewrite as Null statement. If pragma is
2643 -- disabled, it has already been rewritten as a Null statement.
2645 if Is_Ignored (N) then
2646 Rewrite (N, Make_Null_Statement (Loc));
2647 Analyze (N);
2648 return;
2649 end if;
2651 -- The expansion of Loop_Variant is quite distributed as it produces
2652 -- various statements to capture and compare the arguments. To preserve
2653 -- the original context, set the Is_Assertion_Expr flag. This aids the
2654 -- Ghost legality checks when verifying the placement of a reference to
2655 -- a Ghost entity.
2657 In_Assertion_Expr := In_Assertion_Expr + 1;
2659 -- Locate the enclosing loop for which this assertion applies. In the
2660 -- case of Ada 2012 array iteration, we might be dealing with nested
2661 -- loops. Only the outermost loop has an identifier.
2663 Loop_Stmt := N;
2664 while Present (Loop_Stmt) loop
2665 if Nkind (Loop_Stmt) = N_Loop_Statement
2666 and then Present (Identifier (Loop_Stmt))
2667 then
2668 exit;
2669 end if;
2671 Loop_Stmt := Parent (Loop_Stmt);
2672 end loop;
2674 Loop_Scop := Entity (Identifier (Loop_Stmt));
2676 -- Create the circuitry which verifies individual variants
2678 Variant := First (Pragma_Argument_Associations (N));
2679 while Present (Variant) loop
2680 Process_Variant (Variant, Is_Last => Variant = Last_Var);
2681 Next (Variant);
2682 end loop;
2684 -- Construct the segment which stores the old values of all expressions.
2685 -- Generate:
2686 -- if Flag then
2687 -- <Old_Assign>
2688 -- end if;
2690 Insert_Action (N,
2691 Make_If_Statement (Loc,
2692 Condition => New_Occurrence_Of (Flag_Id, Loc),
2693 Then_Statements => Old_Assign));
2695 -- Update the values of all expressions
2697 Insert_Actions (N, Curr_Assign);
2699 -- Add the assertion circuitry to test all changes in expressions.
2700 -- Generate:
2701 -- if Flag then
2702 -- <If_Stmt>
2703 -- else
2704 -- Flag := True;
2705 -- end if;
2707 Insert_Action (N,
2708 Make_If_Statement (Loc,
2709 Condition => New_Occurrence_Of (Flag_Id, Loc),
2710 Then_Statements => New_List (If_Stmt),
2711 Else_Statements => New_List (
2712 Make_Assignment_Statement (Loc,
2713 Name => New_Occurrence_Of (Flag_Id, Loc),
2714 Expression => New_Occurrence_Of (Standard_True, Loc)))));
2716 -- Note: the pragma has been completely transformed into a sequence of
2717 -- corresponding declarations and statements. We leave it in the tree
2718 -- for documentation purposes. It will be ignored by the backend.
2720 In_Assertion_Expr := In_Assertion_Expr - 1;
2721 end Expand_Pragma_Loop_Variant;
2723 --------------------------------
2724 -- Expand_Pragma_Psect_Object --
2725 --------------------------------
2727 -- Convert to Common_Object, and expand the resulting pragma
2729 procedure Expand_Pragma_Psect_Object (N : Node_Id)
2730 renames Expand_Pragma_Common_Object;
2732 -------------------------------------
2733 -- Expand_Pragma_Relative_Deadline --
2734 -------------------------------------
2736 procedure Expand_Pragma_Relative_Deadline (N : Node_Id) is
2737 P : constant Node_Id := Parent (N);
2738 Loc : constant Source_Ptr := Sloc (N);
2740 begin
2741 -- Expand the pragma only in the case of the main subprogram. For tasks
2742 -- the expansion is done in exp_ch9. Generate a call to Set_Deadline
2743 -- at Clock plus the relative deadline specified in the pragma. Time
2744 -- values are translated into Duration to allow for non-private
2745 -- addition operation.
2747 if Nkind (P) = N_Subprogram_Body then
2748 Rewrite
2750 Make_Procedure_Call_Statement (Loc,
2751 Name => New_Occurrence_Of (RTE (RE_Set_Deadline), Loc),
2752 Parameter_Associations => New_List (
2753 Unchecked_Convert_To (RTE (RO_RT_Time),
2754 Make_Op_Add (Loc,
2755 Left_Opnd =>
2756 Make_Function_Call (Loc,
2757 New_Occurrence_Of (RTE (RO_RT_To_Duration), Loc),
2758 New_List
2759 (Make_Function_Call
2760 (Loc, New_Occurrence_Of (RTE (RE_Clock), Loc)))),
2761 Right_Opnd =>
2762 Unchecked_Convert_To (
2763 Standard_Duration,
2764 Arg_N (N, 1)))))));
2766 Analyze (N);
2767 end if;
2768 end Expand_Pragma_Relative_Deadline;
2770 --------------------------------------
2771 -- Expand_Pragma_Subprogram_Variant --
2772 --------------------------------------
2774 -- Aspect Subprogram_Variant is expanded in the following manner:
2776 -- Original code
2778 -- procedure Proc (Param : T) with
2779 -- with Variant (Increases => Incr_Expr,
2780 -- Decreases => Decr_Expr)
2781 -- <declarations>
2782 -- is
2783 -- <source statements>
2784 -- Proc (New_Param_Value);
2785 -- end Proc;
2787 -- Expanded code
2789 -- procedure Proc (Param : T) is
2790 -- Old_Incr : constant <type of Incr_Expr> := <Incr_Expr>;
2791 -- Old_Decr : constant <type of Decr_Expr> := <Decr_Expr> ;
2793 -- procedure Variants (Param : T);
2795 -- procedure Variants (Param : T) is
2796 -- Curr_Incr : constant <type of Incr_Expr> := <Incr_Expr>;
2797 -- Curr_Decr : constant <type of Decr_Expr> := <Decr_Expr>;
2798 -- begin
2799 -- if Curr_Incr /= Old_Incr then
2800 -- pragma Check (Variant, Curr_Incr > Old_Incr);
2801 -- else
2802 -- pragma Check (Variant, Curr_Decr < Old_Decr);
2803 -- end if;
2804 -- end Variants;
2806 -- <declarations>
2807 -- begin
2808 -- <source statements>
2809 -- Variants (New_Param_Value);
2810 -- Proc (New_Param_Value);
2811 -- end Proc;
2813 procedure Expand_Pragma_Subprogram_Variant
2814 (Prag : Node_Id;
2815 Subp_Id : Node_Id;
2816 Body_Decls : List_Id)
2818 Curr_Decls : List_Id;
2819 If_Stmt : Node_Id := Empty;
2821 function Formal_Param_Map
2822 (Old_Subp : Entity_Id;
2823 New_Subp : Entity_Id) return Elist_Id;
2824 -- Given two subprogram entities Old_Subp and New_Subp with the same
2825 -- number of formal parameters return a list of the form:
2827 -- old formal 1
2828 -- new formal 1
2829 -- old formal 2
2830 -- new formal 2
2831 -- ...
2833 -- as required by New_Copy_Tree to replace references to formal
2834 -- parameters of Old_Subp with references to formal parameters of
2835 -- New_Subp.
2837 procedure Process_Variant
2838 (Variant : Node_Id;
2839 Formal_Map : Elist_Id;
2840 Prev_Decl : in out Node_Id;
2841 Is_Last : Boolean);
2842 -- Process a single increasing / decreasing termination variant given by
2843 -- a component association Variant. Formal_Map is a list of formal
2844 -- parameters of the annotated subprogram and of the internal procedure
2845 -- that verifies the variant in the format required by New_Copy_Tree.
2846 -- The Old_... object created by this routine will be appended after
2847 -- Prev_Decl and is stored in this parameter for a next call to this
2848 -- routine. Is_Last is True when there are no more variants to process.
2850 ----------------------
2851 -- Formal_Param_Map --
2852 ----------------------
2854 function Formal_Param_Map
2855 (Old_Subp : Entity_Id;
2856 New_Subp : Entity_Id) return Elist_Id
2858 Old_Formal : Entity_Id := First_Formal (Old_Subp);
2859 New_Formal : Entity_Id := First_Formal (New_Subp);
2861 Param_Map : Elist_Id;
2862 begin
2863 if Present (Old_Formal) then
2864 Param_Map := New_Elmt_List;
2865 while Present (Old_Formal) and then Present (New_Formal) loop
2866 Append_Elmt (Old_Formal, Param_Map);
2867 Append_Elmt (New_Formal, Param_Map);
2869 Next_Formal (Old_Formal);
2870 Next_Formal (New_Formal);
2871 end loop;
2873 return Param_Map;
2874 else
2875 return No_Elist;
2876 end if;
2877 end Formal_Param_Map;
2879 ---------------------
2880 -- Process_Variant --
2881 ---------------------
2883 procedure Process_Variant
2884 (Variant : Node_Id;
2885 Formal_Map : Elist_Id;
2886 Prev_Decl : in out Node_Id;
2887 Is_Last : Boolean)
2889 Expr : constant Node_Id := Expression (Variant);
2890 Expr_Typ : constant Entity_Id := Etype (Expr);
2891 Loc : constant Source_Ptr := Sloc (Expr);
2893 Old_Id : Entity_Id;
2894 Old_Decl : Node_Id;
2895 Curr_Id : Entity_Id;
2896 Curr_Decl : Node_Id;
2897 Prag : Node_Id;
2899 begin
2900 -- Create temporaries that store the old values of the associated
2901 -- expression.
2903 -- Generate:
2904 -- Old : constant <type of Expr> := <Expr>;
2906 Old_Id := Make_Temporary (Loc, 'P');
2908 Old_Decl :=
2909 Make_Object_Declaration (Loc,
2910 Defining_Identifier => Old_Id,
2911 Constant_Present => True,
2912 Object_Definition => New_Occurrence_Of (Expr_Typ, Loc),
2913 Expression => New_Copy_Tree (Expr));
2915 Insert_After_And_Analyze (Prev_Decl, Old_Decl);
2917 Prev_Decl := Old_Decl;
2919 -- Generate:
2920 -- Curr : constant <type of Expr> := <Expr>;
2922 Curr_Id := Make_Temporary (Loc, 'C');
2924 Curr_Decl :=
2925 Make_Object_Declaration (Loc,
2926 Defining_Identifier => Curr_Id,
2927 Constant_Present => True,
2928 Object_Definition => New_Occurrence_Of (Expr_Typ, Loc),
2929 Expression =>
2930 New_Copy_Tree (Expr, Map => Formal_Map));
2932 Append (Curr_Decl, Curr_Decls);
2934 -- Generate:
2935 -- pragma Check (Variant, Curr <|> Old);
2937 Prag :=
2938 Make_Pragma (Loc,
2939 Chars => Name_Check,
2940 Pragma_Argument_Associations => New_List (
2941 Make_Pragma_Argument_Association (Loc,
2942 Expression =>
2943 Make_Identifier (Loc,
2944 Name_Subprogram_Variant)),
2945 Make_Pragma_Argument_Association (Loc,
2946 Expression =>
2947 Make_Variant_Comparison (Loc,
2948 Mode => Chars (First (Choices (Variant))),
2949 Curr_Val => New_Occurrence_Of (Curr_Id, Loc),
2950 Old_Val => New_Occurrence_Of (Old_Id, Loc)))));
2952 -- Generate:
2953 -- if Curr /= Old then
2954 -- <Prag>;
2956 if No (If_Stmt) then
2958 -- When there is just one termination variant, do not compare
2959 -- the old and current value for equality, just check the
2960 -- pragma.
2962 if Is_Last then
2963 If_Stmt := Prag;
2964 else
2965 If_Stmt :=
2966 Make_If_Statement (Loc,
2967 Condition =>
2968 Make_Op_Ne (Loc,
2969 Left_Opnd => New_Occurrence_Of (Curr_Id, Loc),
2970 Right_Opnd => New_Occurrence_Of (Old_Id, Loc)),
2971 Then_Statements => New_List (Prag));
2972 end if;
2974 -- Generate:
2975 -- else
2976 -- <Prag>;
2977 -- end if;
2979 elsif Is_Last then
2980 Set_Else_Statements (If_Stmt, New_List (Prag));
2982 -- Generate:
2983 -- elsif Curr /= Old then
2984 -- <Prag>;
2986 else
2987 if Elsif_Parts (If_Stmt) = No_List then
2988 Set_Elsif_Parts (If_Stmt, New_List);
2989 end if;
2991 Append_To (Elsif_Parts (If_Stmt),
2992 Make_Elsif_Part (Loc,
2993 Condition =>
2994 Make_Op_Ne (Loc,
2995 Left_Opnd => New_Occurrence_Of (Curr_Id, Loc),
2996 Right_Opnd => New_Occurrence_Of (Old_Id, Loc)),
2997 Then_Statements => New_List (Prag)));
2998 end if;
2999 end Process_Variant;
3001 -- Local variables
3003 Loc : constant Source_Ptr := Sloc (Prag);
3005 Aggr : Node_Id;
3006 Formal_Map : Elist_Id;
3007 Last : Node_Id;
3008 Last_Variant : Node_Id;
3009 Proc_Bod : Node_Id;
3010 Proc_Decl : Node_Id;
3011 Proc_Id : Entity_Id;
3012 Proc_Spec : Node_Id;
3013 Variant : Node_Id;
3015 begin
3016 -- Do nothing if pragma is not present or is disabled
3018 if Is_Ignored (Prag) then
3019 return;
3020 end if;
3022 Aggr := Expression (First (Pragma_Argument_Associations (Prag)));
3024 -- The expansion of Subprogram Variant is quite distributed as it
3025 -- produces various statements to capture and compare the arguments.
3026 -- To preserve the original context, set the Is_Assertion_Expr flag.
3027 -- This aids the Ghost legality checks when verifying the placement
3028 -- of a reference to a Ghost entity.
3030 In_Assertion_Expr := In_Assertion_Expr + 1;
3032 -- Create declaration of the procedure that compares values of the
3033 -- variant expressions captured at the start of subprogram with their
3034 -- values at the recursive call of the subprogram.
3036 Proc_Id := Make_Defining_Identifier (Loc, Name_uVariants);
3038 Proc_Spec :=
3039 Make_Procedure_Specification
3040 (Loc,
3041 Defining_Unit_Name => Proc_Id,
3042 Parameter_Specifications => Copy_Parameter_List (Subp_Id));
3044 Proc_Decl :=
3045 Make_Subprogram_Declaration (Loc, Proc_Spec);
3047 Insert_Before_First_Source_Declaration (Proc_Decl, Body_Decls);
3048 Analyze (Proc_Decl);
3050 -- Create a mapping between formals of the annotated subprogram (which
3051 -- are used to compute values of the variant expression at the start of
3052 -- subprogram) and formals of the internal procedure (which are used to
3053 -- compute values of of the variant expression at the recursive call).
3055 Formal_Map :=
3056 Formal_Param_Map (Old_Subp => Subp_Id, New_Subp => Proc_Id);
3058 -- Process invidual increasing / decreasing variants
3060 Last := Proc_Decl;
3061 Curr_Decls := New_List;
3062 Last_Variant := Nlists.Last (Component_Associations (Aggr));
3064 Variant := First (Component_Associations (Aggr));
3065 while Present (Variant) loop
3066 Process_Variant
3067 (Variant => Variant,
3068 Formal_Map => Formal_Map,
3069 Prev_Decl => Last,
3070 Is_Last => Variant = Last_Variant);
3071 Next (Variant);
3072 end loop;
3074 -- Create a subprogram body with declarations of objects that capture
3075 -- the current values of variant expressions at a recursive call and an
3076 -- if-then-else statement that compares current with old values.
3078 Proc_Bod :=
3079 Make_Subprogram_Body (Loc,
3080 Specification =>
3081 Copy_Subprogram_Spec (Proc_Spec),
3082 Declarations => Curr_Decls,
3083 Handled_Statement_Sequence =>
3084 Make_Handled_Sequence_Of_Statements (Loc,
3085 Statements => New_List (If_Stmt),
3086 End_Label => Make_Identifier (Loc, Chars (Proc_Id))));
3088 Insert_After_And_Analyze (Last, Proc_Bod);
3090 -- Restore assertion context
3092 In_Assertion_Expr := In_Assertion_Expr - 1;
3094 -- Rewrite the aspect expression, which is no longer needed, with
3095 -- a reference to the procedure that has just been created. We will
3096 -- generate a call to this procedure at each recursive call of the
3097 -- subprogram that has been annotated with Subprogram_Variant.
3099 Rewrite (Aggr, New_Occurrence_Of (Proc_Id, Loc));
3100 end Expand_Pragma_Subprogram_Variant;
3102 -------------------------------------------
3103 -- Expand_Pragma_Suppress_Initialization --
3104 -------------------------------------------
3106 procedure Expand_Pragma_Suppress_Initialization (N : Node_Id) is
3107 Def_Id : constant Entity_Id := Entity (Arg_N (N, 1));
3109 begin
3110 -- Variable case (we have to undo any initialization already done)
3112 if Ekind (Def_Id) = E_Variable then
3113 Undo_Initialization (Def_Id, N);
3114 end if;
3115 end Expand_Pragma_Suppress_Initialization;
3117 -------------------------
3118 -- Undo_Initialization --
3119 -------------------------
3121 procedure Undo_Initialization (Def_Id : Entity_Id; N : Node_Id) is
3122 Init_Call : Node_Id;
3124 begin
3125 -- When applied to a variable, the default initialization must not be
3126 -- done. As it is already done when the pragma is found, we just get rid
3127 -- of the call the initialization procedure which followed the object
3128 -- declaration. The call is inserted after the declaration, but validity
3129 -- checks may also have been inserted and thus the initialization call
3130 -- does not necessarily appear immediately after the object declaration.
3132 -- We can't use the freezing mechanism for this purpose, since we have
3133 -- to elaborate the initialization expression when it is first seen (so
3134 -- this elaboration cannot be deferred to the freeze point).
3136 -- Find and remove generated initialization call for object, if any
3138 Init_Call := Remove_Init_Call (Def_Id, Rep_Clause => N);
3140 -- Any default initialization expression should be removed (e.g.
3141 -- null defaults for access objects, zero initialization of packed
3142 -- bit arrays). Imported objects aren't allowed to have explicit
3143 -- initialization, so the expression must have been generated by
3144 -- the compiler.
3146 if No (Init_Call) and then Present (Expression (Parent (Def_Id))) then
3147 Set_Expression (Parent (Def_Id), Empty);
3148 end if;
3150 -- The object may not have any initialization, but in the presence of
3151 -- Initialize_Scalars code is inserted after then declaration, which
3152 -- must now be removed as well. The code carries the same source
3153 -- location as the declaration itself.
3155 if Initialize_Scalars and then Is_Array_Type (Etype (Def_Id)) then
3156 declare
3157 Init : Node_Id;
3158 Nxt : Node_Id;
3159 begin
3160 Init := Next (Parent (Def_Id));
3161 while not Comes_From_Source (Init)
3162 and then Sloc (Init) = Sloc (Def_Id)
3163 loop
3164 Nxt := Next (Init);
3165 Remove (Init);
3166 Init := Nxt;
3167 end loop;
3168 end;
3169 end if;
3170 end Undo_Initialization;
3172 end Exp_Prag;