1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2023, Free Software Foundation, Inc. --
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. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
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 Einfo
.Entities
; use Einfo
.Entities
;
32 with Einfo
.Utils
; use Einfo
.Utils
;
33 with Elists
; use Elists
;
34 with Errout
; use Errout
;
35 with Exp_Ch11
; use Exp_Ch11
;
36 with Exp_Util
; use Exp_Util
;
37 with Inline
; use Inline
;
39 with Namet
; use Namet
;
40 with Nlists
; use Nlists
;
41 with Nmake
; use Nmake
;
43 with Restrict
; use Restrict
;
44 with Rident
; use Rident
;
45 with Rtsfind
; use Rtsfind
;
47 with Sem_Aux
; use Sem_Aux
;
48 with Sem_Ch8
; use Sem_Ch8
;
49 with Sem_Prag
; use Sem_Prag
;
50 with Sem_Util
; use Sem_Util
;
51 with Sinfo
; use Sinfo
;
52 with Sinfo
.Nodes
; use Sinfo
.Nodes
;
53 with Sinfo
.Utils
; use Sinfo
.Utils
;
54 with Sinput
; use Sinput
;
55 with Snames
; use Snames
;
56 with Stringt
; use Stringt
;
57 with Stand
; use Stand
;
58 with Tbuild
; use Tbuild
;
59 with Uintp
; use Uintp
;
60 with Validsw
; use Validsw
;
61 with Warnsw
; use Warnsw
;
63 package body Exp_Prag
is
65 -----------------------
66 -- Local Subprograms --
67 -----------------------
69 function Arg_N
(N
: Node_Id
; Arg_Number
: Positive) return Node_Id
;
70 -- Obtain specified pragma argument expression
72 procedure Expand_Pragma_Abort_Defer
(N
: Node_Id
);
73 procedure Expand_Pragma_Check
(N
: Node_Id
);
74 procedure Expand_Pragma_Common_Object
(N
: Node_Id
);
75 procedure Expand_Pragma_CUDA_Execute
(N
: Node_Id
);
76 procedure Expand_Pragma_Import_Or_Interface
(N
: Node_Id
);
77 procedure Expand_Pragma_Inspection_Point
(N
: Node_Id
);
78 procedure Expand_Pragma_Interrupt_Priority
(N
: Node_Id
);
79 procedure Expand_Pragma_Loop_Variant
(N
: Node_Id
);
80 procedure Expand_Pragma_Psect_Object
(N
: Node_Id
);
81 procedure Expand_Pragma_Relative_Deadline
(N
: Node_Id
);
82 procedure Expand_Pragma_Suppress_Initialization
(N
: Node_Id
);
84 procedure Undo_Initialization
(Def_Id
: Entity_Id
; N
: Node_Id
);
85 -- This procedure is used to undo initialization already done for Def_Id,
86 -- which is always an E_Variable, in response to the occurrence of the
87 -- pragma N, a pragma Interface, Import, or Suppress_Initialization. In all
88 -- these cases we want no initialization to occur, but we have already done
89 -- the initialization by the time we see the pragma, so we have to undo it.
95 function Arg_N
(N
: Node_Id
; Arg_Number
: Positive) return Node_Id
is
96 Arg
: Node_Id
:= First
(Pragma_Argument_Associations
(N
));
102 for J
in 2 .. Arg_Number
loop
109 if Present
(Arg
) then
110 return Get_Pragma_Arg
(Arg
);
116 ---------------------
117 -- Expand_N_Pragma --
118 ---------------------
120 procedure Expand_N_Pragma
(N
: Node_Id
) is
121 Pname
: constant Name_Id
:= Pragma_Name
(N
);
122 Prag_Id
: constant Pragma_Id
:= Get_Pragma_Id
(Pname
);
125 -- Suppress the expansion of an ignored assertion pragma. Such a pragma
126 -- should not be transformed into a null statement because:
128 -- * The pragma may be part of the rep item chain of a type, in which
129 -- case rewriting it will destroy the chain.
131 -- * The analysis of the pragma may involve two parts (see routines
132 -- Analyze_xxx_In_Decl_Part). The second part of the analysis will
133 -- not happen if the pragma is rewritten.
135 if Assertion_Expression_Pragma
(Prag_Id
) and then Is_Ignored
(N
) then
138 -- Rewrite the pragma into a null statement when it is ignored using
139 -- pragma Ignore_Pragma, or denotes Default_Scalar_Storage_Order and
140 -- compilation switch -gnatI is in effect.
142 elsif Should_Ignore_Pragma_Sem
(N
)
143 or else (Prag_Id
= Pragma_Default_Scalar_Storage_Order
144 and then Ignore_Rep_Clauses
)
146 Rewrite
(N
, Make_Null_Statement
(Sloc
(N
)));
152 -- Pragmas requiring special expander action
154 when Pragma_Abort_Defer
=>
155 Expand_Pragma_Abort_Defer
(N
);
158 Expand_Pragma_Check
(N
);
160 when Pragma_Common_Object
=>
161 Expand_Pragma_Common_Object
(N
);
163 when Pragma_CUDA_Execute
=>
164 Expand_Pragma_CUDA_Execute
(N
);
166 when Pragma_Import
=>
167 Expand_Pragma_Import_Or_Interface
(N
);
169 when Pragma_Inspection_Point
=>
170 Expand_Pragma_Inspection_Point
(N
);
172 when Pragma_Interface
=>
173 Expand_Pragma_Import_Or_Interface
(N
);
175 when Pragma_Interrupt_Priority
=>
176 Expand_Pragma_Interrupt_Priority
(N
);
178 when Pragma_Loop_Variant
=>
179 Expand_Pragma_Loop_Variant
(N
);
181 when Pragma_Psect_Object
=>
182 Expand_Pragma_Psect_Object
(N
);
184 when Pragma_Relative_Deadline
=>
185 Expand_Pragma_Relative_Deadline
(N
);
187 when Pragma_Suppress_Initialization
=>
188 Expand_Pragma_Suppress_Initialization
(N
);
190 -- All other pragmas need no expander action (includes
197 -------------------------------
198 -- Expand_Pragma_Abort_Defer --
199 -------------------------------
201 -- An Abort_Defer pragma appears as the first statement in a handled
202 -- statement sequence (right after the begin). It defers aborts for
203 -- the entire statement sequence, but not for any declarations or
204 -- handlers (if any) associated with this statement sequence.
206 -- The transformation is to transform
208 -- pragma Abort_Defer;
217 -- when all others =>
218 -- Abort_Undefer.all;
221 -- Abort_Undefer_Direct;
224 procedure Expand_Pragma_Abort_Defer
(N
: Node_Id
) is
226 -- Abort_Defer has no useful effect if Abort's are not allowed
228 if not Abort_Allowed
then
232 -- Normal case where abort is possible
235 Loc
: constant Source_Ptr
:= Sloc
(N
);
239 Blk
: constant Entity_Id
:=
240 New_Internal_Entity
(E_Block
, Current_Scope
, Sloc
(N
), 'B');
241 AUD
: constant Entity_Id
:= RTE
(RE_Abort_Undefer_Direct
);
244 Stms
:= New_List
(Build_Runtime_Call
(Loc
, RE_Abort_Defer
));
246 Stm
:= Remove_Next
(N
);
252 Make_Handled_Sequence_Of_Statements
(Loc
,
254 At_End_Proc
=> New_Occurrence_Of
(AUD
, Loc
));
256 -- Present the Abort_Undefer_Direct function to the backend so that
257 -- it can inline the call to the function.
259 Add_Inlined_Body
(AUD
, N
);
262 Make_Block_Statement
(Loc
, Handled_Statement_Sequence
=> HSS
));
264 Set_Scope
(Blk
, Current_Scope
);
265 Set_Etype
(Blk
, Standard_Void_Type
);
266 Set_Identifier
(N
, New_Occurrence_Of
(Blk
, Sloc
(N
)));
267 Expand_At_End_Handler
(HSS
, Blk
);
270 end Expand_Pragma_Abort_Defer
;
272 -------------------------------------
273 -- Expand_Pragma_Always_Terminates --
274 -------------------------------------
276 procedure Expand_Pragma_Always_Terminates
(Prag
: Node_Id
) is
277 pragma Unreferenced
(Prag
);
280 end Expand_Pragma_Always_Terminates
;
282 --------------------------
283 -- Expand_Pragma_Check --
284 --------------------------
286 procedure Expand_Pragma_Check
(N
: Node_Id
) is
287 Cond
: constant Node_Id
:= Arg_N
(N
, 2);
288 Nam
: constant Name_Id
:= Chars
(Arg_N
(N
, 1));
291 Loc
: constant Source_Ptr
:= Sloc
(First_Node
(Cond
));
292 -- Source location used in the case of a failed assertion: point to the
293 -- failing condition, not Loc. Note that the source location of the
294 -- expression is not usually the best choice here, because it points to
295 -- the location of the topmost tree node, which may be an operator in
296 -- the middle of the source text of the expression. For example, it gets
297 -- located on the last AND keyword in a chain of boolean expressions
298 -- AND'ed together. It is best to put the message on the first character
299 -- of the condition, which is the effect of the First_Node call here.
300 -- This source location is used to build the default exception message,
301 -- and also as the sloc of the call to the runtime subprogram raising
302 -- Assert_Failure, so that coverage analysis tools can relate the
303 -- call to the failed check.
305 procedure Replace_Discriminals_Of_Protected_Op
(Expr
: Node_Id
);
306 -- Discriminants of the enclosing protected object may be referenced
307 -- in the expression of a precondition of a protected operation.
308 -- In the body of the operation these references must be replaced by
309 -- the discriminal created for them, which are renamings of the
310 -- discriminants of the object that is the target of the operation.
311 -- This replacement is done by visibility when the references appear
312 -- in the subprogram body, but in the case of a condition which appears
313 -- on the specification of the subprogram it has be done separately
314 -- because the condition has been replaced by a Check pragma and
315 -- analyzed earlier, before the creation of the discriminal renaming
316 -- declarations that are added to the subprogram body.
318 ------------------------------------------
319 -- Replace_Discriminals_Of_Protected_Op --
320 ------------------------------------------
322 procedure Replace_Discriminals_Of_Protected_Op
(Expr
: Node_Id
) is
323 function Find_Corresponding_Discriminal
324 (E
: Entity_Id
) return Entity_Id
;
325 -- Find the local entity that renames a discriminant of the enclosing
326 -- protected type, and has a matching name.
328 function Replace_Discr_Ref
(N
: Node_Id
) return Traverse_Result
;
329 -- Replace a reference to a discriminant of the original protected
330 -- type by the local renaming declaration of the discriminant of
331 -- the target object.
333 ------------------------------------
334 -- Find_Corresponding_Discriminal --
335 ------------------------------------
337 function Find_Corresponding_Discriminal
338 (E
: Entity_Id
) return Entity_Id
343 R
:= First_Entity
(Current_Scope
);
345 while Present
(R
) loop
346 if Nkind
(Parent
(R
)) = N_Object_Renaming_Declaration
347 and then Present
(Discriminal_Link
(R
))
348 and then Chars
(Discriminal_Link
(R
)) = Chars
(E
)
357 end Find_Corresponding_Discriminal
;
359 -----------------------
360 -- Replace_Discr_Ref --
361 -----------------------
363 function Replace_Discr_Ref
(N
: Node_Id
) return Traverse_Result
is
367 if Is_Entity_Name
(N
)
368 and then Present
(Discriminal_Link
(Entity
(N
)))
370 R
:= Find_Corresponding_Discriminal
(Entity
(N
));
371 Rewrite
(N
, New_Occurrence_Of
(R
, Sloc
(N
)));
375 end Replace_Discr_Ref
;
377 procedure Replace_Discriminant_References
is
378 new Traverse_Proc
(Replace_Discr_Ref
);
380 -- Start of processing for Replace_Discriminals_Of_Protected_Op
383 Replace_Discriminant_References
(Expr
);
384 end Replace_Discriminals_Of_Protected_Op
;
386 -- Start of processing for Expand_Pragma_Check
389 -- Nothing to do if pragma is ignored
391 if Is_Ignored
(N
) then
395 -- Since this check is active, rewrite the pragma into a corresponding
396 -- if statement, and then analyze the statement.
398 -- The normal case expansion transforms:
400 -- pragma Check (name, condition [,message]);
404 -- if not condition then
405 -- System.Assertions.Raise_Assert_Failure (Str);
408 -- where Str is the message if one is present, or the default of
409 -- name failed at file:line if no message is given (the "name failed
410 -- at" is omitted for name = Assertion, since it is redundant, given
411 -- that the name of the exception is Assert_Failure.)
413 -- Also, instead of "XXX failed at", we generate slightly
414 -- different messages for some of the contract assertions (see
415 -- code below for details).
417 -- An alternative expansion is used when the No_Exception_Propagation
418 -- restriction is active and there is a local Assert_Failure handler.
419 -- This is not a common combination of circumstances, but it occurs in
420 -- the context of Aunit and the zero footprint profile. In this case we
423 -- if not condition then
424 -- raise Assert_Failure;
427 -- This will then be transformed into a goto, and the local handler will
428 -- be able to handle the assert error (which would not be the case if a
429 -- call is made to the Raise_Assert_Failure procedure).
431 -- We also generate the direct raise if the Suppress_Exception_Locations
432 -- is active, since we don't want to generate messages in this case.
434 -- Note that the reason we do not always generate a direct raise is that
435 -- the form in which the procedure is called allows for more efficient
436 -- breakpointing of assertion errors.
438 -- Generate the appropriate if statement. Note that we consider this to
439 -- be an explicit conditional in the source, not an implicit if, so we
440 -- do not call Make_Implicit_If_Statement. Note also that we wrap the
441 -- raise statement in a block statement so that, if the condition is
442 -- evaluated at compile time to False, then the rewriting of the if
443 -- statement will not involve the raise but the block statement, and
444 -- thus not leave a dangling reference to the raise statement in the
445 -- Local_Raise_Statements list of the handler.
447 -- Case where we generate a direct raise
449 if ((Debug_Flag_Dot_G
450 or else Restriction_Active
(No_Exception_Propagation
))
451 and then Present
(Find_Local_Handler
(RTE
(RE_Assert_Failure
), N
)))
452 or else (Opt
.Exception_Locations_Suppressed
and then No
(Arg_N
(N
, 3)))
455 Make_If_Statement
(Loc
,
456 Condition
=> Make_Op_Not
(Loc
, Right_Opnd
=> Cond
),
457 Then_Statements
=> New_List
(
458 Make_Block_Statement
(Loc
,
459 Handled_Statement_Sequence
=>
460 Make_Handled_Sequence_Of_Statements
(Loc
,
461 Statements
=> New_List
(
462 Make_Raise_Statement
(Loc
,
464 New_Occurrence_Of
(RTE
(RE_Assert_Failure
),
467 Set_Comes_From_Check_Or_Contract
(N
);
469 -- Case where we call the procedure
472 -- If we have a message given, use it
474 if Present
(Arg_N
(N
, 3)) then
475 Msg
:= Get_Pragma_Arg
(Arg_N
(N
, 3));
477 -- Here we have no string, so prepare one
481 Loc_Str
: constant String := Build_Location_String
(Loc
);
486 -- For Assert, we just use the location
488 if Nam
= Name_Assert
then
491 -- For predicate, we generate the string "predicate failed at
492 -- yyy". We prefer all lower case for predicate.
494 elsif Nam
= Name_Predicate
then
495 Add_Str_To_Name_Buffer
("predicate failed at ");
497 -- For special case of Precondition/Postcondition the string is
498 -- "failed xx from yy" where xx is precondition/postcondition
499 -- in all lower case. The reason for this different wording is
500 -- that the failure is not at the point of occurrence of the
501 -- pragma, unlike the other Check cases.
503 elsif Nam
in Name_Precondition | Name_Postcondition
then
504 Get_Name_String
(Nam
);
505 Insert_Str_In_Name_Buffer
("failed ", 1);
506 Add_Str_To_Name_Buffer
(" from ");
508 -- For special case of Invariant, the string is "failed
509 -- invariant from yy", to be consistent with the string that is
510 -- generated for the aspect case (the code later on checks for
511 -- this specific string to modify it in some cases, so this is
512 -- functionally important).
514 elsif Nam
= Name_Invariant
then
515 Add_Str_To_Name_Buffer
("failed invariant from ");
517 -- For all other checks, the string is "xxx failed at yyy"
518 -- where xxx is the check name with appropriate casing.
521 Get_Name_String
(Nam
);
523 (Identifier_Casing
(Source_Index
(Current_Sem_Unit
)));
524 Add_Str_To_Name_Buffer
(" failed at ");
527 -- In all cases, add location string
529 Add_Str_To_Name_Buffer
(Loc_Str
);
533 Msg
:= Make_String_Literal
(Loc
, Name_Buffer
(1 .. Name_Len
));
537 -- For a precondition, replace references to discriminants of a
538 -- protected type with the local discriminals.
540 if Is_Protected_Type
(Scope
(Current_Scope
))
541 and then Has_Discriminants
(Scope
(Current_Scope
))
542 and then From_Aspect_Specification
(N
)
544 Replace_Discriminals_Of_Protected_Op
(Cond
);
547 -- Now rewrite as an if statement
550 Make_If_Statement
(Loc
,
551 Condition
=> Make_Op_Not
(Loc
, Right_Opnd
=> Cond
),
552 Then_Statements
=> New_List
(
553 Make_Procedure_Call_Statement
(Loc
,
555 New_Occurrence_Of
(RTE
(RE_Raise_Assert_Failure
), Loc
),
556 Parameter_Associations
=> New_List
(Relocate_Node
(Msg
))))));
558 Set_Comes_From_Check_Or_Contract
(N
);
563 -- If new condition is always false, give a warning
565 if Warn_On_Assertion_Failure
566 and then Nkind
(N
) = N_Procedure_Call_Statement
567 and then Is_RTE
(Entity
(Name
(N
)), RE_Raise_Assert_Failure
)
569 -- If original condition was a Standard.False, we assume that this is
570 -- indeed intended to raise assert error and no warning is required.
572 if Is_Entity_Name
(Original_Node
(Cond
))
573 and then Entity
(Original_Node
(Cond
)) = Standard_False
577 -- For Subprogram_Variant suppress the warning altogether, because
578 -- for mutually recursive subprograms with multiple variant clauses
579 -- some of the clauses might have expressions that are only meant for
580 -- verification and would always fail when executed.
582 elsif Nam
= Name_Subprogram_Variant
then
584 elsif Nam
= Name_Assert
then
585 Error_Msg_N
("?.a?assertion will fail at run time", N
);
587 Error_Msg_N
("?.a?check will fail at run time", N
);
590 end Expand_Pragma_Check
;
592 ---------------------------------
593 -- Expand_Pragma_Common_Object --
594 ---------------------------------
596 -- Use a machine attribute to replicate semantic effect in DEC Ada
598 -- pragma Machine_Attribute (intern_name, "common_object", extern_name);
600 -- For now we do nothing with the size attribute ???
602 -- Note: Psect_Object shares this processing
604 procedure Expand_Pragma_Common_Object
(N
: Node_Id
) is
605 Loc
: constant Source_Ptr
:= Sloc
(N
);
607 Internal
: constant Node_Id
:= Arg_N
(N
, 1);
608 External
: constant Node_Id
:= Arg_N
(N
, 2);
611 -- Psect value upper cased as string literal
613 Iloc
: constant Source_Ptr
:= Sloc
(Internal
);
614 Eloc
: constant Source_Ptr
:= Sloc
(External
);
618 -- Acquire Psect value and fold to upper case
620 if Present
(External
) then
621 if Nkind
(External
) = N_String_Literal
then
622 String_To_Name_Buffer
(Strval
(External
));
624 Get_Name_String
(Chars
(External
));
627 Set_Casing
(All_Upper_Case
);
630 Make_String_Literal
(Eloc
, Strval
=> String_From_Name_Buffer
);
633 Get_Name_String
(Chars
(Internal
));
634 Set_Casing
(All_Upper_Case
);
636 Make_String_Literal
(Iloc
, Strval
=> String_From_Name_Buffer
);
639 Ploc
:= Sloc
(Psect
);
643 Insert_After_And_Analyze
(N
,
645 Chars
=> Name_Machine_Attribute
,
646 Pragma_Argument_Associations
=> New_List
(
647 Make_Pragma_Argument_Association
(Iloc
,
648 Expression
=> New_Copy_Tree
(Internal
)),
649 Make_Pragma_Argument_Association
(Eloc
,
651 Make_String_Literal
(Sloc
=> Ploc
, Strval
=> "common_object")),
652 Make_Pragma_Argument_Association
(Ploc
,
653 Expression
=> New_Copy_Tree
(Psect
)))));
654 end Expand_Pragma_Common_Object
;
656 --------------------------------
657 -- Expand_Pragma_CUDA_Execute --
658 --------------------------------
660 -- Pragma CUDA_Execute is expanded in the following manner:
664 -- pragma CUDA_Execute (My_Proc (X, Y), Blocks, Grids, Mem, Stream)
669 -- Blocks_Id : CUDA.Vector_Types.Dim3 := Blocks;
670 -- Grids_Id : CUDA.Vector_Types.Dim3 := Grids;
671 -- Mem_Id : Integer := <Mem or 0>;
672 -- Stream_Id : CUDA.Driver_Types.Stream_T := <Stream or null>;
673 -- X_Id : <Type of X> := X;
674 -- Y_Id : <Type of Y> := Y;
675 -- Arg_Id : Array (1..2) of System.Address :=
676 -- (X'Address,_Id Y'Address);_Id
678 -- CUDA.Internal.Push_Call_Configuration (
683 -- CUDA.Internal.Pop_Call_Configuration (
685 -- Blocks_Id'address,
687 -- Stream_Id'address),
688 -- CUDA.Internal.Launch_Kernel (
697 procedure Expand_Pragma_CUDA_Execute
(N
: Node_Id
) is
699 Loc
: constant Source_Ptr
:= Sloc
(N
);
701 procedure Append_Copies
705 -- For each parameter in list Params, create an object declaration of
706 -- the following form:
708 -- Copy_Id : Param_Typ := Param_Val;
710 -- Param_Typ is the type of the parameter. Param_Val is the initial
711 -- value of the parameter. The declarations are stored in Decls, the
712 -- entities of the new objects are collected in list Copies.
714 function Build_Dim3_Declaration
715 (Decl_Id
: Entity_Id
;
716 Init_Val
: Node_Id
) return Node_Id
;
717 -- Build an object declaration of the form
719 -- Decl_Id : CUDA.Internal.Dim3 := Val;
721 -- Val depends on the nature of Init_Val, as follows:
723 -- * If Init_Val is of type CUDA.Vector_Types.Dim3, then Val has the
726 -- (Interfaces.C.Unsigned (Val.X),
727 -- Interfaces.C.Unsigned (Val.Y),
728 -- Interfaces.C.Unsigned (Val.Z))
730 -- * If Init_Val is a single Integer, Val has the following form:
732 -- (Interfaces.C.Unsigned (Init_Val),
733 -- Interfaces.C.Unsigned (1),
734 -- Interfaces.C.Unsigned (1))
736 -- * If Init_Val is an aggregate of three values, Val has the
739 -- (Interfaces.C.Unsigned (Val_1),
740 -- Interfaces.C.Unsigned (Val_2),
741 -- Interfaces.C.Unsigned (Val_3))
743 function Build_Kernel_Args_Declaration
744 (Kernel_Arg
: Entity_Id
;
745 Var_Ids
: Elist_Id
) return Node_Id
;
746 -- Given a list of variables, return an object declaration of the
749 -- Kernel_Arg : ... := (Var_1'Address, ..., Var_N'Address);
751 function Build_Launch_Kernel_Call
753 Grid_Dims
: Entity_Id
;
754 Block_Dims
: Entity_Id
;
755 Kernel_Arg
: Entity_Id
;
757 Stream
: Entity_Id
) return Node_Id
;
758 -- Builds and returns a call to CUDA.Internal.Launch_Kernel using the
759 -- given arguments. Proc is the entity of the procedure passed to the
760 -- CUDA_Execute pragma. Grid_Dims and Block_Dims are entities of the
761 -- generated declarations that hold the kernel's dimensions. Args is the
762 -- entity of the temporary array that holds the arguments of the kernel.
763 -- Memory and Stream are the entities of the temporaries that hold the
764 -- fourth and fith arguments of CUDA_Execute or their default values.
766 function Build_Shared_Memory_Declaration
767 (Decl_Id
: Entity_Id
;
768 Init_Val
: Node_Id
) return Node_Id
;
769 -- Builds a declaration the Defining_Identifier of which is Decl_Id, the
770 -- type of which is inferred from CUDA.Internal.Launch_Kernel and the
771 -- value of which is Init_Val if present or null if not.
773 function Build_Simple_Declaration_With_Default
774 (Decl_Id
: Entity_Id
;
777 Default_Val
: Node_Id
) return Node_Id
;
778 -- Build a declaration the Defining_Identifier of which is Decl_Id, the
779 -- Object_Definition of which is Typ, the value of which is Init_Val if
780 -- present or Default otherwise.
782 function Build_Stream_Declaration
783 (Decl_Id
: Entity_Id
;
784 Init_Val
: Node_Id
) return Node_Id
;
785 -- Build a declaration the Defining_Identifier of which is Decl_Id, the
786 -- type of which is Integer, the value of which is Init_Val if present
789 function Etype_Or_Dim3
(N
: Node_Id
) return Node_Id
;
790 -- If N is an aggregate whose type is unknown, return a new occurrence
791 -- of the public Dim3 type. Otherwise, return a new occurrence of N's
794 function Get_Nth_Arg_Type
795 (Subprogram
: Entity_Id
;
796 N
: Positive) return Entity_Id
;
797 -- Returns the type of the Nth argument of Subprogram
799 function To_Addresses
(Elmts
: Elist_Id
) return List_Id
;
800 -- Returns a new list containing each element of Elmts wrapped in an
801 -- 'address attribute reference. When passed No_Elist, returns an empty
808 procedure Append_Copies
817 Param
:= First
(Params
);
818 while Present
(Param
) loop
819 Copy
:= Make_Temporary
(Loc
, 'C');
821 if Nkind
(Param
) = N_Parameter_Association
then
822 Expr
:= Explicit_Actual_Parameter
(Param
);
828 Make_Object_Declaration
(Loc
,
829 Defining_Identifier
=> Copy
,
830 Object_Definition
=> New_Occurrence_Of
(Etype
(Expr
), Loc
),
831 Expression
=> New_Copy_Tree
(Expr
)));
833 Append_Elmt
(Copy
, Copies
);
838 ----------------------------
839 -- Build_Dim3_Declaration --
840 ----------------------------
842 function Build_Dim3_Declaration
843 (Decl_Id
: Entity_Id
;
844 Init_Val
: Node_Id
) return Node_Id
846 -- Expressions for each component of the returned Dim3
851 -- Type of CUDA.Internal.Dim3 - inferred from
852 -- RE_Push_Call_Configuration to avoid needing changes in GNAT when
853 -- the CUDA bindings change (this happens frequently).
854 Internal_Dim3
: constant Entity_Id
:=
855 Get_Nth_Arg_Type
(RTE
(RE_Push_Call_Configuration
), 1);
857 -- Entities for each component of external and internal Dim3
858 First_Component
: Entity_Id
:= First_Entity
(RTE
(RE_Dim3
));
859 Second_Component
: Entity_Id
:= Next_Entity
(First_Component
);
860 Third_Component
: Entity_Id
:= Next_Entity
(Second_Component
);
864 -- Sem_prag.adb ensured that Init_Val is either a Dim3, an aggregate
865 -- of three Any_Integers or Any_Integer.
867 -- If Init_Val is a Dim3, use each of its components
869 if Etype
(Init_Val
) = RTE
(RE_Dim3
) then
870 Dim_X
:= Make_Selected_Component
(Loc
,
871 Prefix
=> New_Occurrence_Of
(Entity
(Init_Val
), Loc
),
872 Selector_Name
=> New_Occurrence_Of
(First_Component
, Loc
));
874 Dim_Y
:= Make_Selected_Component
(Loc
,
875 Prefix
=> New_Occurrence_Of
(Entity
(Init_Val
), Loc
),
876 Selector_Name
=> New_Occurrence_Of
(Second_Component
, Loc
));
878 Dim_Z
:= Make_Selected_Component
(Loc
,
879 Prefix
=> New_Occurrence_Of
(Entity
(Init_Val
), Loc
),
880 Selector_Name
=> New_Occurrence_Of
(Third_Component
, Loc
));
882 -- If Init_Val is an aggregate, use each of its arguments
884 if Nkind
(Init_Val
) = N_Aggregate
then
885 Dim_X
:= First
(Expressions
(Init_Val
));
886 Dim_Y
:= Next
(Dim_X
);
887 Dim_Z
:= Next
(Dim_Y
);
889 -- Otherwise, we know it is an integer and the rest defaults to 1
893 Dim_Y
:= Make_Integer_Literal
(Loc
, 1);
894 Dim_Z
:= Make_Integer_Literal
(Loc
, 1);
898 First_Component
:= First_Entity
(Internal_Dim3
);
899 Second_Component
:= Next_Entity
(First_Component
);
900 Third_Component
:= Next_Entity
(Second_Component
);
902 -- Finally return the CUDA.Internal.Dim3 declaration with an
903 -- aggregate initialization expression.
905 return Make_Object_Declaration
(Loc
,
906 Defining_Identifier
=> Decl_Id
,
907 Object_Definition
=> New_Occurrence_Of
(Internal_Dim3
, Loc
),
908 Expression
=> Make_Aggregate
(Loc
,
909 Expressions
=> New_List
(
910 Make_Type_Conversion
(Loc
,
912 New_Occurrence_Of
(Etype
(First_Component
), Loc
),
913 Expression
=> New_Copy_Tree
(Dim_X
)),
914 Make_Type_Conversion
(Loc
,
916 New_Occurrence_Of
(Etype
(Second_Component
), Loc
),
917 Expression
=> New_Copy_Tree
(Dim_Y
)),
918 Make_Type_Conversion
(Loc
,
920 New_Occurrence_Of
(Etype
(Third_Component
), Loc
),
921 Expression
=> New_Copy_Tree
(Dim_Z
)))));
922 end Build_Dim3_Declaration
;
924 -----------------------------------
925 -- Build_Kernel_Args_Declaration --
926 -----------------------------------
928 function Build_Kernel_Args_Declaration
929 (Kernel_Arg
: Entity_Id
;
930 Var_Ids
: Elist_Id
) return Node_Id
932 Vals
: constant List_Id
:= To_Addresses
(Var_Ids
);
935 Make_Object_Declaration
(Loc
,
936 Defining_Identifier
=> Kernel_Arg
,
938 Make_Constrained_Array_Definition
(Loc
,
939 Discrete_Subtype_Definitions
=> New_List
(
941 Low_Bound
=> Make_Integer_Literal
(Loc
, 1),
943 Make_Integer_Literal
(Loc
, List_Length
(Vals
)))),
944 Component_Definition
=>
945 Make_Component_Definition
(Loc
,
946 Subtype_Indication
=>
947 New_Occurrence_Of
(Etype
(RTE
(RE_Address
)), Loc
))),
948 Expression
=> Make_Aggregate
(Loc
, Vals
));
949 end Build_Kernel_Args_Declaration
;
951 -------------------------------
952 -- Build_Launch_Kernel_Call --
953 -------------------------------
955 function Build_Launch_Kernel_Call
957 Grid_Dims
: Entity_Id
;
958 Block_Dims
: Entity_Id
;
959 Kernel_Arg
: Entity_Id
;
961 Stream
: Entity_Id
) return Node_Id
is
964 Make_Procedure_Call_Statement
(Loc
,
966 New_Occurrence_Of
(RTE
(RE_Launch_Kernel
), Loc
),
967 Parameter_Associations
=> New_List
(
968 Make_Attribute_Reference
(Loc
,
969 Prefix
=> New_Occurrence_Of
(Proc
, Loc
),
970 Attribute_Name
=> Name_Address
),
971 New_Occurrence_Of
(Grid_Dims
, Loc
),
972 New_Occurrence_Of
(Block_Dims
, Loc
),
973 Make_Attribute_Reference
(Loc
,
974 Prefix
=> New_Occurrence_Of
(Kernel_Arg
, Loc
),
975 Attribute_Name
=> Name_Address
),
976 New_Occurrence_Of
(Memory
, Loc
),
977 New_Occurrence_Of
(Stream
, Loc
)));
978 end Build_Launch_Kernel_Call
;
980 -------------------------------------
981 -- Build_Shared_Memory_Declaration --
982 -------------------------------------
984 function Build_Shared_Memory_Declaration
985 (Decl_Id
: Entity_Id
;
986 Init_Val
: Node_Id
) return Node_Id
989 return Build_Simple_Declaration_With_Default
991 Init_Val
=> Init_Val
,
994 (Get_Nth_Arg_Type
(RTE
(RE_Launch_Kernel
), 5), Loc
),
995 Default_Val
=> Make_Integer_Literal
(Loc
, 0));
996 end Build_Shared_Memory_Declaration
;
998 -------------------------------------------
999 -- Build_Simple_Declaration_With_Default --
1000 -------------------------------------------
1002 function Build_Simple_Declaration_With_Default
1003 (Decl_Id
: Entity_Id
;
1006 Default_Val
: Node_Id
) return Node_Id
1008 Value
: Node_Id
:= Init_Val
;
1011 Value
:= Default_Val
;
1014 return Make_Object_Declaration
(Loc
,
1015 Defining_Identifier
=> Decl_Id
,
1016 Object_Definition
=> Typ
,
1017 Expression
=> Value
);
1018 end Build_Simple_Declaration_With_Default
;
1020 ------------------------------
1021 -- Build_Stream_Declaration --
1022 ------------------------------
1024 function Build_Stream_Declaration
1025 (Decl_Id
: Entity_Id
;
1026 Init_Val
: Node_Id
) return Node_Id
1029 return Build_Simple_Declaration_With_Default
1030 (Decl_Id
=> Decl_Id
,
1031 Init_Val
=> Init_Val
,
1034 (Get_Nth_Arg_Type
(RTE
(RE_Launch_Kernel
), 6), Loc
),
1035 Default_Val
=> Make_Null
(Loc
));
1036 end Build_Stream_Declaration
;
1042 function Etype_Or_Dim3
(N
: Node_Id
) return Node_Id
is
1044 if Nkind
(N
) = N_Aggregate
and then Is_Composite_Type
(Etype
(N
)) then
1045 return New_Occurrence_Of
(RTE
(RE_Dim3
), Sloc
(N
));
1048 return New_Occurrence_Of
(Etype
(N
), Loc
);
1051 ----------------------
1052 -- Get_Nth_Arg_Type --
1053 ----------------------
1055 function Get_Nth_Arg_Type
1056 (Subprogram
: Entity_Id
;
1057 N
: Positive) return Entity_Id
1059 Argument
: Entity_Id
:= First_Entity
(Subprogram
);
1061 for J
in 2 .. N
loop
1062 Next_Entity
(Argument
);
1065 return Etype
(Argument
);
1066 end Get_Nth_Arg_Type
;
1072 function To_Addresses
(Elmts
: Elist_Id
) return List_Id
is
1073 Result
: constant List_Id
:= New_List
;
1080 Elmt
:= First_Elmt
(Elmts
);
1081 while Present
(Elmt
) loop
1083 Make_Attribute_Reference
(Loc
,
1084 Prefix
=> New_Occurrence_Of
(Node
(Elmt
), Loc
),
1085 Attribute_Name
=> Name_Address
));
1096 Procedure_Call
: constant Node_Id
:= Get_Pragma_Arg
(Arg_N
(N
, 1));
1097 Grid_Dimensions
: constant Node_Id
:= Get_Pragma_Arg
(Arg_N
(N
, 2));
1098 Block_Dimensions
: constant Node_Id
:= Get_Pragma_Arg
(Arg_N
(N
, 3));
1099 Shared_Memory
: constant Node_Id
:= Get_Pragma_Arg
(Arg_N
(N
, 4));
1100 CUDA_Stream
: constant Node_Id
:= Get_Pragma_Arg
(Arg_N
(N
, 5));
1102 -- Entities of objects that will be overwritten by calls to cuda runtime
1103 Grids_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'C');
1104 Blocks_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'C');
1105 Memory_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'C');
1106 Stream_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'C');
1108 -- Entities of objects that capture the value of pragma arguments
1109 Temp_Grid
: constant Entity_Id
:= Make_Temporary
(Loc
, 'C');
1110 Temp_Block
: constant Entity_Id
:= Make_Temporary
(Loc
, 'C');
1112 -- Declarations for temporary block and grids. These needs to be stored
1113 -- in temporary declarations as the expressions will need to be
1114 -- referenced multiple times but could have side effects.
1115 Temp_Grid_Decl
: constant Node_Id
:= Make_Object_Declaration
(Loc
,
1116 Defining_Identifier
=> Temp_Grid
,
1117 Object_Definition
=> Etype_Or_Dim3
(Grid_Dimensions
),
1118 Expression
=> Grid_Dimensions
);
1119 Temp_Block_Decl
: constant Node_Id
:= Make_Object_Declaration
(Loc
,
1120 Defining_Identifier
=> Temp_Block
,
1121 Object_Definition
=> Etype_Or_Dim3
(Block_Dimensions
),
1122 Expression
=> Block_Dimensions
);
1124 -- List holding the entities of the copies of Procedure_Call's arguments
1126 Kernel_Arg_Copies
: constant Elist_Id
:= New_Elmt_List
;
1128 -- Entity of the array that contains the address of each of the kernel's
1131 Kernel_Args_Id
: constant Entity_Id
:= Make_Temporary
(Loc
, 'C');
1133 -- Calls to the CUDA runtime API.
1135 Launch_Kernel_Call
: Node_Id
;
1137 Push_Call
: Node_Id
;
1139 -- Declaration of all temporaries required for CUDA API Calls
1141 Blk_Decls
: constant List_Id
:= New_List
;
1143 -- Start of processing for CUDA_Execute
1146 -- Append temporary declarations
1148 Append_To
(Blk_Decls
, Temp_Grid_Decl
);
1149 Analyze
(Temp_Grid_Decl
);
1151 Append_To
(Blk_Decls
, Temp_Block_Decl
);
1152 Analyze
(Temp_Block_Decl
);
1154 -- Build parameter declarations for CUDA API calls
1158 Build_Dim3_Declaration
1159 (Grids_Id
, New_Occurrence_Of
(Temp_Grid
, Loc
)));
1163 Build_Dim3_Declaration
1164 (Blocks_Id
, New_Occurrence_Of
(Temp_Block
, Loc
)));
1168 Build_Shared_Memory_Declaration
(Memory_Id
, Shared_Memory
));
1171 (Blk_Decls
, Build_Stream_Declaration
(Stream_Id
, CUDA_Stream
));
1174 (Parameter_Associations
(Procedure_Call
),
1180 Build_Kernel_Args_Declaration
1181 (Kernel_Args_Id
, Kernel_Arg_Copies
));
1183 -- Build calls to the CUDA API
1186 Make_Procedure_Call_Statement
(Loc
,
1188 New_Occurrence_Of
(RTE
(RE_Push_Call_Configuration
), Loc
),
1189 Parameter_Associations
=> New_List
(
1190 New_Occurrence_Of
(Grids_Id
, Loc
),
1191 New_Occurrence_Of
(Blocks_Id
, Loc
),
1192 New_Occurrence_Of
(Memory_Id
, Loc
),
1193 New_Occurrence_Of
(Stream_Id
, Loc
)));
1196 Make_Procedure_Call_Statement
(Loc
,
1198 New_Occurrence_Of
(RTE
(RE_Pop_Call_Configuration
), Loc
),
1199 Parameter_Associations
=> To_Addresses
1206 Launch_Kernel_Call
:= Build_Launch_Kernel_Call
1207 (Proc
=> Entity
(Name
(Procedure_Call
)),
1208 Grid_Dims
=> Grids_Id
,
1209 Block_Dims
=> Blocks_Id
,
1210 Kernel_Arg
=> Kernel_Args_Id
,
1211 Memory
=> Memory_Id
,
1212 Stream
=> Stream_Id
);
1214 -- Finally make the block that holds declarations and calls
1217 Make_Block_Statement
(Loc
,
1218 Declarations
=> Blk_Decls
,
1219 Handled_Statement_Sequence
=>
1220 Make_Handled_Sequence_Of_Statements
(Loc
,
1221 Statements
=> New_List
(
1224 Launch_Kernel_Call
))));
1226 end Expand_Pragma_CUDA_Execute
;
1228 ----------------------------------
1229 -- Expand_Pragma_Contract_Cases --
1230 ----------------------------------
1232 -- Pragma Contract_Cases is expanded in the following manner:
1235 -- Count : Natural := 0;
1236 -- Flag_1 : Boolean := False;
1238 -- Flag_N : Boolean := False;
1239 -- Flag_N+1 : Boolean := False; -- when "others" present
1244 -- <preconditions (if any)>
1246 -- -- Evaluate all case guards
1248 -- if Case_Guard_1 then
1250 -- Count := Count + 1;
1253 -- if Case_Guard_N then
1255 -- Count := Count + 1;
1258 -- -- Emit errors depending on the number of case guards that
1259 -- -- evaluated to True.
1261 -- if Count = 0 then
1262 -- raise Assertion_Error with "xxx contract cases incomplete";
1264 -- Flag_N+1 := True; -- when "others" present
1266 -- elsif Count > 1 then
1268 -- Str0 : constant String :=
1269 -- "contract cases overlap for subprogram ABC";
1270 -- Str1 : constant String :=
1272 -- Str0 & "case guard at xxx evaluates to True"
1274 -- StrN : constant String :=
1276 -- StrN-1 & "case guard at xxx evaluates to True"
1279 -- raise Assertion_Error with StrN;
1283 -- -- Evaluate all attribute 'Old prefixes found in the selected
1287 -- Pref_1 := <prefix of 'Old found in Consequence_1>
1289 -- elsif Flag_N then
1290 -- Pref_M := <prefix of 'Old found in Consequence_N>
1293 -- procedure _Postconditions is
1295 -- <postconditions (if any)>
1297 -- if Flag_1 and then not Consequence_1 then
1298 -- raise Assertion_Error with "failed contract case at xxx";
1301 -- if Flag_N[+1] and then not Consequence_N[+1] then
1302 -- raise Assertion_Error with "failed contract case at xxx";
1304 -- end _Postconditions;
1309 procedure Expand_Pragma_Contract_Cases
1311 Subp_Id
: Entity_Id
;
1313 Stmts
: in out List_Id
)
1315 Loc
: constant Source_Ptr
:= Sloc
(CCs
);
1317 procedure Case_Guard_Error
1320 Error_Loc
: Source_Ptr
;
1321 Msg
: in out Entity_Id
);
1322 -- Given a declarative list Decls, status flag Flag, the location of the
1323 -- error and a string Msg, construct the following check:
1324 -- Msg : constant String :=
1326 -- Msg & "case guard at Error_Loc evaluates to True"
1328 -- The resulting code is added to Decls
1330 procedure Consequence_Error
1331 (Checks
: in out Node_Id
;
1334 -- Given an if statement Checks, status flag Flag and a consequence
1335 -- Conseq, construct the following check:
1336 -- [els]if Flag and then not Conseq then
1337 -- raise Assertion_Error
1338 -- with "failed contract case at Sloc (Conseq)";
1340 -- The resulting code is added to Checks
1342 function Declaration_Of
(Id
: Entity_Id
) return Node_Id
;
1343 -- Given the entity Id of a boolean flag, generate:
1344 -- Id : Boolean := False;
1346 procedure Expand_Attributes_In_Consequence
1348 Evals
: in out Node_Id
;
1351 -- Perform specialized expansion of all attribute 'Old references found
1352 -- in consequence Conseq such that at runtime only prefixes coming from
1353 -- the selected consequence are evaluated. Similarly expand attribute
1354 -- 'Result references by replacing them with identifier _result which
1355 -- resolves to the sole formal parameter of procedure _Postconditions.
1356 -- Any temporaries generated in the process are added to declarations
1357 -- Decls. Evals is a complex if statement tasked with the evaluation of
1358 -- all prefixes coming from a single selected consequence. Flag is the
1359 -- corresponding case guard flag. Conseq is the consequence expression.
1361 function Increment
(Id
: Entity_Id
) return Node_Id
;
1362 -- Given the entity Id of a numerical variable, generate:
1365 function Set
(Id
: Entity_Id
) return Node_Id
;
1366 -- Given the entity Id of a boolean variable, generate:
1369 ----------------------
1370 -- Case_Guard_Error --
1371 ----------------------
1373 procedure Case_Guard_Error
1376 Error_Loc
: Source_Ptr
;
1377 Msg
: in out Entity_Id
)
1379 New_Line
: constant Character := Character'Val (10);
1380 New_Msg
: constant Entity_Id
:= Make_Temporary
(Loc
, 'S');
1384 Store_String_Char
(New_Line
);
1385 Store_String_Chars
(" case guard at ");
1386 Store_String_Chars
(Build_Location_String
(Error_Loc
));
1387 Store_String_Chars
(" evaluates to True");
1390 -- New_Msg : constant String :=
1392 -- Msg & "case guard at Error_Loc evaluates to True"
1396 Make_Object_Declaration
(Loc
,
1397 Defining_Identifier
=> New_Msg
,
1398 Constant_Present
=> True,
1399 Object_Definition
=> New_Occurrence_Of
(Standard_String
, Loc
),
1401 Make_If_Expression
(Loc
,
1402 Expressions
=> New_List
(
1403 New_Occurrence_Of
(Flag
, Loc
),
1405 Make_Op_Concat
(Loc
,
1406 Left_Opnd
=> New_Occurrence_Of
(Msg
, Loc
),
1407 Right_Opnd
=> Make_String_Literal
(Loc
, End_String
)),
1409 New_Occurrence_Of
(Msg
, Loc
)))));
1412 end Case_Guard_Error
;
1414 -----------------------
1415 -- Consequence_Error --
1416 -----------------------
1418 procedure Consequence_Error
1419 (Checks
: in out Node_Id
;
1428 -- Flag and then not Conseq
1432 Left_Opnd
=> New_Occurrence_Of
(Flag
, Loc
),
1435 Right_Opnd
=> Relocate_Node
(Conseq
)));
1438 -- raise Assertion_Error
1439 -- with "failed contract case at Sloc (Conseq)";
1442 Store_String_Chars
("failed contract case at ");
1443 Store_String_Chars
(Build_Location_String
(Sloc
(Conseq
)));
1446 Make_Procedure_Call_Statement
(Loc
,
1448 New_Occurrence_Of
(RTE
(RE_Raise_Assert_Failure
), Loc
),
1449 Parameter_Associations
=> New_List
(
1450 Make_String_Literal
(Loc
, End_String
)));
1454 Make_Implicit_If_Statement
(CCs
,
1456 Then_Statements
=> New_List
(Error
));
1458 Set_Comes_From_Check_Or_Contract
(Checks
);
1461 if No
(Elsif_Parts
(Checks
)) then
1462 Set_Elsif_Parts
(Checks
, New_List
);
1465 Append_To
(Elsif_Parts
(Checks
),
1466 Make_Elsif_Part
(Loc
,
1468 Then_Statements
=> New_List
(Error
)));
1470 end Consequence_Error
;
1472 --------------------
1473 -- Declaration_Of --
1474 --------------------
1476 function Declaration_Of
(Id
: Entity_Id
) return Node_Id
is
1479 Make_Object_Declaration
(Loc
,
1480 Defining_Identifier
=> Id
,
1481 Object_Definition
=> New_Occurrence_Of
(Standard_Boolean
, Loc
),
1482 Expression
=> New_Occurrence_Of
(Standard_False
, Loc
));
1485 --------------------------------------
1486 -- Expand_Attributes_In_Consequence --
1487 --------------------------------------
1489 procedure Expand_Attributes_In_Consequence
1491 Evals
: in out Node_Id
;
1495 Eval_Stmts
: List_Id
:= No_List
;
1496 -- The evaluation sequence expressed as assignment statements of all
1497 -- prefixes of attribute 'Old found in the current consequence.
1499 function Expand_Attributes
(N
: Node_Id
) return Traverse_Result
;
1500 -- Determine whether an arbitrary node denotes attribute 'Old or
1501 -- 'Result and if it does, perform all expansion-related actions.
1503 -----------------------
1504 -- Expand_Attributes --
1505 -----------------------
1507 function Expand_Attributes
(N
: Node_Id
) return Traverse_Result
is
1511 Indirect
: Boolean := False;
1513 use Sem_Util
.Old_Attr_Util
.Indirect_Temps
;
1515 procedure Append_For_Indirect_Temp
1516 (N
: Node_Id
; Is_Eval_Stmt
: Boolean);
1518 -- Append either a declaration (which is to be elaborated
1519 -- unconditionally) or an evaluation statement (which is
1520 -- to be executed conditionally).
1522 -------------------------------
1523 -- Append_For_Indirect_Temp --
1524 -------------------------------
1526 procedure Append_For_Indirect_Temp
1527 (N
: Node_Id
; Is_Eval_Stmt
: Boolean)
1530 if Is_Eval_Stmt
then
1531 Append_To
(Eval_Stmts
, N
);
1533 Prepend_To
(Decls
, N
);
1534 -- This use of Prepend (as opposed to Append) is why
1535 -- we have the Append_Decls_In_Reverse_Order parameter.
1537 end Append_For_Indirect_Temp
;
1539 procedure Declare_Indirect_Temporary
is new
1540 Declare_Indirect_Temp
(
1541 Append_Item
=> Append_For_Indirect_Temp
,
1542 Append_Decls_In_Reverse_Order
=> True);
1544 -- Start of processing for Expand_Attributes
1549 if Is_Attribute_Old
(N
) then
1552 Indirect
:= Indirect_Temp_Needed
(Etype
(Pref
));
1555 if No
(Eval_Stmts
) then
1556 Eval_Stmts
:= New_List
;
1559 Declare_Indirect_Temporary
1560 (Attr_Prefix
=> Pref
,
1561 Indirect_Temp
=> Temp
);
1563 -- Declare a temporary of the prefix type with no explicit
1564 -- initial value. If the appropriate contract case is selected
1565 -- at run time, then the temporary will be initialized via an
1566 -- assignment statement.
1569 Temp
:= Make_Temporary
(Loc
, 'T', Pref
);
1570 Set_Etype
(Temp
, Etype
(Pref
));
1572 -- Generate a temporary to capture the value of the prefix:
1573 -- Temp : <Pref type>;
1576 Make_Object_Declaration
(Loc
,
1577 Defining_Identifier
=> Temp
,
1578 Object_Definition
=>
1579 New_Occurrence_Of
(Etype
(Pref
), Loc
));
1581 -- Place that temporary at the beginning of declarations, to
1582 -- prevent anomalies in the GNATprove flow-analysis pass in
1583 -- the precondition procedure that follows.
1585 Prepend_To
(Decls
, Decl
);
1587 -- Initially Temp is uninitialized (which is required for
1588 -- correctness if default initialization might have side
1589 -- effects). Assign prefix value to temp on Eval_Statement
1590 -- list, so assignment will be executed conditionally.
1592 Mutate_Ekind
(Temp
, E_Variable
);
1593 Set_Suppress_Initialization
(Temp
);
1596 if No
(Eval_Stmts
) then
1597 Eval_Stmts
:= New_List
;
1600 Append_To
(Eval_Stmts
,
1601 Make_Assignment_Statement
(Loc
,
1602 Name
=> New_Occurrence_Of
(Temp
, Loc
),
1603 Expression
=> Pref
));
1606 -- Mark the temporary as coming from a 'Old reference
1608 if Present
(Temp
) then
1609 Set_Stores_Attribute_Old_Prefix
(Temp
);
1612 -- Ensure that the prefix is valid
1614 if Validity_Checks_On
and then Validity_Check_Operands
then
1615 Ensure_Valid
(Pref
);
1618 -- Replace the original attribute 'Old by a reference to the
1619 -- generated temporary.
1624 (Temp
=> Temp
, Typ
=> Etype
(Pref
), Loc
=> Loc
));
1626 Rewrite
(N
, New_Occurrence_Of
(Temp
, Loc
));
1629 -- Attribute 'Result
1631 elsif Is_Attribute_Result
(N
) then
1632 Rewrite
(N
, Make_Identifier
(Loc
, Name_uResult
));
1636 end Expand_Attributes
;
1638 procedure Expand_Attributes_In
is
1639 new Traverse_Proc
(Expand_Attributes
);
1641 -- Start of processing for Expand_Attributes_In_Consequence
1644 -- Inspect the consequence and expand any attribute 'Old and 'Result
1645 -- references found within.
1647 Expand_Attributes_In
(Conseq
);
1649 -- The consequence does not contain any attribute 'Old references
1651 if No
(Eval_Stmts
) then
1655 -- Augment the machinery to trigger the evaluation of all prefixes
1656 -- found in the step above. If Eval is empty, then this is the first
1657 -- consequence to yield expansion of 'Old. Generate:
1660 -- <evaluation statements>
1665 Make_Implicit_If_Statement
(CCs
,
1666 Condition
=> New_Occurrence_Of
(Flag
, Loc
),
1667 Then_Statements
=> Eval_Stmts
);
1669 Set_Comes_From_Check_Or_Contract
(Evals
);
1671 -- Otherwise generate:
1673 -- <evaluation statements>
1677 if No
(Elsif_Parts
(Evals
)) then
1678 Set_Elsif_Parts
(Evals
, New_List
);
1681 Append_To
(Elsif_Parts
(Evals
),
1682 Make_Elsif_Part
(Loc
,
1683 Condition
=> New_Occurrence_Of
(Flag
, Loc
),
1684 Then_Statements
=> Eval_Stmts
));
1686 end Expand_Attributes_In_Consequence
;
1692 function Increment
(Id
: Entity_Id
) return Node_Id
is
1695 Make_Assignment_Statement
(Loc
,
1696 Name
=> New_Occurrence_Of
(Id
, Loc
),
1699 Left_Opnd
=> New_Occurrence_Of
(Id
, Loc
),
1700 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)));
1707 function Set
(Id
: Entity_Id
) return Node_Id
is
1710 Make_Assignment_Statement
(Loc
,
1711 Name
=> New_Occurrence_Of
(Id
, Loc
),
1712 Expression
=> New_Occurrence_Of
(Standard_True
, Loc
));
1717 Aggr
: constant Node_Id
:=
1718 Expression
(First
(Pragma_Argument_Associations
(CCs
)));
1720 Case_Guard
: Node_Id
;
1721 CG_Checks
: Node_Id
;
1724 Conseq_Checks
: Node_Id
:= Empty
;
1726 Count_Decl
: Node_Id
;
1727 Error_Decls
: List_Id
:= No_List
; -- init to avoid warning
1729 Flag_Decl
: Node_Id
;
1731 Msg_Str
: Entity_Id
:= Empty
;
1732 Multiple_PCs
: Boolean;
1733 Old_Evals
: Node_Id
:= Empty
;
1734 Others_Decl
: Node_Id
;
1735 Others_Flag
: Entity_Id
:= Empty
;
1736 Post_Case
: Node_Id
;
1738 -- Start of processing for Expand_Pragma_Contract_Cases
1741 -- Do nothing if pragma is not enabled. If pragma is disabled, it has
1742 -- already been rewritten as a Null statement.
1744 if Is_Ignored
(CCs
) then
1747 -- Guard against malformed contract cases
1749 elsif Nkind
(Aggr
) /= N_Aggregate
then
1753 -- The expansion of contract cases is quite distributed as it produces
1754 -- various statements to evaluate the case guards and consequences. To
1755 -- preserve the original context, set the Is_Assertion_Expr flag. This
1756 -- aids the Ghost legality checks when verifying the placement of a
1757 -- reference to a Ghost entity.
1759 In_Assertion_Expr
:= In_Assertion_Expr
+ 1;
1761 Multiple_PCs
:= List_Length
(Component_Associations
(Aggr
)) > 1;
1763 -- Create the counter which tracks the number of case guards that
1764 -- evaluate to True.
1766 -- Count : Natural := 0;
1768 Count
:= Make_Temporary
(Loc
, 'C');
1770 Make_Object_Declaration
(Loc
,
1771 Defining_Identifier
=> Count
,
1772 Object_Definition
=> New_Occurrence_Of
(Standard_Natural
, Loc
),
1773 Expression
=> Make_Integer_Literal
(Loc
, 0));
1775 Prepend_To
(Decls
, Count_Decl
);
1776 Analyze
(Count_Decl
);
1778 -- Create the base error message for multiple overlapping case guards
1780 -- Msg_Str : constant String :=
1781 -- "contract cases overlap for subprogram Subp_Id";
1783 if Multiple_PCs
then
1784 Msg_Str
:= Make_Temporary
(Loc
, 'S');
1787 Store_String_Chars
("contract cases overlap for subprogram ");
1788 Store_String_Chars
(Get_Name_String
(Chars
(Subp_Id
)));
1790 Error_Decls
:= New_List
(
1791 Make_Object_Declaration
(Loc
,
1792 Defining_Identifier
=> Msg_Str
,
1793 Constant_Present
=> True,
1794 Object_Definition
=> New_Occurrence_Of
(Standard_String
, Loc
),
1795 Expression
=> Make_String_Literal
(Loc
, End_String
)));
1798 -- Process individual post cases
1800 Post_Case
:= First
(Component_Associations
(Aggr
));
1801 while Present
(Post_Case
) loop
1802 Case_Guard
:= First
(Choices
(Post_Case
));
1803 Conseq
:= Expression
(Post_Case
);
1805 -- The "others" choice requires special processing
1807 if Nkind
(Case_Guard
) = N_Others_Choice
then
1808 Others_Flag
:= Make_Temporary
(Loc
, 'F');
1809 Others_Decl
:= Declaration_Of
(Others_Flag
);
1811 Prepend_To
(Decls
, Others_Decl
);
1812 Analyze
(Others_Decl
);
1814 -- Check possible overlap between a case guard and "others"
1816 if Multiple_PCs
and Exception_Extra_Info
then
1818 (Decls
=> Error_Decls
,
1819 Flag
=> Others_Flag
,
1820 Error_Loc
=> Sloc
(Case_Guard
),
1824 -- Inspect the consequence and perform special expansion of any
1825 -- attribute 'Old and 'Result references found within.
1827 Expand_Attributes_In_Consequence
1830 Flag
=> Others_Flag
,
1833 -- Check the corresponding consequence of "others"
1836 (Checks
=> Conseq_Checks
,
1837 Flag
=> Others_Flag
,
1840 -- Regular post case
1843 -- Create the flag which tracks the state of its associated case
1846 Flag
:= Make_Temporary
(Loc
, 'F');
1847 Flag_Decl
:= Declaration_Of
(Flag
);
1849 Prepend_To
(Decls
, Flag_Decl
);
1850 Analyze
(Flag_Decl
);
1852 -- The flag is set when the case guard is evaluated to True
1853 -- if Case_Guard then
1855 -- Count := Count + 1;
1859 Make_Implicit_If_Statement
(CCs
,
1860 Condition
=> Relocate_Node
(Case_Guard
),
1861 Then_Statements
=> New_List
(
1863 Increment
(Count
)));
1865 Set_Comes_From_Check_Or_Contract
(If_Stmt
);
1867 Append_To
(Decls
, If_Stmt
);
1870 -- Check whether this case guard overlaps with another one
1872 if Multiple_PCs
and Exception_Extra_Info
then
1874 (Decls
=> Error_Decls
,
1876 Error_Loc
=> Sloc
(Case_Guard
),
1880 -- Inspect the consequence and perform special expansion of any
1881 -- attribute 'Old and 'Result references found within.
1883 Expand_Attributes_In_Consequence
1889 -- The corresponding consequence of the case guard which evaluated
1890 -- to True must hold on exit from the subprogram.
1893 (Checks
=> Conseq_Checks
,
1901 -- Raise Assertion_Error when none of the case guards evaluate to True.
1902 -- The only exception is when we have "others", in which case there is
1903 -- no error because "others" acts as a default True.
1908 if Present
(Others_Flag
) then
1909 CG_Stmts
:= New_List
(Set
(Others_Flag
));
1912 -- raise Assertion_Error with "xxx contract cases incomplete";
1916 Store_String_Chars
(Build_Location_String
(Loc
));
1917 Store_String_Chars
(" contract cases incomplete");
1919 CG_Stmts
:= New_List
(
1920 Make_Procedure_Call_Statement
(Loc
,
1922 New_Occurrence_Of
(RTE
(RE_Raise_Assert_Failure
), Loc
),
1923 Parameter_Associations
=> New_List
(
1924 Make_String_Literal
(Loc
, End_String
))));
1928 Make_Implicit_If_Statement
(CCs
,
1931 Left_Opnd
=> New_Occurrence_Of
(Count
, Loc
),
1932 Right_Opnd
=> Make_Integer_Literal
(Loc
, 0)),
1933 Then_Statements
=> CG_Stmts
);
1935 Set_Comes_From_Check_Or_Contract
(CG_Checks
);
1937 -- Detect a possible failure due to several case guards evaluating to
1941 -- elsif Count > 0 then
1945 -- raise Assertion_Error with <Msg_Str>;
1948 if Multiple_PCs
then
1949 Set_Elsif_Parts
(CG_Checks
, New_List
(
1950 Make_Elsif_Part
(Loc
,
1953 Left_Opnd
=> New_Occurrence_Of
(Count
, Loc
),
1954 Right_Opnd
=> Make_Integer_Literal
(Loc
, 1)),
1956 Then_Statements
=> New_List
(
1957 Make_Block_Statement
(Loc
,
1958 Declarations
=> Error_Decls
,
1959 Handled_Statement_Sequence
=>
1960 Make_Handled_Sequence_Of_Statements
(Loc
,
1961 Statements
=> New_List
(
1962 Make_Procedure_Call_Statement
(Loc
,
1965 (RTE
(RE_Raise_Assert_Failure
), Loc
),
1966 Parameter_Associations
=> New_List
(
1967 New_Occurrence_Of
(Msg_Str
, Loc
))))))))));
1970 -- Append the checks, but do not analyze them at this point, because
1971 -- contracts get potentially expanded as part of a wrapper which gets
1972 -- fully analyzed once it is fully formed.
1974 Append_To
(Decls
, CG_Checks
);
1976 -- Once all case guards are evaluated and checked, evaluate any prefixes
1977 -- of attribute 'Old founds in the selected consequence.
1979 if Present
(Old_Evals
) then
1980 Append_To
(Decls
, Old_Evals
);
1983 -- Raise Assertion_Error when the corresponding consequence of a case
1984 -- guard that evaluated to True fails.
1986 Append_New_To
(Stmts
, Conseq_Checks
);
1988 In_Assertion_Expr
:= In_Assertion_Expr
- 1;
1989 end Expand_Pragma_Contract_Cases
;
1991 -------------------------------------
1992 -- Expand_Pragma_Exceptional_Cases --
1993 -------------------------------------
1995 -- Aspect Exceptional_Cases shoule be expanded in the following manner:
1997 -- Original declaration
1999 -- procedure P (...) with
2000 -- Exceptional_Cases =>
2002 -- Exp_2 => Post_4);
2006 -- procedure P (...) is
2008 -- -- normal body of of P
2015 -- pragma Assert (True);
2018 -- pragma Assert (Post_4);
2021 -- pragma Assert (False);
2025 procedure Expand_Pragma_Exceptional_Cases
(Prag
: Node_Id
) is
2027 -- Currently we don't expand this pragma
2029 Rewrite
(Prag
, Make_Null_Statement
(Sloc
(Prag
)));
2030 end Expand_Pragma_Exceptional_Cases
;
2032 ---------------------------------------
2033 -- Expand_Pragma_Import_Or_Interface --
2034 ---------------------------------------
2036 procedure Expand_Pragma_Import_Or_Interface
(N
: Node_Id
) is
2040 -- In Relaxed_RM_Semantics, support old Ada 83 style:
2041 -- pragma Import (Entity, "external name");
2043 if Relaxed_RM_Semantics
2044 and then List_Length
(Pragma_Argument_Associations
(N
)) = 2
2045 and then Pragma_Name
(N
) = Name_Import
2046 and then Nkind
(Arg_N
(N
, 2)) = N_String_Literal
2048 Def_Id
:= Entity
(Arg_N
(N
, 1));
2050 Def_Id
:= Entity
(Arg_N
(N
, 2));
2053 -- Variable case (we have to undo any initialization already done)
2055 if Ekind
(Def_Id
) = E_Variable
then
2056 Undo_Initialization
(Def_Id
, N
);
2058 -- Case of exception with convention C++
2060 elsif Ekind
(Def_Id
) = E_Exception
2061 and then Convention
(Def_Id
) = Convention_CPP
2063 -- Import a C++ convention
2066 Loc
: constant Source_Ptr
:= Sloc
(N
);
2067 Rtti_Name
: constant Node_Id
:= Arg_N
(N
, 3);
2068 Dum
: constant Entity_Id
:= Make_Temporary
(Loc
, 'D');
2070 Lang_Char
: Node_Id
;
2071 Foreign_Data
: Node_Id
;
2074 Exdata
:= Component_Associations
(Expression
(Parent
(Def_Id
)));
2076 Lang_Char
:= Next
(First
(Exdata
));
2078 -- Change the one-character language designator to 'C'
2080 Rewrite
(Expression
(Lang_Char
),
2081 Make_Character_Literal
(Loc
,
2083 Char_Literal_Value
=> UI_From_CC
(Get_Char_Code
('C'))));
2084 Analyze
(Expression
(Lang_Char
));
2086 -- Change the value of Foreign_Data
2088 Foreign_Data
:= Next
(Next
(Next
(Next
(Lang_Char
))));
2090 Insert_Actions
(Def_Id
, New_List
(
2091 Make_Object_Declaration
(Loc
,
2092 Defining_Identifier
=> Dum
,
2093 Object_Definition
=>
2094 New_Occurrence_Of
(Standard_Character
, Loc
)),
2097 Chars
=> Name_Import
,
2098 Pragma_Argument_Associations
=> New_List
(
2099 Make_Pragma_Argument_Association
(Loc
,
2100 Expression
=> Make_Identifier
(Loc
, Name_Ada
)),
2102 Make_Pragma_Argument_Association
(Loc
,
2103 Expression
=> Make_Identifier
(Loc
, Chars
(Dum
))),
2105 Make_Pragma_Argument_Association
(Loc
,
2106 Chars
=> Name_External_Name
,
2107 Expression
=> Relocate_Node
(Rtti_Name
))))));
2109 Rewrite
(Expression
(Foreign_Data
),
2110 OK_Convert_To
(Standard_Address
,
2111 Make_Attribute_Reference
(Loc
,
2112 Prefix
=> Make_Identifier
(Loc
, Chars
(Dum
)),
2113 Attribute_Name
=> Name_Address
)));
2114 Analyze
(Expression
(Foreign_Data
));
2117 -- No special expansion required for any other case
2122 end Expand_Pragma_Import_Or_Interface
;
2124 -------------------------------------
2125 -- Expand_Pragma_Initial_Condition --
2126 -------------------------------------
2128 procedure Expand_Pragma_Initial_Condition
2129 (Pack_Id
: Entity_Id
;
2132 procedure Extract_Package_Body_Lists
2133 (Pack_Body
: Node_Id
;
2134 Body_List
: out List_Id
;
2135 Call_List
: out List_Id
;
2136 Spec_List
: out List_Id
);
2137 -- Obtain the various declarative and statement lists of package body
2138 -- Pack_Body needed to insert the initial condition procedure and the
2139 -- call to it. The lists are as follows:
2141 -- * Body_List - used to insert the initial condition procedure body
2143 -- * Call_List - used to insert the call to the initial condition
2146 -- * Spec_List - used to insert the initial condition procedure spec
2148 procedure Extract_Package_Declaration_Lists
2149 (Pack_Decl
: Node_Id
;
2150 Body_List
: out List_Id
;
2151 Call_List
: out List_Id
;
2152 Spec_List
: out List_Id
);
2153 -- Obtain the various declarative lists of package declaration Pack_Decl
2154 -- needed to insert the initial condition procedure and the call to it.
2155 -- The lists are as follows:
2157 -- * Body_List - used to insert the initial condition procedure body
2159 -- * Call_List - used to insert the call to the initial condition
2162 -- * Spec_List - used to insert the initial condition procedure spec
2164 --------------------------------
2165 -- Extract_Package_Body_Lists --
2166 --------------------------------
2168 procedure Extract_Package_Body_Lists
2169 (Pack_Body
: Node_Id
;
2170 Body_List
: out List_Id
;
2171 Call_List
: out List_Id
;
2172 Spec_List
: out List_Id
)
2174 Pack_Spec
: constant Entity_Id
:= Corresponding_Spec
(Pack_Body
);
2181 pragma Assert
(Present
(Pack_Spec
));
2183 -- The different parts of the invariant procedure are inserted as
2186 -- package Pack is package body Pack is
2187 -- <IC spec> <IC body>
2190 -- end Pack; end Pack;
2192 -- The initial condition procedure spec is inserted in the visible
2193 -- declaration of the corresponding package spec.
2195 Extract_Package_Declaration_Lists
2196 (Pack_Decl
=> Unit_Declaration_Node
(Pack_Spec
),
2197 Body_List
=> Dummy_1
,
2198 Call_List
=> Dummy_2
,
2199 Spec_List
=> Spec_List
);
2201 -- The initial condition procedure body is added to the declarations
2202 -- of the package body.
2204 Body_List
:= Declarations
(Pack_Body
);
2206 if No
(Body_List
) then
2207 Body_List
:= New_List
;
2208 Set_Declarations
(Pack_Body
, Body_List
);
2211 -- The call to the initial condition procedure is inserted in the
2212 -- statements of the package body.
2214 HSS
:= Handled_Statement_Sequence
(Pack_Body
);
2218 Make_Handled_Sequence_Of_Statements
(Sloc
(Pack_Body
),
2219 Statements
=> New_List
);
2220 Set_Handled_Statement_Sequence
(Pack_Body
, HSS
);
2223 Call_List
:= Statements
(HSS
);
2224 end Extract_Package_Body_Lists
;
2226 ---------------------------------------
2227 -- Extract_Package_Declaration_Lists --
2228 ---------------------------------------
2230 procedure Extract_Package_Declaration_Lists
2231 (Pack_Decl
: Node_Id
;
2232 Body_List
: out List_Id
;
2233 Call_List
: out List_Id
;
2234 Spec_List
: out List_Id
)
2236 Pack_Spec
: constant Node_Id
:= Specification
(Pack_Decl
);
2239 -- The different parts of the invariant procedure are inserted as
2249 -- The initial condition procedure spec and body are inserted in the
2250 -- visible declarations of the package spec.
2252 Body_List
:= Visible_Declarations
(Pack_Spec
);
2254 if No
(Body_List
) then
2255 Body_List
:= New_List
;
2256 Set_Visible_Declarations
(Pack_Spec
, Body_List
);
2259 Spec_List
:= Body_List
;
2261 -- The call to the initial procedure is inserted in the private
2262 -- declarations of the package spec.
2264 Call_List
:= Private_Declarations
(Pack_Spec
);
2266 if No
(Call_List
) then
2267 Call_List
:= New_List
;
2268 Set_Private_Declarations
(Pack_Spec
, Call_List
);
2270 end Extract_Package_Declaration_Lists
;
2274 IC_Prag
: constant Node_Id
:=
2275 Get_Pragma
(Pack_Id
, Pragma_Initial_Condition
);
2277 Body_List
: List_Id
;
2279 Call_List
: List_Id
;
2280 Call_Loc
: Source_Ptr
;
2283 Proc_Body
: Node_Id
;
2284 Proc_Body_Id
: Entity_Id
;
2285 Proc_Decl
: Node_Id
;
2286 Proc_Id
: Entity_Id
;
2287 Spec_List
: List_Id
;
2289 -- Start of processing for Expand_Pragma_Initial_Condition
2292 -- Nothing to do when the package is not subject to an Initial_Condition
2295 if No
(IC_Prag
) then
2299 Expr
:= Get_Pragma_Arg
(First
(Pragma_Argument_Associations
(IC_Prag
)));
2300 Loc
:= Sloc
(IC_Prag
);
2302 -- Nothing to do when the pragma is ignored because its semantics are
2305 if Is_Ignored
(IC_Prag
) then
2308 -- Nothing to do when the pragma or its argument are illegal because
2309 -- there is no valid expression to check.
2311 elsif Error_Posted
(IC_Prag
) or else Error_Posted
(Expr
) then
2315 -- Obtain the various lists of the context where the individual pieces
2316 -- of the initial condition procedure are to be inserted.
2318 if Nkind
(N
) = N_Package_Body
then
2319 Extract_Package_Body_Lists
2321 Body_List
=> Body_List
,
2322 Call_List
=> Call_List
,
2323 Spec_List
=> Spec_List
);
2325 elsif Nkind
(N
) = N_Package_Declaration
then
2326 Extract_Package_Declaration_Lists
2328 Body_List
=> Body_List
,
2329 Call_List
=> Call_List
,
2330 Spec_List
=> Spec_List
);
2332 -- This routine should not be used on anything other than packages
2335 pragma Assert
(False);
2340 Make_Defining_Identifier
(Loc
,
2341 Chars
=> New_External_Name
(Chars
(Pack_Id
), "Initial_Condition"));
2343 Mutate_Ekind
(Proc_Id
, E_Procedure
);
2344 Set_Is_Initial_Condition_Procedure
(Proc_Id
);
2347 -- procedure <Pack_Id>Initial_Condition;
2350 Make_Subprogram_Declaration
(Loc
,
2351 Make_Procedure_Specification
(Loc
,
2352 Defining_Unit_Name
=> Proc_Id
));
2354 Append_To
(Spec_List
, Proc_Decl
);
2356 -- The initial condition procedure requires debug info when initial
2357 -- condition is subject to Source Coverage Obligations.
2359 if Generate_SCO
then
2360 Set_Debug_Info_Needed
(Proc_Id
);
2364 -- procedure <Pack_Id>Initial_Condition is
2366 -- pragma Check (Initial_Condition, <Expr>);
2367 -- end <Pack_Id>Initial_Condition;
2370 Make_Subprogram_Body
(Loc
,
2372 Copy_Subprogram_Spec
(Specification
(Proc_Decl
)),
2373 Declarations
=> Empty_List
,
2374 Handled_Statement_Sequence
=>
2375 Make_Handled_Sequence_Of_Statements
(Loc
,
2376 Statements
=> New_List
(
2378 Chars
=> Name_Check
,
2379 Pragma_Argument_Associations
=> New_List
(
2380 Make_Pragma_Argument_Association
(Loc
,
2382 Make_Identifier
(Loc
, Name_Initial_Condition
)),
2383 Make_Pragma_Argument_Association
(Loc
,
2384 Expression
=> New_Copy_Tree
(Expr
)))))));
2386 Append_To
(Body_List
, Proc_Body
);
2388 -- The initial condition procedure requires debug info when initial
2389 -- condition is subject to Source Coverage Obligations.
2391 Proc_Body_Id
:= Defining_Entity
(Proc_Body
);
2393 if Generate_SCO
then
2394 Set_Debug_Info_Needed
(Proc_Body_Id
);
2397 -- The location of the initial condition procedure call must be as close
2398 -- as possible to the intended semantic location of the check because
2399 -- the ABE mechanism relies heavily on accurate locations.
2401 Call_Loc
:= End_Keyword_Location
(N
);
2404 -- <Pack_Id>Initial_Condition;
2407 Make_Procedure_Call_Statement
(Call_Loc
,
2408 Name
=> New_Occurrence_Of
(Proc_Id
, Call_Loc
));
2410 Append_To
(Call_List
, Call
);
2412 Analyze
(Proc_Decl
);
2413 Analyze
(Proc_Body
);
2415 end Expand_Pragma_Initial_Condition
;
2417 ------------------------------------
2418 -- Expand_Pragma_Inspection_Point --
2419 ------------------------------------
2421 -- If no argument is given, then we supply a default argument list that
2422 -- includes all objects declared at the source level in all subprograms
2423 -- that enclose the inspection point pragma.
2425 procedure Expand_Pragma_Inspection_Point
(N
: Node_Id
) is
2426 Loc
: constant Source_Ptr
:= Sloc
(N
);
2435 if No
(Pragma_Argument_Associations
(N
)) then
2439 while S
/= Standard_Standard
loop
2440 E
:= First_Entity
(S
);
2441 while Present
(E
) loop
2442 if Comes_From_Source
(E
)
2443 and then Is_Object
(E
)
2444 and then not Is_Entry_Formal
(E
)
2445 and then not Is_Formal_Object
(E
)
2446 and then Ekind
(E
) /= E_Component
2447 and then Ekind
(E
) /= E_Discriminant
2450 Make_Pragma_Argument_Association
(Loc
,
2451 Expression
=> New_Occurrence_Of
(E
, Loc
)));
2460 Set_Pragma_Argument_Associations
(N
, A
);
2463 -- Process the arguments of the pragma
2466 Assoc
:= First
(Pragma_Argument_Associations
(N
));
2467 while Present
(Assoc
) loop
2468 -- The back end may need to take the address of the object
2470 Set_Address_Taken
(Entity
(Expression
(Assoc
)));
2472 -- If any of the objects have a freeze node, it must appear before
2473 -- pragma Inspection_Point, otherwise the entity won't be elaborated
2474 -- when Gigi processes the pragma.
2476 if Has_Delayed_Freeze
(Entity
(Expression
(Assoc
)))
2477 and then not Is_Frozen
(Entity
(Expression
(Assoc
)))
2480 ("??inspection point references unfrozen object &",
2482 Entity
(Expression
(Assoc
)));
2489 -- When the above requirement isn't met, turn the pragma into a no-op
2492 Error_Msg_N
("\pragma will be ignored", N
);
2494 -- We can't just remove the pragma from the tree as it might be
2495 -- iterated over by the caller. Turn it into a null statement
2498 Rewrite
(N
, Make_Null_Statement
(Loc
));
2500 end Expand_Pragma_Inspection_Point
;
2502 --------------------------------------
2503 -- Expand_Pragma_Interrupt_Priority --
2504 --------------------------------------
2506 -- Supply default argument if none exists (System.Interrupt_Priority'Last)
2508 procedure Expand_Pragma_Interrupt_Priority
(N
: Node_Id
) is
2509 Loc
: constant Source_Ptr
:= Sloc
(N
);
2511 if No
(Pragma_Argument_Associations
(N
)) then
2512 Set_Pragma_Argument_Associations
(N
, New_List
(
2513 Make_Pragma_Argument_Association
(Loc
,
2515 Make_Attribute_Reference
(Loc
,
2517 New_Occurrence_Of
(RTE
(RE_Interrupt_Priority
), Loc
),
2518 Attribute_Name
=> Name_Last
))));
2520 end Expand_Pragma_Interrupt_Priority
;
2522 --------------------------------
2523 -- Expand_Pragma_Loop_Variant --
2524 --------------------------------
2526 -- Pragma Loop_Variant is expanded in the following manner:
2530 -- for | while ... loop
2531 -- <preceding source statements>
2532 -- pragma Loop_Variant
2533 -- (Increases => Incr_Expr,
2534 -- Decreases => Decr_Expr);
2535 -- <succeeding source statements>
2540 -- Curr_1 : <type of Incr_Expr>;
2541 -- Curr_2 : <type of Decr_Expr>;
2542 -- Old_1 : <type of Incr_Expr>;
2543 -- Old_2 : <type of Decr_Expr>;
2544 -- Flag : Boolean := False;
2546 -- for | while ... loop
2547 -- <preceding source statements>
2554 -- Curr_1 := <Incr_Expr>;
2555 -- Curr_2 := <Decr_Expr>;
2558 -- if Curr_1 /= Old_1 then
2559 -- pragma Check (Loop_Variant, Curr_1 > Old_1);
2561 -- pragma Check (Loop_Variant, Curr_2 < Old_2);
2567 -- <succeeding source statements>
2570 procedure Expand_Pragma_Loop_Variant
(N
: Node_Id
) is
2571 Loc
: constant Source_Ptr
:= Sloc
(N
);
2572 Last_Var
: constant Node_Id
:=
2573 Last
(Pragma_Argument_Associations
(N
));
2575 Curr_Assign
: List_Id
:= No_List
;
2576 Flag_Id
: Entity_Id
:= Empty
;
2577 If_Stmt
: Node_Id
:= Empty
;
2578 Old_Assign
: List_Id
:= No_List
;
2579 Loop_Scop
: Entity_Id
;
2580 Loop_Stmt
: Node_Id
;
2583 procedure Process_Variant
(Variant
: Node_Id
; Is_Last
: Boolean);
2584 -- Process a single increasing / decreasing termination variant. Flag
2585 -- Is_Last should be set when processing the last variant.
2587 ---------------------
2588 -- Process_Variant --
2589 ---------------------
2591 procedure Process_Variant
(Variant
: Node_Id
; Is_Last
: Boolean) is
2592 Expr
: constant Node_Id
:= Expression
(Variant
);
2593 Expr_Typ
: constant Entity_Id
:= Etype
(Expr
);
2594 Loc
: constant Source_Ptr
:= Sloc
(Expr
);
2595 Loop_Loc
: constant Source_Ptr
:= Sloc
(Loop_Stmt
);
2596 Curr_Id
: Entity_Id
;
2601 -- All temporaries generated in this routine must be inserted before
2602 -- the related loop statement. Ensure that the proper scope is on the
2603 -- stack when analyzing the temporaries. Note that we also use the
2604 -- Sloc of the related loop.
2606 Push_Scope
(Scope
(Loop_Scop
));
2608 -- Step 1: Create the declaration of the flag which controls the
2609 -- behavior of the assertion on the first iteration of the loop.
2611 if No
(Flag_Id
) then
2614 -- Flag : Boolean := False;
2616 Flag_Id
:= Make_Temporary
(Loop_Loc
, 'F');
2618 Insert_Action
(Loop_Stmt
,
2619 Make_Object_Declaration
(Loop_Loc
,
2620 Defining_Identifier
=> Flag_Id
,
2621 Object_Definition
=>
2622 New_Occurrence_Of
(Standard_Boolean
, Loop_Loc
),
2624 New_Occurrence_Of
(Standard_False
, Loop_Loc
)));
2626 -- Prevent an unwanted optimization where the Current_Value of
2627 -- the flag eliminates the if statement which stores the variant
2628 -- values coming from the previous iteration.
2630 -- Flag : Boolean := False;
2632 -- if Flag then -- condition rewritten to False
2633 -- Old_N := Curr_N; -- and if statement eliminated
2639 Set_Current_Value
(Flag_Id
, Empty
);
2642 -- Step 2: Create the temporaries which store the old and current
2643 -- values of the associated expression.
2646 -- Curr : <type of Expr>;
2648 Curr_Id
:= Make_Temporary
(Loc
, 'C');
2650 Insert_Action
(Loop_Stmt
,
2651 Make_Object_Declaration
(Loop_Loc
,
2652 Defining_Identifier
=> Curr_Id
,
2653 Object_Definition
=> New_Occurrence_Of
(Expr_Typ
, Loop_Loc
)));
2656 -- Old : <type of Expr>;
2658 Old_Id
:= Make_Temporary
(Loc
, 'P');
2660 Insert_Action
(Loop_Stmt
,
2661 Make_Object_Declaration
(Loop_Loc
,
2662 Defining_Identifier
=> Old_Id
,
2663 Object_Definition
=> New_Occurrence_Of
(Expr_Typ
, Loop_Loc
)));
2665 -- Restore original scope after all temporaries have been analyzed
2669 -- Step 3: Store value of the expression from the previous iteration
2674 Append_New_To
(Old_Assign
,
2675 Make_Assignment_Statement
(Loc
,
2676 Name
=> New_Occurrence_Of
(Old_Id
, Loc
),
2677 Expression
=> New_Occurrence_Of
(Curr_Id
, Loc
)));
2679 -- Step 4: Store the current value of the expression
2684 Append_New_To
(Curr_Assign
,
2685 Make_Assignment_Statement
(Loc
,
2686 Name
=> New_Occurrence_Of
(Curr_Id
, Loc
),
2687 Expression
=> Relocate_Node
(Expr
)));
2689 -- Step 5: Create corresponding assertion to verify change of value
2692 -- pragma Check (Loop_Variant, Curr <|> Old);
2696 Chars
=> Name_Check
,
2697 Pragma_Argument_Associations
=> New_List
(
2698 Make_Pragma_Argument_Association
(Loc
,
2699 Expression
=> Make_Identifier
(Loc
, Name_Loop_Variant
)),
2700 Make_Pragma_Argument_Association
(Loc
,
2702 Make_Variant_Comparison
(Loc
,
2703 Mode
=> Chars
(Variant
),
2705 Curr_Val
=> New_Occurrence_Of
(Curr_Id
, Loc
),
2706 Old_Val
=> New_Occurrence_Of
(Old_Id
, Loc
)))));
2709 -- if Curr /= Old then
2712 if No
(If_Stmt
) then
2714 -- When there is just one termination variant, do not compare the
2715 -- old and current value for equality, just check the pragma.
2721 Make_If_Statement
(Loc
,
2724 Left_Opnd
=> New_Occurrence_Of
(Curr_Id
, Loc
),
2725 Right_Opnd
=> New_Occurrence_Of
(Old_Id
, Loc
)),
2726 Then_Statements
=> New_List
(Prag
));
2735 Set_Else_Statements
(If_Stmt
, New_List
(Prag
));
2738 -- elsif Curr /= Old then
2742 if Elsif_Parts
(If_Stmt
) = No_List
then
2743 Set_Elsif_Parts
(If_Stmt
, New_List
);
2746 Append_To
(Elsif_Parts
(If_Stmt
),
2747 Make_Elsif_Part
(Loc
,
2750 Left_Opnd
=> New_Occurrence_Of
(Curr_Id
, Loc
),
2751 Right_Opnd
=> New_Occurrence_Of
(Old_Id
, Loc
)),
2752 Then_Statements
=> New_List
(Prag
)));
2754 end Process_Variant
;
2756 -- Start of processing for Expand_Pragma_Loop_Variant
2759 -- If pragma is not enabled, rewrite as Null statement. If pragma is
2760 -- disabled, it has already been rewritten as a Null statement.
2762 -- Likewise, ignore structural variants for execution.
2764 -- Also do this in CodePeer mode, because the expanded code is too
2765 -- complicated for CodePeer to analyse.
2768 or else Chars
(Last_Var
) = Name_Structural
2769 or else CodePeer_Mode
2771 Rewrite
(N
, Make_Null_Statement
(Loc
));
2776 -- The expansion of Loop_Variant is quite distributed as it produces
2777 -- various statements to capture and compare the arguments. To preserve
2778 -- the original context, set the Is_Assertion_Expr flag. This aids the
2779 -- Ghost legality checks when verifying the placement of a reference to
2782 In_Assertion_Expr
:= In_Assertion_Expr
+ 1;
2784 -- Locate the enclosing loop for which this assertion applies. In the
2785 -- case of Ada 2012 array iteration, we might be dealing with nested
2786 -- loops. Only the outermost loop has an identifier.
2789 while Present
(Loop_Stmt
) loop
2790 if Nkind
(Loop_Stmt
) = N_Loop_Statement
2791 and then Present
(Identifier
(Loop_Stmt
))
2796 Loop_Stmt
:= Parent
(Loop_Stmt
);
2799 Loop_Scop
:= Entity
(Identifier
(Loop_Stmt
));
2801 -- Create the circuitry which verifies individual variants
2803 Variant
:= First
(Pragma_Argument_Associations
(N
));
2804 while Present
(Variant
) loop
2805 Process_Variant
(Variant
, Is_Last
=> Variant
= Last_Var
);
2809 -- Construct the segment which stores the old values of all expressions.
2816 Make_If_Statement
(Loc
,
2817 Condition
=> New_Occurrence_Of
(Flag_Id
, Loc
),
2818 Then_Statements
=> Old_Assign
));
2820 -- Update the values of all expressions
2822 Insert_Actions
(N
, Curr_Assign
);
2824 -- Add the assertion circuitry to test all changes in expressions.
2833 Make_If_Statement
(Loc
,
2834 Condition
=> New_Occurrence_Of
(Flag_Id
, Loc
),
2835 Then_Statements
=> New_List
(If_Stmt
),
2836 Else_Statements
=> New_List
(
2837 Make_Assignment_Statement
(Loc
,
2838 Name
=> New_Occurrence_Of
(Flag_Id
, Loc
),
2839 Expression
=> New_Occurrence_Of
(Standard_True
, Loc
)))));
2841 -- Note: the pragma has been completely transformed into a sequence of
2842 -- corresponding declarations and statements. We leave it in the tree
2843 -- for documentation purposes. It will be ignored by the backend.
2845 In_Assertion_Expr
:= In_Assertion_Expr
- 1;
2846 end Expand_Pragma_Loop_Variant
;
2848 --------------------------------
2849 -- Expand_Pragma_Psect_Object --
2850 --------------------------------
2852 -- Convert to Common_Object, and expand the resulting pragma
2854 procedure Expand_Pragma_Psect_Object
(N
: Node_Id
)
2855 renames Expand_Pragma_Common_Object
;
2857 -------------------------------------
2858 -- Expand_Pragma_Relative_Deadline --
2859 -------------------------------------
2861 procedure Expand_Pragma_Relative_Deadline
(N
: Node_Id
) is
2862 P
: constant Node_Id
:= Parent
(N
);
2863 Loc
: constant Source_Ptr
:= Sloc
(N
);
2866 -- Expand the pragma only in the case of the main subprogram. For tasks
2867 -- the expansion is done in exp_ch9. Generate a call to Set_Deadline
2868 -- at Clock plus the relative deadline specified in the pragma. Time
2869 -- values are translated into Duration to allow for non-private
2870 -- addition operation.
2872 if Nkind
(P
) = N_Subprogram_Body
then
2875 Make_Procedure_Call_Statement
(Loc
,
2876 Name
=> New_Occurrence_Of
(RTE
(RE_Set_Deadline
), Loc
),
2877 Parameter_Associations
=> New_List
(
2878 Unchecked_Convert_To
(RTE
(RO_RT_Time
),
2881 Make_Function_Call
(Loc
,
2882 New_Occurrence_Of
(RTE
(RO_RT_To_Duration
), Loc
),
2885 (Loc
, New_Occurrence_Of
(RTE
(RE_Clock
), Loc
)))),
2887 Unchecked_Convert_To
(
2893 end Expand_Pragma_Relative_Deadline
;
2895 --------------------------------------
2896 -- Expand_Pragma_Subprogram_Variant --
2897 --------------------------------------
2899 -- Aspect Subprogram_Variant is expanded in the following manner:
2903 -- procedure Proc (Param : T) with
2904 -- with Variant (Increases => Incr_Expr,
2905 -- Decreases => Decr_Expr)
2908 -- <source statements>
2909 -- Proc (New_Param_Value);
2914 -- procedure Proc (Param : T) is
2915 -- Old_Incr : constant <type of Incr_Expr> := <Incr_Expr>;
2916 -- Old_Decr : constant <type of Decr_Expr> := <Decr_Expr> ;
2918 -- procedure Variants (Param : T);
2920 -- procedure Variants (Param : T) is
2921 -- Curr_Incr : constant <type of Incr_Expr> := <Incr_Expr>;
2922 -- Curr_Decr : constant <type of Decr_Expr> := <Decr_Expr>;
2924 -- if Curr_Incr /= Old_Incr then
2925 -- pragma Check (Variant, Curr_Incr > Old_Incr);
2927 -- pragma Check (Variant, Curr_Decr < Old_Decr);
2933 -- <source statements>
2934 -- Variants (New_Param_Value);
2935 -- Proc (New_Param_Value);
2938 procedure Expand_Pragma_Subprogram_Variant
2940 Subp_Id
: Entity_Id
;
2941 Body_Decls
: List_Id
)
2943 Curr_Decls
: List_Id
;
2944 If_Stmt
: Node_Id
:= Empty
;
2946 function Formal_Param_Map
2947 (Old_Subp
: Entity_Id
;
2948 New_Subp
: Entity_Id
) return Elist_Id
;
2949 -- Given two subprogram entities Old_Subp and New_Subp with the same
2950 -- number of formal parameters return a list of the form:
2958 -- as required by New_Copy_Tree to replace references to formal
2959 -- parameters of Old_Subp with references to formal parameters of
2962 procedure Process_Variant
2964 Formal_Map
: Elist_Id
;
2965 Prev_Decl
: in out Node_Id
;
2967 -- Process a single increasing / decreasing termination variant given by
2968 -- a component association Variant. Formal_Map is a list of formal
2969 -- parameters of the annotated subprogram and of the internal procedure
2970 -- that verifies the variant in the format required by New_Copy_Tree.
2971 -- The Old_... object created by this routine will be appended after
2972 -- Prev_Decl and is stored in this parameter for a next call to this
2973 -- routine. Is_Last is True when there are no more variants to process.
2975 ----------------------
2976 -- Formal_Param_Map --
2977 ----------------------
2979 function Formal_Param_Map
2980 (Old_Subp
: Entity_Id
;
2981 New_Subp
: Entity_Id
) return Elist_Id
2983 Old_Formal
: Entity_Id
:= First_Formal
(Old_Subp
);
2984 New_Formal
: Entity_Id
:= First_Formal
(New_Subp
);
2986 Param_Map
: Elist_Id
;
2988 if Present
(Old_Formal
) then
2989 Param_Map
:= New_Elmt_List
;
2990 while Present
(Old_Formal
) and then Present
(New_Formal
) loop
2991 Append_Elmt
(Old_Formal
, Param_Map
);
2992 Append_Elmt
(New_Formal
, Param_Map
);
2994 Next_Formal
(Old_Formal
);
2995 Next_Formal
(New_Formal
);
3002 end Formal_Param_Map
;
3004 ---------------------
3005 -- Process_Variant --
3006 ---------------------
3008 procedure Process_Variant
3010 Formal_Map
: Elist_Id
;
3011 Prev_Decl
: in out Node_Id
;
3014 Expr
: constant Node_Id
:= Expression
(Variant
);
3015 Expr_Typ
: constant Entity_Id
:= Etype
(Expr
);
3016 Loc
: constant Source_Ptr
:= Sloc
(Expr
);
3020 Curr_Id
: Entity_Id
;
3021 Curr_Decl
: Node_Id
;
3025 -- Create temporaries that store the old values of the associated
3029 -- Old : constant <type of Expr> := <Expr>;
3031 Old_Id
:= Make_Temporary
(Loc
, 'P');
3034 Make_Object_Declaration
(Loc
,
3035 Defining_Identifier
=> Old_Id
,
3036 Constant_Present
=> True,
3037 Object_Definition
=> New_Occurrence_Of
(Expr_Typ
, Loc
),
3038 Expression
=> New_Copy_Tree
(Expr
));
3040 Insert_After_And_Analyze
(Prev_Decl
, Old_Decl
);
3042 Prev_Decl
:= Old_Decl
;
3045 -- Curr : constant <type of Expr> := <Expr>;
3047 Curr_Id
:= Make_Temporary
(Loc
, 'C');
3050 Make_Object_Declaration
(Loc
,
3051 Defining_Identifier
=> Curr_Id
,
3052 Constant_Present
=> True,
3053 Object_Definition
=> New_Occurrence_Of
(Expr_Typ
, Loc
),
3055 New_Copy_Tree
(Expr
, Map
=> Formal_Map
));
3057 Append
(Curr_Decl
, Curr_Decls
);
3060 -- pragma Check (Variant, Curr <|> Old);
3064 Chars
=> Name_Check
,
3065 Pragma_Argument_Associations
=> New_List
(
3066 Make_Pragma_Argument_Association
(Loc
,
3068 Make_Identifier
(Loc
,
3069 Name_Subprogram_Variant
)),
3070 Make_Pragma_Argument_Association
(Loc
,
3072 Make_Variant_Comparison
(Loc
,
3073 Mode
=> Chars
(First
(Choices
(Variant
))),
3075 Curr_Val
=> New_Occurrence_Of
(Curr_Id
, Loc
),
3076 Old_Val
=> New_Occurrence_Of
(Old_Id
, Loc
)))));
3079 -- if Curr /= Old then
3082 if No
(If_Stmt
) then
3084 -- When there is just one termination variant, do not compare
3085 -- the old and current value for equality, just check the
3092 Make_If_Statement
(Loc
,
3095 Left_Opnd
=> New_Occurrence_Of
(Curr_Id
, Loc
),
3096 Right_Opnd
=> New_Occurrence_Of
(Old_Id
, Loc
)),
3097 Then_Statements
=> New_List
(Prag
));
3106 Set_Else_Statements
(If_Stmt
, New_List
(Prag
));
3109 -- elsif Curr /= Old then
3113 if Elsif_Parts
(If_Stmt
) = No_List
then
3114 Set_Elsif_Parts
(If_Stmt
, New_List
);
3117 Append_To
(Elsif_Parts
(If_Stmt
),
3118 Make_Elsif_Part
(Loc
,
3121 Left_Opnd
=> New_Occurrence_Of
(Curr_Id
, Loc
),
3122 Right_Opnd
=> New_Occurrence_Of
(Old_Id
, Loc
)),
3123 Then_Statements
=> New_List
(Prag
)));
3125 end Process_Variant
;
3129 Loc
: constant Source_Ptr
:= Sloc
(Prag
);
3131 Aggr
: constant Node_Id
:=
3132 Expression
(First
(Pragma_Argument_Associations
(Prag
)));
3133 Formal_Map
: Elist_Id
;
3135 Last_Variant
: constant Node_Id
:=
3136 Nlists
.Last
(Component_Associations
(Aggr
));
3138 Proc_Decl
: Node_Id
;
3139 Proc_Id
: Entity_Id
;
3140 Proc_Spec
: Node_Id
;
3144 -- Do nothing if pragma is not present or is disabled.
3145 -- Also ignore structural variants for execution.
3147 if Is_Ignored
(Prag
)
3148 or else Chars
(Nlists
.Last
(Choices
(Last_Variant
))) = Name_Structural
3153 -- The expansion of Subprogram Variant is quite distributed as it
3154 -- produces various statements to capture and compare the arguments.
3155 -- To preserve the original context, set the Is_Assertion_Expr flag.
3156 -- This aids the Ghost legality checks when verifying the placement
3157 -- of a reference to a Ghost entity.
3159 In_Assertion_Expr
:= In_Assertion_Expr
+ 1;
3161 -- Create declaration of the procedure that compares values of the
3162 -- variant expressions captured at the start of subprogram with their
3163 -- values at the recursive call of the subprogram.
3165 Proc_Id
:= Make_Defining_Identifier
(Loc
, Name_uVariants
);
3168 Make_Procedure_Specification
3170 Defining_Unit_Name
=> Proc_Id
,
3171 Parameter_Specifications
=> Copy_Parameter_List
(Subp_Id
));
3174 Make_Subprogram_Declaration
(Loc
, Proc_Spec
);
3176 Insert_Before_First_Source_Declaration
(Proc_Decl
, Body_Decls
);
3177 Analyze
(Proc_Decl
);
3179 -- Create a mapping between formals of the annotated subprogram (which
3180 -- are used to compute values of the variant expression at the start of
3181 -- subprogram) and formals of the internal procedure (which are used to
3182 -- compute values of of the variant expression at the recursive call).
3185 Formal_Param_Map
(Old_Subp
=> Subp_Id
, New_Subp
=> Proc_Id
);
3187 -- Process invidual increasing / decreasing variants
3190 Curr_Decls
:= New_List
;
3192 Variant
:= First
(Component_Associations
(Aggr
));
3193 while Present
(Variant
) loop
3195 (Variant
=> Variant
,
3196 Formal_Map
=> Formal_Map
,
3198 Is_Last
=> Variant
= Last_Variant
);
3202 -- Create a subprogram body with declarations of objects that capture
3203 -- the current values of variant expressions at a recursive call and an
3204 -- if-then-else statement that compares current with old values.
3207 Make_Subprogram_Body
(Loc
,
3209 Copy_Subprogram_Spec
(Proc_Spec
),
3210 Declarations
=> Curr_Decls
,
3211 Handled_Statement_Sequence
=>
3212 Make_Handled_Sequence_Of_Statements
(Loc
,
3213 Statements
=> New_List
(If_Stmt
),
3214 End_Label
=> Make_Identifier
(Loc
, Chars
(Proc_Id
))));
3216 Insert_After_And_Analyze
(Last
, Proc_Bod
);
3218 -- Restore assertion context
3220 In_Assertion_Expr
:= In_Assertion_Expr
- 1;
3222 -- Rewrite the aspect expression, which is no longer needed, with
3223 -- a reference to the procedure that has just been created. We will
3224 -- generate a call to this procedure at each recursive call of the
3225 -- subprogram that has been annotated with Subprogram_Variant.
3227 Rewrite
(Aggr
, New_Occurrence_Of
(Proc_Id
, Loc
));
3228 end Expand_Pragma_Subprogram_Variant
;
3230 -------------------------------------------
3231 -- Expand_Pragma_Suppress_Initialization --
3232 -------------------------------------------
3234 procedure Expand_Pragma_Suppress_Initialization
(N
: Node_Id
) is
3235 Def_Id
: constant Entity_Id
:= Entity
(Arg_N
(N
, 1));
3238 -- Variable case (we have to undo any initialization already done)
3240 if Ekind
(Def_Id
) = E_Variable
then
3241 Undo_Initialization
(Def_Id
, N
);
3243 end Expand_Pragma_Suppress_Initialization
;
3245 -------------------------
3246 -- Undo_Initialization --
3247 -------------------------
3249 procedure Undo_Initialization
(Def_Id
: Entity_Id
; N
: Node_Id
) is
3250 Init_Call
: Node_Id
;
3253 -- When applied to a variable, the default initialization must not be
3254 -- done. As it is already done when the pragma is found, we just get rid
3255 -- of the call to the initialization procedure which followed the object
3256 -- declaration. The call is inserted after the declaration, but validity
3257 -- checks may also have been inserted and thus the initialization call
3258 -- does not necessarily appear immediately after the object declaration.
3260 -- We can't use the freezing mechanism for this purpose, since we have
3261 -- to elaborate the initialization expression when it is first seen (so
3262 -- this elaboration cannot be deferred to the freeze point).
3264 -- Find and remove generated initialization call for object, if any
3266 Init_Call
:= Remove_Init_Call
(Def_Id
, Rep_Clause
=> N
);
3268 -- Any default initialization expression should be removed (e.g.
3269 -- null defaults for access objects, zero initialization of packed
3270 -- bit arrays). Imported objects aren't allowed to have explicit
3271 -- initialization, so the expression must have been generated by
3274 if No
(Init_Call
) and then Present
(Expression
(Parent
(Def_Id
))) then
3275 Set_Expression
(Parent
(Def_Id
), Empty
);
3278 -- The object may not have any initialization, but in the presence of
3279 -- Initialize_Scalars code is inserted after then declaration, which
3280 -- must now be removed as well. The code carries the same source
3281 -- location as the declaration itself.
3283 if Initialize_Scalars
and then Is_Array_Type
(Etype
(Def_Id
)) then
3288 Init
:= Next
(Parent
(Def_Id
));
3289 while not Comes_From_Source
(Init
)
3290 and then Sloc
(Init
) = Sloc
(Def_Id
)
3298 end Undo_Initialization
;