Fix typo in t-dimode
[official-gcc.git] / gcc / ada / exp_prag.adb
blobf0b4b0b93cae68d176fe101f25707a437a570d5c
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-2021, 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 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 Expander; use Expander;
38 with Inline; use Inline;
39 with Lib; use Lib;
40 with Namet; use Namet;
41 with Nlists; use Nlists;
42 with Nmake; use Nmake;
43 with Opt; use Opt;
44 with Restrict; use Restrict;
45 with Rident; use Rident;
46 with Rtsfind; use Rtsfind;
47 with Sem; use Sem;
48 with Sem_Aux; use Sem_Aux;
49 with Sem_Ch8; use Sem_Ch8;
50 with Sem_Prag; use Sem_Prag;
51 with Sem_Util; use Sem_Util;
52 with Sinfo; use Sinfo;
53 with Sinfo.Nodes; use Sinfo.Nodes;
54 with Sinfo.Utils; use Sinfo.Utils;
55 with Sinput; use Sinput;
56 with Snames; use Snames;
57 with Stringt; use Stringt;
58 with Stand; use Stand;
59 with Tbuild; use Tbuild;
60 with Uintp; use Uintp;
61 with Validsw; use Validsw;
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.
91 -----------
92 -- Arg_N --
93 -----------
95 function Arg_N (N : Node_Id; Arg_Number : Positive) return Node_Id is
96 Arg : Node_Id := First (Pragma_Argument_Associations (N));
97 begin
98 if No (Arg) then
99 return Empty;
100 end if;
102 for J in 2 .. Arg_Number loop
103 Next (Arg);
104 if No (Arg) then
105 return Empty;
106 end if;
107 end loop;
109 if Present (Arg)
110 and then Nkind (Arg) = N_Pragma_Argument_Association
111 then
112 return Expression (Arg);
113 else
114 return Arg;
115 end if;
116 end Arg_N;
118 ---------------------
119 -- Expand_N_Pragma --
120 ---------------------
122 procedure Expand_N_Pragma (N : Node_Id) is
123 Pname : constant Name_Id := Pragma_Name (N);
124 Prag_Id : constant Pragma_Id := Get_Pragma_Id (Pname);
126 begin
127 -- Suppress the expansion of an ignored assertion pragma. Such a pragma
128 -- should not be transformed into a null statment because:
130 -- * The pragma may be part of the rep item chain of a type, in which
131 -- case rewriting it will destroy the chain.
133 -- * The analysis of the pragma may involve two parts (see routines
134 -- Analyze_xxx_In_Decl_Part). The second part of the analysis will
135 -- not happen if the pragma is rewritten.
137 if Assertion_Expression_Pragma (Prag_Id) and then Is_Ignored (N) then
138 return;
140 -- Rewrite the pragma into a null statement when it is ignored using
141 -- pragma Ignore_Pragma, or denotes Default_Scalar_Storage_Order and
142 -- compilation switch -gnatI is in effect.
144 elsif Should_Ignore_Pragma_Sem (N)
145 or else (Prag_Id = Pragma_Default_Scalar_Storage_Order
146 and then Ignore_Rep_Clauses)
147 then
148 Rewrite (N, Make_Null_Statement (Sloc (N)));
149 return;
150 end if;
152 case Prag_Id is
154 -- Pragmas requiring special expander action
156 when Pragma_Abort_Defer =>
157 Expand_Pragma_Abort_Defer (N);
159 when Pragma_Check =>
160 Expand_Pragma_Check (N);
162 when Pragma_Common_Object =>
163 Expand_Pragma_Common_Object (N);
165 when Pragma_CUDA_Execute =>
166 Expand_Pragma_CUDA_Execute (N);
168 when Pragma_Import =>
169 Expand_Pragma_Import_Or_Interface (N);
171 when Pragma_Inspection_Point =>
172 Expand_Pragma_Inspection_Point (N);
174 when Pragma_Interface =>
175 Expand_Pragma_Import_Or_Interface (N);
177 when Pragma_Interrupt_Priority =>
178 Expand_Pragma_Interrupt_Priority (N);
180 when Pragma_Loop_Variant =>
181 Expand_Pragma_Loop_Variant (N);
183 when Pragma_Psect_Object =>
184 Expand_Pragma_Psect_Object (N);
186 when Pragma_Relative_Deadline =>
187 Expand_Pragma_Relative_Deadline (N);
189 when Pragma_Suppress_Initialization =>
190 Expand_Pragma_Suppress_Initialization (N);
192 -- All other pragmas need no expander action (includes
193 -- Unknown_Pragma).
195 when others => null;
196 end case;
197 end Expand_N_Pragma;
199 -------------------------------
200 -- Expand_Pragma_Abort_Defer --
201 -------------------------------
203 -- An Abort_Defer pragma appears as the first statement in a handled
204 -- statement sequence (right after the begin). It defers aborts for
205 -- the entire statement sequence, but not for any declarations or
206 -- handlers (if any) associated with this statement sequence.
208 -- The transformation is to transform
210 -- pragma Abort_Defer;
211 -- statements;
213 -- into
215 -- begin
216 -- Abort_Defer.all;
217 -- statements
218 -- exception
219 -- when all others =>
220 -- Abort_Undefer.all;
221 -- raise;
222 -- at end
223 -- Abort_Undefer_Direct;
224 -- end;
226 procedure Expand_Pragma_Abort_Defer (N : Node_Id) is
227 begin
228 -- Abort_Defer has no useful effect if Abort's are not allowed
230 if not Abort_Allowed then
231 return;
232 end if;
234 -- Normal case where abort is possible
236 declare
237 Loc : constant Source_Ptr := Sloc (N);
238 Stm : Node_Id;
239 Stms : List_Id;
240 HSS : Node_Id;
241 Blk : constant Entity_Id :=
242 New_Internal_Entity (E_Block, Current_Scope, Sloc (N), 'B');
243 AUD : constant Entity_Id := RTE (RE_Abort_Undefer_Direct);
245 begin
246 Stms := New_List (Build_Runtime_Call (Loc, RE_Abort_Defer));
247 loop
248 Stm := Remove_Next (N);
249 exit when No (Stm);
250 Append (Stm, Stms);
251 end loop;
253 HSS :=
254 Make_Handled_Sequence_Of_Statements (Loc,
255 Statements => Stms,
256 At_End_Proc => New_Occurrence_Of (AUD, Loc));
258 -- Present the Abort_Undefer_Direct function to the backend so that
259 -- it can inline the call to the function.
261 Add_Inlined_Body (AUD, N);
263 Rewrite (N,
264 Make_Block_Statement (Loc, Handled_Statement_Sequence => HSS));
266 Set_Scope (Blk, Current_Scope);
267 Set_Etype (Blk, Standard_Void_Type);
268 Set_Identifier (N, New_Occurrence_Of (Blk, Sloc (N)));
269 Expand_At_End_Handler (HSS, Blk);
270 Analyze (N);
271 end;
272 end Expand_Pragma_Abort_Defer;
274 --------------------------
275 -- Expand_Pragma_Check --
276 --------------------------
278 procedure Expand_Pragma_Check (N : Node_Id) is
279 Cond : constant Node_Id := Arg_N (N, 2);
280 Nam : constant Name_Id := Chars (Arg_N (N, 1));
281 Msg : Node_Id;
283 Loc : constant Source_Ptr := Sloc (First_Node (Cond));
284 -- Source location used in the case of a failed assertion: point to the
285 -- failing condition, not Loc. Note that the source location of the
286 -- expression is not usually the best choice here, because it points to
287 -- the location of the topmost tree node, which may be an operator in
288 -- the middle of the source text of the expression. For example, it gets
289 -- located on the last AND keyword in a chain of boolean expressiond
290 -- AND'ed together. It is best to put the message on the first character
291 -- of the condition, which is the effect of the First_Node call here.
292 -- This source location is used to build the default exception message,
293 -- and also as the sloc of the call to the runtime subprogram raising
294 -- Assert_Failure, so that coverage analysis tools can relate the
295 -- call to the failed check.
297 procedure Replace_Discriminals_Of_Protected_Op (Expr : Node_Id);
298 -- Discriminants of the enclosing protected object may be referenced
299 -- in the expression of a precondition of a protected operation.
300 -- In the body of the operation these references must be replaced by
301 -- the discriminal created for them, which are renamings of the
302 -- discriminants of the object that is the target of the operation.
303 -- This replacement is done by visibility when the references appear
304 -- in the subprogram body, but in the case of a condition which appears
305 -- on the specification of the subprogram it has be done separately
306 -- because the condition has been replaced by a Check pragma and
307 -- analyzed earlier, before the creation of the discriminal renaming
308 -- declarations that are added to the subprogram body.
310 ------------------------------------------
311 -- Replace_Discriminals_Of_Protected_Op --
312 ------------------------------------------
314 procedure Replace_Discriminals_Of_Protected_Op (Expr : Node_Id) is
315 function Find_Corresponding_Discriminal
316 (E : Entity_Id) return Entity_Id;
317 -- Find the local entity that renames a discriminant of the enclosing
318 -- protected type, and has a matching name.
320 function Replace_Discr_Ref (N : Node_Id) return Traverse_Result;
321 -- Replace a reference to a discriminant of the original protected
322 -- type by the local renaming declaration of the discriminant of
323 -- the target object.
325 ------------------------------------
326 -- Find_Corresponding_Discriminal --
327 ------------------------------------
329 function Find_Corresponding_Discriminal
330 (E : Entity_Id) return Entity_Id
332 R : Entity_Id;
334 begin
335 R := First_Entity (Current_Scope);
337 while Present (R) loop
338 if Nkind (Parent (R)) = N_Object_Renaming_Declaration
339 and then Present (Discriminal_Link (R))
340 and then Chars (Discriminal_Link (R)) = Chars (E)
341 then
342 return R;
343 end if;
345 Next_Entity (R);
346 end loop;
348 return Empty;
349 end Find_Corresponding_Discriminal;
351 -----------------------
352 -- Replace_Discr_Ref --
353 -----------------------
355 function Replace_Discr_Ref (N : Node_Id) return Traverse_Result is
356 R : Entity_Id;
358 begin
359 if Is_Entity_Name (N)
360 and then Present (Discriminal_Link (Entity (N)))
361 then
362 R := Find_Corresponding_Discriminal (Entity (N));
363 Rewrite (N, New_Occurrence_Of (R, Sloc (N)));
364 end if;
366 return OK;
367 end Replace_Discr_Ref;
369 procedure Replace_Discriminant_References is
370 new Traverse_Proc (Replace_Discr_Ref);
372 -- Start of processing for Replace_Discriminals_Of_Protected_Op
374 begin
375 Replace_Discriminant_References (Expr);
376 end Replace_Discriminals_Of_Protected_Op;
378 -- Start of processing for Expand_Pragma_Check
380 begin
381 -- Nothing to do if pragma is ignored
383 if Is_Ignored (N) then
384 return;
385 end if;
387 -- Since this check is active, rewrite the pragma into a corresponding
388 -- if statement, and then analyze the statement.
390 -- The normal case expansion transforms:
392 -- pragma Check (name, condition [,message]);
394 -- into
396 -- if not condition then
397 -- System.Assertions.Raise_Assert_Failure (Str);
398 -- end if;
400 -- where Str is the message if one is present, or the default of
401 -- name failed at file:line if no message is given (the "name failed
402 -- at" is omitted for name = Assertion, since it is redundant, given
403 -- that the name of the exception is Assert_Failure.)
405 -- Also, instead of "XXX failed at", we generate slightly
406 -- different messages for some of the contract assertions (see
407 -- code below for details).
409 -- An alternative expansion is used when the No_Exception_Propagation
410 -- restriction is active and there is a local Assert_Failure handler.
411 -- This is not a common combination of circumstances, but it occurs in
412 -- the context of Aunit and the zero footprint profile. In this case we
413 -- generate:
415 -- if not condition then
416 -- raise Assert_Failure;
417 -- end if;
419 -- This will then be transformed into a goto, and the local handler will
420 -- be able to handle the assert error (which would not be the case if a
421 -- call is made to the Raise_Assert_Failure procedure).
423 -- We also generate the direct raise if the Suppress_Exception_Locations
424 -- is active, since we don't want to generate messages in this case.
426 -- Note that the reason we do not always generate a direct raise is that
427 -- the form in which the procedure is called allows for more efficient
428 -- breakpointing of assertion errors.
430 -- Generate the appropriate if statement. Note that we consider this to
431 -- be an explicit conditional in the source, not an implicit if, so we
432 -- do not call Make_Implicit_If_Statement. Note also that we wrap the
433 -- raise statement in a block statement so that, if the condition is
434 -- evaluated at compile time to False, then the rewriting of the if
435 -- statement will not involve the raise but the block statement, and
436 -- thus not leave a dangling reference to the raise statement in the
437 -- Local_Raise_Statements list of the handler.
439 -- Case where we generate a direct raise
441 if ((Debug_Flag_Dot_G
442 or else Restriction_Active (No_Exception_Propagation))
443 and then Present (Find_Local_Handler (RTE (RE_Assert_Failure), N)))
444 or else (Opt.Exception_Locations_Suppressed and then No (Arg_N (N, 3)))
445 then
446 Rewrite (N,
447 Make_If_Statement (Loc,
448 Condition => Make_Op_Not (Loc, Right_Opnd => Cond),
449 Then_Statements => New_List (
450 Make_Block_Statement (Loc,
451 Handled_Statement_Sequence =>
452 Make_Handled_Sequence_Of_Statements (Loc,
453 Statements => New_List (
454 Make_Raise_Statement (Loc,
455 Name =>
456 New_Occurrence_Of (RTE (RE_Assert_Failure),
457 Loc))))))));
459 -- Case where we call the procedure
461 else
462 -- If we have a message given, use it
464 if Present (Arg_N (N, 3)) then
465 Msg := Get_Pragma_Arg (Arg_N (N, 3));
467 -- Here we have no string, so prepare one
469 else
470 declare
471 Loc_Str : constant String := Build_Location_String (Loc);
473 begin
474 Name_Len := 0;
476 -- For Assert, we just use the location
478 if Nam = Name_Assert then
479 null;
481 -- For predicate, we generate the string "predicate failed at
482 -- yyy". We prefer all lower case for predicate.
484 elsif Nam = Name_Predicate then
485 Add_Str_To_Name_Buffer ("predicate failed at ");
487 -- For special case of Precondition/Postcondition the string is
488 -- "failed xx from yy" where xx is precondition/postcondition
489 -- in all lower case. The reason for this different wording is
490 -- that the failure is not at the point of occurrence of the
491 -- pragma, unlike the other Check cases.
493 elsif Nam in Name_Precondition | Name_Postcondition then
494 Get_Name_String (Nam);
495 Insert_Str_In_Name_Buffer ("failed ", 1);
496 Add_Str_To_Name_Buffer (" from ");
498 -- For special case of Invariant, the string is "failed
499 -- invariant from yy", to be consistent with the string that is
500 -- generated for the aspect case (the code later on checks for
501 -- this specific string to modify it in some cases, so this is
502 -- functionally important).
504 elsif Nam = Name_Invariant then
505 Add_Str_To_Name_Buffer ("failed invariant from ");
507 -- For all other checks, the string is "xxx failed at yyy"
508 -- where xxx is the check name with appropriate casing.
510 else
511 Get_Name_String (Nam);
512 Set_Casing
513 (Identifier_Casing (Source_Index (Current_Sem_Unit)));
514 Add_Str_To_Name_Buffer (" failed at ");
515 end if;
517 -- In all cases, add location string
519 Add_Str_To_Name_Buffer (Loc_Str);
521 -- Build the message
523 Msg := Make_String_Literal (Loc, Name_Buffer (1 .. Name_Len));
524 end;
525 end if;
527 -- For a precondition, replace references to discriminants of a
528 -- protected type with the local discriminals.
530 if Is_Protected_Type (Scope (Current_Scope))
531 and then Has_Discriminants (Scope (Current_Scope))
532 and then From_Aspect_Specification (N)
533 then
534 Replace_Discriminals_Of_Protected_Op (Cond);
535 end if;
537 -- Now rewrite as an if statement
539 Rewrite (N,
540 Make_If_Statement (Loc,
541 Condition => Make_Op_Not (Loc, Right_Opnd => Cond),
542 Then_Statements => New_List (
543 Make_Procedure_Call_Statement (Loc,
544 Name =>
545 New_Occurrence_Of (RTE (RE_Raise_Assert_Failure), Loc),
546 Parameter_Associations => New_List (Relocate_Node (Msg))))));
547 end if;
549 Analyze (N);
551 -- If new condition is always false, give a warning
553 if Warn_On_Assertion_Failure
554 and then Nkind (N) = N_Procedure_Call_Statement
555 and then Is_RTE (Entity (Name (N)), RE_Raise_Assert_Failure)
556 then
557 -- If original condition was a Standard.False, we assume that this is
558 -- indeed intended to raise assert error and no warning is required.
560 if Is_Entity_Name (Original_Node (Cond))
561 and then Entity (Original_Node (Cond)) = Standard_False
562 then
563 null;
565 elsif Nam = Name_Assert then
566 Error_Msg_N ("?.a?assertion will fail at run time", N);
567 else
568 Error_Msg_N ("?.a?check will fail at run time", N);
569 end if;
570 end if;
571 end Expand_Pragma_Check;
573 ---------------------------------
574 -- Expand_Pragma_Common_Object --
575 ---------------------------------
577 -- Use a machine attribute to replicate semantic effect in DEC Ada
579 -- pragma Machine_Attribute (intern_name, "common_object", extern_name);
581 -- For now we do nothing with the size attribute ???
583 -- Note: Psect_Object shares this processing
585 procedure Expand_Pragma_Common_Object (N : Node_Id) is
586 Loc : constant Source_Ptr := Sloc (N);
588 Internal : constant Node_Id := Arg_N (N, 1);
589 External : constant Node_Id := Arg_N (N, 2);
591 Psect : Node_Id;
592 -- Psect value upper cased as string literal
594 Iloc : constant Source_Ptr := Sloc (Internal);
595 Eloc : constant Source_Ptr := Sloc (External);
596 Ploc : Source_Ptr;
598 begin
599 -- Acquire Psect value and fold to upper case
601 if Present (External) then
602 if Nkind (External) = N_String_Literal then
603 String_To_Name_Buffer (Strval (External));
604 else
605 Get_Name_String (Chars (External));
606 end if;
608 Set_All_Upper_Case;
610 Psect :=
611 Make_String_Literal (Eloc, Strval => String_From_Name_Buffer);
613 else
614 Get_Name_String (Chars (Internal));
615 Set_All_Upper_Case;
616 Psect :=
617 Make_String_Literal (Iloc, Strval => String_From_Name_Buffer);
618 end if;
620 Ploc := Sloc (Psect);
622 -- Insert the pragma
624 Insert_After_And_Analyze (N,
625 Make_Pragma (Loc,
626 Chars => Name_Machine_Attribute,
627 Pragma_Argument_Associations => New_List (
628 Make_Pragma_Argument_Association (Iloc,
629 Expression => New_Copy_Tree (Internal)),
630 Make_Pragma_Argument_Association (Eloc,
631 Expression =>
632 Make_String_Literal (Sloc => Ploc, Strval => "common_object")),
633 Make_Pragma_Argument_Association (Ploc,
634 Expression => New_Copy_Tree (Psect)))));
635 end Expand_Pragma_Common_Object;
637 --------------------------------
638 -- Expand_Pragma_CUDA_Execute --
639 --------------------------------
641 -- Pragma CUDA_Execute is expanded in the following manner:
643 -- Original Code
645 -- pragma CUDA_Execute (My_Proc (X, Y), Blocks, Grids, Mem, Stream)
647 -- Expanded Code
649 -- declare
650 -- Blocks_Id : CUDA.Vector_Types.Dim3 := Blocks;
651 -- Grids_Id : CUDA.Vector_Types.Dim3 := Grids;
652 -- Mem_Id : Integer := <Mem or 0>;
653 -- Stream_Id : CUDA.Driver_Types.Stream_T := <Stream or null>;
654 -- X_Id : <Type of X> := X;
655 -- Y_Id : <Type of Y> := Y;
656 -- Arg_Id : Array (1..2) of System.Address :=
657 -- (X'Address,_Id Y'Address);_Id
658 -- begin
659 -- CUDA.Internal.Push_Call_Configuration (
660 -- Grids_Id,
661 -- Blocks_Id,
662 -- Mem_Id,
663 -- Stream_Id);
664 -- CUDA.Internal.Pop_Call_Configuration (
665 -- Grids_Id'address,
666 -- Blocks_Id'address,
667 -- Mem_Id'address,
668 -- Stream_Id'address),
669 -- CUDA.Runtime_Api.Launch_Kernel (
670 -- My_Proc'Address,
671 -- Blocks_Id,
672 -- Grids_Id,
673 -- Arg_Id'Address,
674 -- Mem_Id,
675 -- Stream_Id);
676 -- end;
678 procedure Expand_Pragma_CUDA_Execute (N : Node_Id) is
680 Loc : constant Source_Ptr := Sloc (N);
682 procedure Append_Copies
683 (Params : List_Id;
684 Decls : List_Id;
685 Copies : Elist_Id);
686 -- For each parameter in list Params, create an object declaration of
687 -- the followinng form:
689 -- Copy_Id : Param_Typ := Param_Val;
691 -- Param_Typ is the type of the parameter. Param_Val is the initial
692 -- value of the parameter. The declarations are stored in Decls, the
693 -- entities of the new objects are collected in list Copies.
695 function Build_Dim3_Declaration
696 (Decl_Id : Entity_Id;
697 Init_Val : Node_Id) return Node_Id;
698 -- Build an object declaration of the form
700 -- Decl_Id : CUDA.Internal.Dim3 := Val;
702 -- Val depends on the nature of Init_Val, as follows:
704 -- * If Init_Val is of type CUDA.Vector_Types.Dim3, then Val has the
705 -- following form:
707 -- (Interfaces.C.Unsigned (Val.X),
708 -- Interfaces.C.Unsigned (Val.Y),
709 -- Interfaces.C.Unsigned (Val.Z))
711 -- * If Init_Val is a single Integer, Val has the following form:
713 -- (Interfaces.C.Unsigned (Init_Val),
714 -- Interfaces.C.Unsigned (1),
715 -- Interfaces.C.Unsigned (1))
717 -- * If Init_Val is an aggregate of three values, Val has the
718 -- following form:
720 -- (Interfaces.C.Unsigned (Val_1),
721 -- Interfaces.C.Unsigned (Val_2),
722 -- Interfaces.C.Unsigned (Val_3))
724 function Build_Kernel_Args_Declaration
725 (Kernel_Arg : Entity_Id;
726 Var_Ids : Elist_Id) return Node_Id;
727 -- Given a list of variables, return an object declaration of the
728 -- following form:
730 -- Kernel_Arg : ... := (Var_1'Address, ..., Var_N'Address);
732 function Build_Launch_Kernel_Call
733 (Proc : Entity_Id;
734 Grid_Dims : Entity_Id;
735 Block_Dims : Entity_Id;
736 Kernel_Arg : Entity_Id;
737 Memory : Entity_Id;
738 Stream : Entity_Id) return Node_Id;
739 -- Builds and returns a call to CUDA.Launch_Kernel using the given
740 -- arguments. Proc is the entity of the procedure passed to the
741 -- CUDA_Execute pragma. Grid_Dims and Block_Dims are entities of the
742 -- generated declarations that hold the kernel's dimensions. Args is the
743 -- entity of the temporary array that holds the arguments of the kernel.
744 -- Memory and Stream are the entities of the temporaries that hold the
745 -- fourth and fith arguments of CUDA_Execute or their default values.
747 function Build_Shared_Memory_Declaration
748 (Decl_Id : Entity_Id;
749 Init_Val : Node_Id) return Node_Id;
750 -- Builds a declaration the Defining_Identifier of which is Decl_Id, the
751 -- type of which is inferred from CUDA.Internal.Launch_Kernel and the
752 -- value of which is Init_Val if present or null if not.
754 function Build_Simple_Declaration_With_Default
755 (Decl_Id : Entity_Id;
756 Init_Val : Node_Id;
757 Typ : Node_Id;
758 Default_Val : Node_Id) return Node_Id;
759 -- Build a declaration the Defining_Identifier of which is Decl_Id, the
760 -- Object_Definition of which is Typ, the value of which is Init_Val if
761 -- present or Default otherwise.
763 function Build_Stream_Declaration
764 (Decl_Id : Entity_Id;
765 Init_Val : Node_Id) return Node_Id;
766 -- Build a declaration the Defining_Identifier of which is Decl_Id, the
767 -- type of which is Integer, the value of which is Init_Val if present
768 -- and 0 otherwise.
770 function Etype_Or_Dim3 (N : Node_Id) return Node_Id;
771 -- If N is an aggregate whose type is unknown, return a new occurrence
772 -- of the public Dim3 type. Otherwise, return a new occurrence of N's
773 -- type.
775 function Get_Nth_Arg_Type
776 (Subprogram : Entity_Id;
777 N : Positive) return Entity_Id;
778 -- Returns the type of the Nth argument of Subprogram
780 function To_Addresses (Elmts : Elist_Id) return List_Id;
781 -- Returns a new list containing each element of Elmts wrapped in an
782 -- 'address attribute reference. When passed No_Elist, returns an empty
783 -- list.
785 -------------------
786 -- Append_Copies --
787 -------------------
789 procedure Append_Copies
790 (Params : List_Id;
791 Decls : List_Id;
792 Copies : Elist_Id)
794 Copy : Entity_Id;
795 Param : Node_Id;
796 Expr : Node_Id;
797 begin
798 Param := First (Params);
799 while Present (Param) loop
800 Copy := Make_Temporary (Loc, 'C');
802 if Nkind (Param) = N_Parameter_Association then
803 Expr := Explicit_Actual_Parameter (Param);
804 else
805 Expr := Param;
806 end if;
808 Append_To (Decls,
809 Make_Object_Declaration (Loc,
810 Defining_Identifier => Copy,
811 Object_Definition => New_Occurrence_Of (Etype (Expr), Loc),
812 Expression => New_Copy_Tree (Expr)));
814 Append_Elmt (Copy, Copies);
815 Next (Param);
816 end loop;
817 end Append_Copies;
819 ----------------------------
820 -- Build_Dim3_Declaration --
821 ----------------------------
823 function Build_Dim3_Declaration
824 (Decl_Id : Entity_Id;
825 Init_Val : Node_Id) return Node_Id
827 -- Expressions for each component of the returned Dim3
828 Dim_X : Node_Id;
829 Dim_Y : Node_Id;
830 Dim_Z : Node_Id;
832 -- Type of CUDA.Internal.Dim3 - inferred from
833 -- RE_Push_Call_Configuration to avoid needing changes in GNAT when
834 -- the CUDA bindings change (this happens frequently).
835 Internal_Dim3 : constant Entity_Id :=
836 Get_Nth_Arg_Type (RTE (RE_Push_Call_Configuration), 1);
838 -- Entities for each component of external and internal Dim3
839 First_Component : Entity_Id := First_Entity (RTE (RE_Dim3));
840 Second_Component : Entity_Id := Next_Entity (First_Component);
841 Third_Component : Entity_Id := Next_Entity (Second_Component);
843 begin
845 -- Sem_prag.adb ensured that Init_Val is either a Dim3, an aggregate
846 -- of three Any_Integers or Any_Integer.
848 -- If Init_Val is a Dim3, use each of its components
850 if Etype (Init_Val) = RTE (RE_Dim3) then
851 Dim_X := Make_Selected_Component (Loc,
852 Prefix => New_Occurrence_Of (Entity (Init_Val), Loc),
853 Selector_Name => New_Occurrence_Of (First_Component, Loc));
855 Dim_Y := Make_Selected_Component (Loc,
856 Prefix => New_Occurrence_Of (Entity (Init_Val), Loc),
857 Selector_Name => New_Occurrence_Of (Second_Component, Loc));
859 Dim_Z := Make_Selected_Component (Loc,
860 Prefix => New_Occurrence_Of (Entity (Init_Val), Loc),
861 Selector_Name => New_Occurrence_Of (Third_Component, Loc));
862 else
863 -- If Init_Val is an aggregate, use each of its arguments
865 if Nkind (Init_Val) = N_Aggregate then
866 Dim_X := First (Expressions (Init_Val));
867 Dim_Y := Next (Dim_X);
868 Dim_Z := Next (Dim_Y);
870 -- Otherwise, we know it is an integer and the rest defaults to 1
872 else
873 Dim_X := Init_Val;
874 Dim_Y := Make_Integer_Literal (Loc, 1);
875 Dim_Z := Make_Integer_Literal (Loc, 1);
876 end if;
877 end if;
879 First_Component := First_Entity (Internal_Dim3);
880 Second_Component := Next_Entity (First_Component);
881 Third_Component := Next_Entity (Second_Component);
883 -- Finally return the CUDA.Internal.Dim3 declaration with an
884 -- aggregate initialization expression.
886 return Make_Object_Declaration (Loc,
887 Defining_Identifier => Decl_Id,
888 Object_Definition => New_Occurrence_Of (Internal_Dim3, Loc),
889 Expression => Make_Aggregate (Loc,
890 Expressions => New_List (
891 Make_Type_Conversion (Loc,
892 Subtype_Mark =>
893 New_Occurrence_Of (Etype (First_Component), Loc),
894 Expression => New_Copy_Tree (Dim_X)),
895 Make_Type_Conversion (Loc,
896 Subtype_Mark =>
897 New_Occurrence_Of (Etype (Second_Component), Loc),
898 Expression => New_Copy_Tree (Dim_Y)),
899 Make_Type_Conversion (Loc,
900 Subtype_Mark =>
901 New_Occurrence_Of (Etype (Third_Component), Loc),
902 Expression => New_Copy_Tree (Dim_Z)))));
903 end Build_Dim3_Declaration;
905 -----------------------------------
906 -- Build_Kernel_Args_Declaration --
907 -----------------------------------
909 function Build_Kernel_Args_Declaration
910 (Kernel_Arg : Entity_Id;
911 Var_Ids : Elist_Id) return Node_Id
913 Vals : constant List_Id := To_Addresses (Var_Ids);
914 begin
915 return
916 Make_Object_Declaration (Loc,
917 Defining_Identifier => Kernel_Arg,
918 Object_Definition =>
919 Make_Constrained_Array_Definition (Loc,
920 Discrete_Subtype_Definitions => New_List (
921 Make_Range (Loc,
922 Low_Bound => Make_Integer_Literal (Loc, 1),
923 High_Bound =>
924 Make_Integer_Literal (Loc, List_Length (Vals)))),
925 Component_Definition =>
926 Make_Component_Definition (Loc,
927 Subtype_Indication =>
928 New_Occurrence_Of (Etype (RTE (RE_Address)), Loc))),
929 Expression => Make_Aggregate (Loc, Vals));
930 end Build_Kernel_Args_Declaration;
932 -------------------------------
933 -- Build_Launch_Kernel_Call --
934 -------------------------------
936 function Build_Launch_Kernel_Call
937 (Proc : Entity_Id;
938 Grid_Dims : Entity_Id;
939 Block_Dims : Entity_Id;
940 Kernel_Arg : Entity_Id;
941 Memory : Entity_Id;
942 Stream : Entity_Id) return Node_Id is
943 begin
944 return
945 Make_Procedure_Call_Statement (Loc,
946 Name =>
947 New_Occurrence_Of (RTE (RE_Launch_Kernel), Loc),
948 Parameter_Associations => New_List (
949 Make_Attribute_Reference (Loc,
950 Prefix => New_Occurrence_Of (Proc, Loc),
951 Attribute_Name => Name_Address),
952 New_Occurrence_Of (Grid_Dims, Loc),
953 New_Occurrence_Of (Block_Dims, Loc),
954 Make_Attribute_Reference (Loc,
955 Prefix => New_Occurrence_Of (Kernel_Arg, Loc),
956 Attribute_Name => Name_Address),
957 New_Occurrence_Of (Memory, Loc),
958 New_Occurrence_Of (Stream, Loc)));
959 end Build_Launch_Kernel_Call;
961 -------------------------------------
962 -- Build_Shared_Memory_Declaration --
963 -------------------------------------
965 function Build_Shared_Memory_Declaration
966 (Decl_Id : Entity_Id;
967 Init_Val : Node_Id) return Node_Id
969 begin
970 return Build_Simple_Declaration_With_Default
971 (Decl_Id => Decl_Id,
972 Init_Val => Init_Val,
973 Typ =>
974 New_Occurrence_Of
975 (Get_Nth_Arg_Type (RTE (RE_Launch_Kernel), 5), Loc),
976 Default_Val => Make_Integer_Literal (Loc, 0));
977 end Build_Shared_Memory_Declaration;
979 -------------------------------------------
980 -- Build_Simple_Declaration_With_Default --
981 -------------------------------------------
983 function Build_Simple_Declaration_With_Default
984 (Decl_Id : Entity_Id;
985 Init_Val : Node_Id;
986 Typ : Node_Id;
987 Default_Val : Node_Id) return Node_Id
989 Value : Node_Id := Init_Val;
990 begin
991 if No (Value) then
992 Value := Default_Val;
993 end if;
995 return Make_Object_Declaration (Loc,
996 Defining_Identifier => Decl_Id,
997 Object_Definition => Typ,
998 Expression => Value);
999 end Build_Simple_Declaration_With_Default;
1001 ------------------------------
1002 -- Build_Stream_Declaration --
1003 ------------------------------
1005 function Build_Stream_Declaration
1006 (Decl_Id : Entity_Id;
1007 Init_Val : Node_Id) return Node_Id
1009 begin
1010 return Build_Simple_Declaration_With_Default
1011 (Decl_Id => Decl_Id,
1012 Init_Val => Init_Val,
1013 Typ =>
1014 New_Occurrence_Of
1015 (Get_Nth_Arg_Type (RTE (RE_Launch_Kernel), 6), Loc),
1016 Default_Val => Make_Null (Loc));
1017 end Build_Stream_Declaration;
1019 -------------------
1020 -- Etype_Or_Dim3 --
1021 -------------------
1023 function Etype_Or_Dim3 (N : Node_Id) return Node_Id is
1024 begin
1025 if Nkind (N) = N_Aggregate and then Is_Composite_Type (Etype (N)) then
1026 return New_Occurrence_Of (RTE (RE_Dim3), Sloc (N));
1027 end if;
1029 return New_Occurrence_Of (Etype (N), Loc);
1030 end Etype_Or_Dim3;
1032 ----------------------
1033 -- Get_Nth_Arg_Type --
1034 ----------------------
1036 function Get_Nth_Arg_Type
1037 (Subprogram : Entity_Id;
1038 N : Positive) return Entity_Id
1040 Argument : Entity_Id := First_Entity (Subprogram);
1041 begin
1042 for J in 2 .. N loop
1043 Next_Entity (Argument);
1044 end loop;
1046 return Etype (Argument);
1047 end Get_Nth_Arg_Type;
1049 ------------------
1050 -- To_Addresses --
1051 ------------------
1053 function To_Addresses (Elmts : Elist_Id) return List_Id is
1054 Result : constant List_Id := New_List;
1055 Elmt : Elmt_Id;
1056 begin
1057 if Elmts = No_Elist then
1058 return Result;
1059 end if;
1061 Elmt := First_Elmt (Elmts);
1062 while Present (Elmt) loop
1063 Append_To (Result,
1064 Make_Attribute_Reference (Loc,
1065 Prefix => New_Occurrence_Of (Node (Elmt), Loc),
1066 Attribute_Name => Name_Address));
1067 Next_Elmt (Elmt);
1068 end loop;
1070 return Result;
1071 end To_Addresses;
1073 -- Local variables
1075 -- Pragma arguments
1077 Procedure_Call : constant Node_Id := Get_Pragma_Arg (Arg_N (N, 1));
1078 Grid_Dimensions : constant Node_Id := Get_Pragma_Arg (Arg_N (N, 2));
1079 Block_Dimensions : constant Node_Id := Get_Pragma_Arg (Arg_N (N, 3));
1080 Shared_Memory : constant Node_Id := Get_Pragma_Arg (Arg_N (N, 4));
1081 CUDA_Stream : constant Node_Id := Get_Pragma_Arg (Arg_N (N, 5));
1083 -- Entities of objects that will be overwritten by calls to cuda runtime
1084 Grids_Id : constant Entity_Id := Make_Temporary (Loc, 'C');
1085 Blocks_Id : constant Entity_Id := Make_Temporary (Loc, 'C');
1086 Memory_Id : constant Entity_Id := Make_Temporary (Loc, 'C');
1087 Stream_Id : constant Entity_Id := Make_Temporary (Loc, 'C');
1089 -- Entities of objects that capture the value of pragma arguments
1090 Temp_Grid : constant Entity_Id := Make_Temporary (Loc, 'C');
1091 Temp_Block : constant Entity_Id := Make_Temporary (Loc, 'C');
1093 -- Declarations for temporary block and grids. These needs to be stored
1094 -- in temporary declarations as the expressions will need to be
1095 -- referenced multiple times but could have side effects.
1096 Temp_Grid_Decl : constant Node_Id := Make_Object_Declaration (Loc,
1097 Defining_Identifier => Temp_Grid,
1098 Object_Definition => Etype_Or_Dim3 (Grid_Dimensions),
1099 Expression => Grid_Dimensions);
1100 Temp_Block_Decl : constant Node_Id := Make_Object_Declaration (Loc,
1101 Defining_Identifier => Temp_Block,
1102 Object_Definition => Etype_Or_Dim3 (Block_Dimensions),
1103 Expression => Block_Dimensions);
1105 -- List holding the entities of the copies of Procedure_Call's arguments
1107 Kernel_Arg_Copies : constant Elist_Id := New_Elmt_List;
1109 -- Entity of the array that contains the address of each of the kernel's
1110 -- arguments.
1112 Kernel_Args_Id : constant Entity_Id := Make_Temporary (Loc, 'C');
1114 -- Calls to the CUDA runtime API.
1116 Launch_Kernel_Call : Node_Id;
1117 Pop_Call : Node_Id;
1118 Push_Call : Node_Id;
1120 -- Declaration of all temporaries required for CUDA API Calls
1122 Blk_Decls : constant List_Id := New_List;
1124 -- Start of processing for CUDA_Execute
1126 begin
1127 -- Append temporary declarations
1129 Append_To (Blk_Decls, Temp_Grid_Decl);
1130 Analyze (Temp_Grid_Decl);
1132 Append_To (Blk_Decls, Temp_Block_Decl);
1133 Analyze (Temp_Block_Decl);
1135 -- Build parameter declarations for CUDA API calls
1137 Append_To
1138 (Blk_Decls,
1139 Build_Dim3_Declaration
1140 (Grids_Id, New_Occurrence_Of (Temp_Grid, Loc)));
1142 Append_To
1143 (Blk_Decls,
1144 Build_Dim3_Declaration
1145 (Blocks_Id, New_Occurrence_Of (Temp_Block, Loc)));
1147 Append_To
1148 (Blk_Decls,
1149 Build_Shared_Memory_Declaration (Memory_Id, Shared_Memory));
1151 Append_To
1152 (Blk_Decls, Build_Stream_Declaration (Stream_Id, CUDA_Stream));
1154 Append_Copies
1155 (Parameter_Associations (Procedure_Call),
1156 Blk_Decls,
1157 Kernel_Arg_Copies);
1159 Append_To
1160 (Blk_Decls,
1161 Build_Kernel_Args_Declaration
1162 (Kernel_Args_Id, Kernel_Arg_Copies));
1164 -- Build calls to the CUDA API
1166 Push_Call :=
1167 Make_Procedure_Call_Statement (Loc,
1168 Name =>
1169 New_Occurrence_Of (RTE (RE_Push_Call_Configuration), Loc),
1170 Parameter_Associations => New_List (
1171 New_Occurrence_Of (Grids_Id, Loc),
1172 New_Occurrence_Of (Blocks_Id, Loc),
1173 New_Occurrence_Of (Memory_Id, Loc),
1174 New_Occurrence_Of (Stream_Id, Loc)));
1176 Pop_Call :=
1177 Make_Procedure_Call_Statement (Loc,
1178 Name =>
1179 New_Occurrence_Of (RTE (RE_Pop_Call_Configuration), Loc),
1180 Parameter_Associations => To_Addresses
1181 (New_Elmt_List
1182 (Grids_Id,
1183 Blocks_Id,
1184 Memory_Id,
1185 Stream_Id)));
1187 Launch_Kernel_Call := Build_Launch_Kernel_Call
1188 (Proc => Entity (Name (Procedure_Call)),
1189 Grid_Dims => Grids_Id,
1190 Block_Dims => Blocks_Id,
1191 Kernel_Arg => Kernel_Args_Id,
1192 Memory => Memory_Id,
1193 Stream => Stream_Id);
1195 -- Finally make the block that holds declarations and calls
1197 Rewrite (N,
1198 Make_Block_Statement (Loc,
1199 Declarations => Blk_Decls,
1200 Handled_Statement_Sequence =>
1201 Make_Handled_Sequence_Of_Statements (Loc,
1202 Statements => New_List (
1203 Push_Call,
1204 Pop_Call,
1205 Launch_Kernel_Call))));
1206 Analyze (N);
1207 end Expand_Pragma_CUDA_Execute;
1209 ----------------------------------
1210 -- Expand_Pragma_Contract_Cases --
1211 ----------------------------------
1213 -- Pragma Contract_Cases is expanded in the following manner:
1215 -- subprogram S is
1216 -- Count : Natural := 0;
1217 -- Flag_1 : Boolean := False;
1218 -- . . .
1219 -- Flag_N : Boolean := False;
1220 -- Flag_N+1 : Boolean := False; -- when "others" present
1221 -- Pref_1 : ...;
1222 -- . . .
1223 -- Pref_M : ...;
1225 -- <preconditions (if any)>
1227 -- -- Evaluate all case guards
1229 -- if Case_Guard_1 then
1230 -- Flag_1 := True;
1231 -- Count := Count + 1;
1232 -- end if;
1233 -- . . .
1234 -- if Case_Guard_N then
1235 -- Flag_N := True;
1236 -- Count := Count + 1;
1237 -- end if;
1239 -- -- Emit errors depending on the number of case guards that
1240 -- -- evaluated to True.
1242 -- if Count = 0 then
1243 -- raise Assertion_Error with "xxx contract cases incomplete";
1244 -- <or>
1245 -- Flag_N+1 := True; -- when "others" present
1247 -- elsif Count > 1 then
1248 -- declare
1249 -- Str0 : constant String :=
1250 -- "contract cases overlap for subprogram ABC";
1251 -- Str1 : constant String :=
1252 -- (if Flag_1 then
1253 -- Str0 & "case guard at xxx evaluates to True"
1254 -- else Str0);
1255 -- StrN : constant String :=
1256 -- (if Flag_N then
1257 -- StrN-1 & "case guard at xxx evaluates to True"
1258 -- else StrN-1);
1259 -- begin
1260 -- raise Assertion_Error with StrN;
1261 -- end;
1262 -- end if;
1264 -- -- Evaluate all attribute 'Old prefixes found in the selected
1265 -- -- consequence.
1267 -- if Flag_1 then
1268 -- Pref_1 := <prefix of 'Old found in Consequence_1>
1269 -- . . .
1270 -- elsif Flag_N then
1271 -- Pref_M := <prefix of 'Old found in Consequence_N>
1272 -- end if;
1274 -- procedure _Postconditions is
1275 -- begin
1276 -- <postconditions (if any)>
1278 -- if Flag_1 and then not Consequence_1 then
1279 -- raise Assertion_Error with "failed contract case at xxx";
1280 -- end if;
1281 -- . . .
1282 -- if Flag_N[+1] and then not Consequence_N[+1] then
1283 -- raise Assertion_Error with "failed contract case at xxx";
1284 -- end if;
1285 -- end _Postconditions;
1286 -- begin
1287 -- . . .
1288 -- end S;
1290 procedure Expand_Pragma_Contract_Cases
1291 (CCs : Node_Id;
1292 Subp_Id : Entity_Id;
1293 Decls : List_Id;
1294 Stmts : in out List_Id)
1296 Loc : constant Source_Ptr := Sloc (CCs);
1298 procedure Case_Guard_Error
1299 (Decls : List_Id;
1300 Flag : Entity_Id;
1301 Error_Loc : Source_Ptr;
1302 Msg : in out Entity_Id);
1303 -- Given a declarative list Decls, status flag Flag, the location of the
1304 -- error and a string Msg, construct the following check:
1305 -- Msg : constant String :=
1306 -- (if Flag then
1307 -- Msg & "case guard at Error_Loc evaluates to True"
1308 -- else Msg);
1309 -- The resulting code is added to Decls
1311 procedure Consequence_Error
1312 (Checks : in out Node_Id;
1313 Flag : Entity_Id;
1314 Conseq : Node_Id);
1315 -- Given an if statement Checks, status flag Flag and a consequence
1316 -- Conseq, construct the following check:
1317 -- [els]if Flag and then not Conseq then
1318 -- raise Assertion_Error
1319 -- with "failed contract case at Sloc (Conseq)";
1320 -- [end if;]
1321 -- The resulting code is added to Checks
1323 function Declaration_Of (Id : Entity_Id) return Node_Id;
1324 -- Given the entity Id of a boolean flag, generate:
1325 -- Id : Boolean := False;
1327 procedure Expand_Attributes_In_Consequence
1328 (Decls : List_Id;
1329 Evals : in out Node_Id;
1330 Flag : Entity_Id;
1331 Conseq : Node_Id);
1332 -- Perform specialized expansion of all attribute 'Old references found
1333 -- in consequence Conseq such that at runtime only prefixes coming from
1334 -- the selected consequence are evaluated. Similarly expand attribute
1335 -- 'Result references by replacing them with identifier _result which
1336 -- resolves to the sole formal parameter of procedure _Postconditions.
1337 -- Any temporaries generated in the process are added to declarations
1338 -- Decls. Evals is a complex if statement tasked with the evaluation of
1339 -- all prefixes coming from a single selected consequence. Flag is the
1340 -- corresponding case guard flag. Conseq is the consequence expression.
1342 function Increment (Id : Entity_Id) return Node_Id;
1343 -- Given the entity Id of a numerical variable, generate:
1344 -- Id := Id + 1;
1346 function Set (Id : Entity_Id) return Node_Id;
1347 -- Given the entity Id of a boolean variable, generate:
1348 -- Id := True;
1350 ----------------------
1351 -- Case_Guard_Error --
1352 ----------------------
1354 procedure Case_Guard_Error
1355 (Decls : List_Id;
1356 Flag : Entity_Id;
1357 Error_Loc : Source_Ptr;
1358 Msg : in out Entity_Id)
1360 New_Line : constant Character := Character'Val (10);
1361 New_Msg : constant Entity_Id := Make_Temporary (Loc, 'S');
1363 begin
1364 Start_String;
1365 Store_String_Char (New_Line);
1366 Store_String_Chars (" case guard at ");
1367 Store_String_Chars (Build_Location_String (Error_Loc));
1368 Store_String_Chars (" evaluates to True");
1370 -- Generate:
1371 -- New_Msg : constant String :=
1372 -- (if Flag then
1373 -- Msg & "case guard at Error_Loc evaluates to True"
1374 -- else Msg);
1376 Append_To (Decls,
1377 Make_Object_Declaration (Loc,
1378 Defining_Identifier => New_Msg,
1379 Constant_Present => True,
1380 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1381 Expression =>
1382 Make_If_Expression (Loc,
1383 Expressions => New_List (
1384 New_Occurrence_Of (Flag, Loc),
1386 Make_Op_Concat (Loc,
1387 Left_Opnd => New_Occurrence_Of (Msg, Loc),
1388 Right_Opnd => Make_String_Literal (Loc, End_String)),
1390 New_Occurrence_Of (Msg, Loc)))));
1392 Msg := New_Msg;
1393 end Case_Guard_Error;
1395 -----------------------
1396 -- Consequence_Error --
1397 -----------------------
1399 procedure Consequence_Error
1400 (Checks : in out Node_Id;
1401 Flag : Entity_Id;
1402 Conseq : Node_Id)
1404 Cond : Node_Id;
1405 Error : Node_Id;
1407 begin
1408 -- Generate:
1409 -- Flag and then not Conseq
1411 Cond :=
1412 Make_And_Then (Loc,
1413 Left_Opnd => New_Occurrence_Of (Flag, Loc),
1414 Right_Opnd =>
1415 Make_Op_Not (Loc,
1416 Right_Opnd => Relocate_Node (Conseq)));
1418 -- Generate:
1419 -- raise Assertion_Error
1420 -- with "failed contract case at Sloc (Conseq)";
1422 Start_String;
1423 Store_String_Chars ("failed contract case at ");
1424 Store_String_Chars (Build_Location_String (Sloc (Conseq)));
1426 Error :=
1427 Make_Procedure_Call_Statement (Loc,
1428 Name =>
1429 New_Occurrence_Of (RTE (RE_Raise_Assert_Failure), Loc),
1430 Parameter_Associations => New_List (
1431 Make_String_Literal (Loc, End_String)));
1433 if No (Checks) then
1434 Checks :=
1435 Make_Implicit_If_Statement (CCs,
1436 Condition => Cond,
1437 Then_Statements => New_List (Error));
1439 else
1440 if No (Elsif_Parts (Checks)) then
1441 Set_Elsif_Parts (Checks, New_List);
1442 end if;
1444 Append_To (Elsif_Parts (Checks),
1445 Make_Elsif_Part (Loc,
1446 Condition => Cond,
1447 Then_Statements => New_List (Error)));
1448 end if;
1449 end Consequence_Error;
1451 --------------------
1452 -- Declaration_Of --
1453 --------------------
1455 function Declaration_Of (Id : Entity_Id) return Node_Id is
1456 begin
1457 return
1458 Make_Object_Declaration (Loc,
1459 Defining_Identifier => Id,
1460 Object_Definition => New_Occurrence_Of (Standard_Boolean, Loc),
1461 Expression => New_Occurrence_Of (Standard_False, Loc));
1462 end Declaration_Of;
1464 --------------------------------------
1465 -- Expand_Attributes_In_Consequence --
1466 --------------------------------------
1468 procedure Expand_Attributes_In_Consequence
1469 (Decls : List_Id;
1470 Evals : in out Node_Id;
1471 Flag : Entity_Id;
1472 Conseq : Node_Id)
1474 Eval_Stmts : List_Id := No_List;
1475 -- The evaluation sequence expressed as assignment statements of all
1476 -- prefixes of attribute 'Old found in the current consequence.
1478 function Expand_Attributes (N : Node_Id) return Traverse_Result;
1479 -- Determine whether an arbitrary node denotes attribute 'Old or
1480 -- 'Result and if it does, perform all expansion-related actions.
1482 -----------------------
1483 -- Expand_Attributes --
1484 -----------------------
1486 function Expand_Attributes (N : Node_Id) return Traverse_Result is
1487 Decl : Node_Id;
1488 Pref : Node_Id;
1489 Temp : Entity_Id;
1490 Indirect : Boolean := False;
1492 use Sem_Util.Old_Attr_Util.Indirect_Temps;
1494 procedure Append_For_Indirect_Temp
1495 (N : Node_Id; Is_Eval_Stmt : Boolean);
1497 -- Append either a declaration (which is to be elaborated
1498 -- unconditionally) or an evaluation statement (which is
1499 -- to be executed conditionally).
1501 -------------------------------
1502 -- Append_For_Indirect_Temp --
1503 -------------------------------
1505 procedure Append_For_Indirect_Temp
1506 (N : Node_Id; Is_Eval_Stmt : Boolean)
1508 begin
1509 if Is_Eval_Stmt then
1510 Append_To (Eval_Stmts, N);
1511 else
1512 Prepend_To (Decls, N);
1513 -- This use of Prepend (as opposed to Append) is why
1514 -- we have the Append_Decls_In_Reverse_Order parameter.
1515 end if;
1516 end Append_For_Indirect_Temp;
1518 procedure Declare_Indirect_Temporary is new
1519 Declare_Indirect_Temp (
1520 Append_Item => Append_For_Indirect_Temp,
1521 Append_Decls_In_Reverse_Order => True);
1523 -- Start of processing for Expand_Attributes
1525 begin
1526 -- Attribute 'Old
1528 if Is_Attribute_Old (N) then
1529 Pref := Prefix (N);
1531 Indirect := Indirect_Temp_Needed (Etype (Pref));
1533 if Indirect then
1534 if No (Eval_Stmts) then
1535 Eval_Stmts := New_List;
1536 end if;
1538 Declare_Indirect_Temporary
1539 (Attr_Prefix => Pref,
1540 Indirect_Temp => Temp);
1542 -- Declare a temporary of the prefix type with no explicit
1543 -- initial value. If the appropriate contract case is selected
1544 -- at run time, then the temporary will be initialized via an
1545 -- assignment statement.
1547 else
1548 Temp := Make_Temporary (Loc, 'T', Pref);
1549 Set_Etype (Temp, Etype (Pref));
1551 -- Generate a temporary to capture the value of the prefix:
1552 -- Temp : <Pref type>;
1554 Decl :=
1555 Make_Object_Declaration (Loc,
1556 Defining_Identifier => Temp,
1557 Object_Definition =>
1558 New_Occurrence_Of (Etype (Pref), Loc));
1560 -- Place that temporary at the beginning of declarations, to
1561 -- prevent anomalies in the GNATprove flow-analysis pass in
1562 -- the precondition procedure that follows.
1564 Prepend_To (Decls, Decl);
1566 -- Initially Temp is uninitialized (which is required for
1567 -- correctness if default initialization might have side
1568 -- effects). Assign prefix value to temp on Eval_Statement
1569 -- list, so assignment will be executed conditionally.
1571 Mutate_Ekind (Temp, E_Variable);
1572 Set_Suppress_Initialization (Temp);
1573 Analyze (Decl);
1575 if No (Eval_Stmts) then
1576 Eval_Stmts := New_List;
1577 end if;
1579 Append_To (Eval_Stmts,
1580 Make_Assignment_Statement (Loc,
1581 Name => New_Occurrence_Of (Temp, Loc),
1582 Expression => Pref));
1583 end if;
1585 -- Mark the temporary as coming from a 'Old reference
1587 if Present (Temp) then
1588 Set_Stores_Attribute_Old_Prefix (Temp);
1589 end if;
1591 -- Ensure that the prefix is valid
1593 if Validity_Checks_On and then Validity_Check_Operands then
1594 Ensure_Valid (Pref);
1595 end if;
1597 -- Replace the original attribute 'Old by a reference to the
1598 -- generated temporary.
1600 if Indirect then
1601 Rewrite (N,
1602 Indirect_Temp_Value
1603 (Temp => Temp, Typ => Etype (Pref), Loc => Loc));
1604 else
1605 Rewrite (N, New_Occurrence_Of (Temp, Loc));
1606 end if;
1608 -- Attribute 'Result
1610 elsif Is_Attribute_Result (N) then
1611 Rewrite (N, Make_Identifier (Loc, Name_uResult));
1612 end if;
1614 return OK;
1615 end Expand_Attributes;
1617 procedure Expand_Attributes_In is
1618 new Traverse_Proc (Expand_Attributes);
1620 -- Start of processing for Expand_Attributes_In_Consequence
1622 begin
1623 -- Inspect the consequence and expand any attribute 'Old and 'Result
1624 -- references found within.
1626 Expand_Attributes_In (Conseq);
1628 -- The consequence does not contain any attribute 'Old references
1630 if No (Eval_Stmts) then
1631 return;
1632 end if;
1634 -- Augment the machinery to trigger the evaluation of all prefixes
1635 -- found in the step above. If Eval is empty, then this is the first
1636 -- consequence to yield expansion of 'Old. Generate:
1638 -- if Flag then
1639 -- <evaluation statements>
1640 -- end if;
1642 if No (Evals) then
1643 Evals :=
1644 Make_Implicit_If_Statement (CCs,
1645 Condition => New_Occurrence_Of (Flag, Loc),
1646 Then_Statements => Eval_Stmts);
1648 -- Otherwise generate:
1649 -- elsif Flag then
1650 -- <evaluation statements>
1651 -- end if;
1653 else
1654 if No (Elsif_Parts (Evals)) then
1655 Set_Elsif_Parts (Evals, New_List);
1656 end if;
1658 Append_To (Elsif_Parts (Evals),
1659 Make_Elsif_Part (Loc,
1660 Condition => New_Occurrence_Of (Flag, Loc),
1661 Then_Statements => Eval_Stmts));
1662 end if;
1663 end Expand_Attributes_In_Consequence;
1665 ---------------
1666 -- Increment --
1667 ---------------
1669 function Increment (Id : Entity_Id) return Node_Id is
1670 begin
1671 return
1672 Make_Assignment_Statement (Loc,
1673 Name => New_Occurrence_Of (Id, Loc),
1674 Expression =>
1675 Make_Op_Add (Loc,
1676 Left_Opnd => New_Occurrence_Of (Id, Loc),
1677 Right_Opnd => Make_Integer_Literal (Loc, 1)));
1678 end Increment;
1680 ---------
1681 -- Set --
1682 ---------
1684 function Set (Id : Entity_Id) return Node_Id is
1685 begin
1686 return
1687 Make_Assignment_Statement (Loc,
1688 Name => New_Occurrence_Of (Id, Loc),
1689 Expression => New_Occurrence_Of (Standard_True, Loc));
1690 end Set;
1692 -- Local variables
1694 Aggr : constant Node_Id :=
1695 Expression (First (Pragma_Argument_Associations (CCs)));
1697 Case_Guard : Node_Id;
1698 CG_Checks : Node_Id;
1699 CG_Stmts : List_Id;
1700 Conseq : Node_Id;
1701 Conseq_Checks : Node_Id := Empty;
1702 Count : Entity_Id;
1703 Count_Decl : Node_Id;
1704 Error_Decls : List_Id := No_List; -- init to avoid warning
1705 Flag : Entity_Id;
1706 Flag_Decl : Node_Id;
1707 If_Stmt : Node_Id;
1708 Msg_Str : Entity_Id := Empty;
1709 Multiple_PCs : Boolean;
1710 Old_Evals : Node_Id := Empty;
1711 Others_Decl : Node_Id;
1712 Others_Flag : Entity_Id := Empty;
1713 Post_Case : Node_Id;
1715 -- Start of processing for Expand_Pragma_Contract_Cases
1717 begin
1718 -- Do nothing if pragma is not enabled. If pragma is disabled, it has
1719 -- already been rewritten as a Null statement.
1721 if Is_Ignored (CCs) then
1722 return;
1724 -- Guard against malformed contract cases
1726 elsif Nkind (Aggr) /= N_Aggregate then
1727 return;
1728 end if;
1730 -- The expansion of contract cases is quite distributed as it produces
1731 -- various statements to evaluate the case guards and consequences. To
1732 -- preserve the original context, set the Is_Assertion_Expr flag. This
1733 -- aids the Ghost legality checks when verifying the placement of a
1734 -- reference to a Ghost entity.
1736 In_Assertion_Expr := In_Assertion_Expr + 1;
1738 Multiple_PCs := List_Length (Component_Associations (Aggr)) > 1;
1740 -- Create the counter which tracks the number of case guards that
1741 -- evaluate to True.
1743 -- Count : Natural := 0;
1745 Count := Make_Temporary (Loc, 'C');
1746 Count_Decl :=
1747 Make_Object_Declaration (Loc,
1748 Defining_Identifier => Count,
1749 Object_Definition => New_Occurrence_Of (Standard_Natural, Loc),
1750 Expression => Make_Integer_Literal (Loc, 0));
1752 Prepend_To (Decls, Count_Decl);
1753 Analyze (Count_Decl);
1755 -- Create the base error message for multiple overlapping case guards
1757 -- Msg_Str : constant String :=
1758 -- "contract cases overlap for subprogram Subp_Id";
1760 if Multiple_PCs then
1761 Msg_Str := Make_Temporary (Loc, 'S');
1763 Start_String;
1764 Store_String_Chars ("contract cases overlap for subprogram ");
1765 Store_String_Chars (Get_Name_String (Chars (Subp_Id)));
1767 Error_Decls := New_List (
1768 Make_Object_Declaration (Loc,
1769 Defining_Identifier => Msg_Str,
1770 Constant_Present => True,
1771 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1772 Expression => Make_String_Literal (Loc, End_String)));
1773 end if;
1775 -- Process individual post cases
1777 Post_Case := First (Component_Associations (Aggr));
1778 while Present (Post_Case) loop
1779 Case_Guard := First (Choices (Post_Case));
1780 Conseq := Expression (Post_Case);
1782 -- The "others" choice requires special processing
1784 if Nkind (Case_Guard) = N_Others_Choice then
1785 Others_Flag := Make_Temporary (Loc, 'F');
1786 Others_Decl := Declaration_Of (Others_Flag);
1788 Prepend_To (Decls, Others_Decl);
1789 Analyze (Others_Decl);
1791 -- Check possible overlap between a case guard and "others"
1793 if Multiple_PCs and Exception_Extra_Info then
1794 Case_Guard_Error
1795 (Decls => Error_Decls,
1796 Flag => Others_Flag,
1797 Error_Loc => Sloc (Case_Guard),
1798 Msg => Msg_Str);
1799 end if;
1801 -- Inspect the consequence and perform special expansion of any
1802 -- attribute 'Old and 'Result references found within.
1804 Expand_Attributes_In_Consequence
1805 (Decls => Decls,
1806 Evals => Old_Evals,
1807 Flag => Others_Flag,
1808 Conseq => Conseq);
1810 -- Check the corresponding consequence of "others"
1812 Consequence_Error
1813 (Checks => Conseq_Checks,
1814 Flag => Others_Flag,
1815 Conseq => Conseq);
1817 -- Regular post case
1819 else
1820 -- Create the flag which tracks the state of its associated case
1821 -- guard.
1823 Flag := Make_Temporary (Loc, 'F');
1824 Flag_Decl := Declaration_Of (Flag);
1826 Prepend_To (Decls, Flag_Decl);
1827 Analyze (Flag_Decl);
1829 -- The flag is set when the case guard is evaluated to True
1830 -- if Case_Guard then
1831 -- Flag := True;
1832 -- Count := Count + 1;
1833 -- end if;
1835 If_Stmt :=
1836 Make_Implicit_If_Statement (CCs,
1837 Condition => Relocate_Node (Case_Guard),
1838 Then_Statements => New_List (
1839 Set (Flag),
1840 Increment (Count)));
1842 Append_To (Decls, If_Stmt);
1843 Analyze (If_Stmt);
1845 -- Check whether this case guard overlaps with another one
1847 if Multiple_PCs and Exception_Extra_Info then
1848 Case_Guard_Error
1849 (Decls => Error_Decls,
1850 Flag => Flag,
1851 Error_Loc => Sloc (Case_Guard),
1852 Msg => Msg_Str);
1853 end if;
1855 -- Inspect the consequence and perform special expansion of any
1856 -- attribute 'Old and 'Result references found within.
1858 Expand_Attributes_In_Consequence
1859 (Decls => Decls,
1860 Evals => Old_Evals,
1861 Flag => Flag,
1862 Conseq => Conseq);
1864 -- The corresponding consequence of the case guard which evaluated
1865 -- to True must hold on exit from the subprogram.
1867 Consequence_Error
1868 (Checks => Conseq_Checks,
1869 Flag => Flag,
1870 Conseq => Conseq);
1871 end if;
1873 Next (Post_Case);
1874 end loop;
1876 -- Raise Assertion_Error when none of the case guards evaluate to True.
1877 -- The only exception is when we have "others", in which case there is
1878 -- no error because "others" acts as a default True.
1880 -- Generate:
1881 -- Flag := True;
1883 if Present (Others_Flag) then
1884 CG_Stmts := New_List (Set (Others_Flag));
1886 -- Generate:
1887 -- raise Assertion_Error with "xxx contract cases incomplete";
1889 else
1890 Start_String;
1891 Store_String_Chars (Build_Location_String (Loc));
1892 Store_String_Chars (" contract cases incomplete");
1894 CG_Stmts := New_List (
1895 Make_Procedure_Call_Statement (Loc,
1896 Name =>
1897 New_Occurrence_Of (RTE (RE_Raise_Assert_Failure), Loc),
1898 Parameter_Associations => New_List (
1899 Make_String_Literal (Loc, End_String))));
1900 end if;
1902 CG_Checks :=
1903 Make_Implicit_If_Statement (CCs,
1904 Condition =>
1905 Make_Op_Eq (Loc,
1906 Left_Opnd => New_Occurrence_Of (Count, Loc),
1907 Right_Opnd => Make_Integer_Literal (Loc, 0)),
1908 Then_Statements => CG_Stmts);
1910 -- Detect a possible failure due to several case guards evaluating to
1911 -- True.
1913 -- Generate:
1914 -- elsif Count > 0 then
1915 -- declare
1916 -- <Error_Decls>
1917 -- begin
1918 -- raise Assertion_Error with <Msg_Str>;
1919 -- end if;
1921 if Multiple_PCs then
1922 Set_Elsif_Parts (CG_Checks, New_List (
1923 Make_Elsif_Part (Loc,
1924 Condition =>
1925 Make_Op_Gt (Loc,
1926 Left_Opnd => New_Occurrence_Of (Count, Loc),
1927 Right_Opnd => Make_Integer_Literal (Loc, 1)),
1929 Then_Statements => New_List (
1930 Make_Block_Statement (Loc,
1931 Declarations => Error_Decls,
1932 Handled_Statement_Sequence =>
1933 Make_Handled_Sequence_Of_Statements (Loc,
1934 Statements => New_List (
1935 Make_Procedure_Call_Statement (Loc,
1936 Name =>
1937 New_Occurrence_Of
1938 (RTE (RE_Raise_Assert_Failure), Loc),
1939 Parameter_Associations => New_List (
1940 New_Occurrence_Of (Msg_Str, Loc))))))))));
1941 end if;
1943 Append_To (Decls, CG_Checks);
1944 Analyze (CG_Checks);
1946 -- Once all case guards are evaluated and checked, evaluate any prefixes
1947 -- of attribute 'Old founds in the selected consequence.
1949 if Present (Old_Evals) then
1950 Append_To (Decls, Old_Evals);
1951 Analyze (Old_Evals);
1952 end if;
1954 -- Raise Assertion_Error when the corresponding consequence of a case
1955 -- guard that evaluated to True fails.
1957 Append_New_To (Stmts, Conseq_Checks);
1959 In_Assertion_Expr := In_Assertion_Expr - 1;
1960 end Expand_Pragma_Contract_Cases;
1962 ---------------------------------------
1963 -- Expand_Pragma_Import_Or_Interface --
1964 ---------------------------------------
1966 procedure Expand_Pragma_Import_Or_Interface (N : Node_Id) is
1967 Def_Id : Entity_Id;
1969 begin
1970 -- In Relaxed_RM_Semantics, support old Ada 83 style:
1971 -- pragma Import (Entity, "external name");
1973 if Relaxed_RM_Semantics
1974 and then List_Length (Pragma_Argument_Associations (N)) = 2
1975 and then Pragma_Name (N) = Name_Import
1976 and then Nkind (Arg_N (N, 2)) = N_String_Literal
1977 then
1978 Def_Id := Entity (Arg_N (N, 1));
1979 else
1980 Def_Id := Entity (Arg_N (N, 2));
1981 end if;
1983 -- Variable case (we have to undo any initialization already done)
1985 if Ekind (Def_Id) = E_Variable then
1986 Undo_Initialization (Def_Id, N);
1988 -- Case of exception with convention C++
1990 elsif Ekind (Def_Id) = E_Exception
1991 and then Convention (Def_Id) = Convention_CPP
1992 then
1993 -- Import a C++ convention
1995 declare
1996 Loc : constant Source_Ptr := Sloc (N);
1997 Rtti_Name : constant Node_Id := Arg_N (N, 3);
1998 Dum : constant Entity_Id := Make_Temporary (Loc, 'D');
1999 Exdata : List_Id;
2000 Lang_Char : Node_Id;
2001 Foreign_Data : Node_Id;
2003 begin
2004 Exdata := Component_Associations (Expression (Parent (Def_Id)));
2006 Lang_Char := Next (First (Exdata));
2008 -- Change the one-character language designator to 'C'
2010 Rewrite (Expression (Lang_Char),
2011 Make_Character_Literal (Loc,
2012 Chars => Name_uC,
2013 Char_Literal_Value => UI_From_Int (Character'Pos ('C'))));
2014 Analyze (Expression (Lang_Char));
2016 -- Change the value of Foreign_Data
2018 Foreign_Data := Next (Next (Next (Next (Lang_Char))));
2020 Insert_Actions (Def_Id, New_List (
2021 Make_Object_Declaration (Loc,
2022 Defining_Identifier => Dum,
2023 Object_Definition =>
2024 New_Occurrence_Of (Standard_Character, Loc)),
2026 Make_Pragma (Loc,
2027 Chars => Name_Import,
2028 Pragma_Argument_Associations => New_List (
2029 Make_Pragma_Argument_Association (Loc,
2030 Expression => Make_Identifier (Loc, Name_Ada)),
2032 Make_Pragma_Argument_Association (Loc,
2033 Expression => Make_Identifier (Loc, Chars (Dum))),
2035 Make_Pragma_Argument_Association (Loc,
2036 Chars => Name_External_Name,
2037 Expression => Relocate_Node (Rtti_Name))))));
2039 Rewrite (Expression (Foreign_Data),
2040 OK_Convert_To (Standard_Address,
2041 Make_Attribute_Reference (Loc,
2042 Prefix => Make_Identifier (Loc, Chars (Dum)),
2043 Attribute_Name => Name_Address)));
2044 Analyze (Expression (Foreign_Data));
2045 end;
2047 -- No special expansion required for any other case
2049 else
2050 null;
2051 end if;
2052 end Expand_Pragma_Import_Or_Interface;
2054 -------------------------------------
2055 -- Expand_Pragma_Initial_Condition --
2056 -------------------------------------
2058 procedure Expand_Pragma_Initial_Condition
2059 (Pack_Id : Entity_Id;
2060 N : Node_Id)
2062 procedure Extract_Package_Body_Lists
2063 (Pack_Body : Node_Id;
2064 Body_List : out List_Id;
2065 Call_List : out List_Id;
2066 Spec_List : out List_Id);
2067 -- Obtain the various declarative and statement lists of package body
2068 -- Pack_Body needed to insert the initial condition procedure and the
2069 -- call to it. The lists are as follows:
2071 -- * Body_List - used to insert the initial condition procedure body
2073 -- * Call_List - used to insert the call to the initial condition
2074 -- procedure.
2076 -- * Spec_List - used to insert the initial condition procedure spec
2078 procedure Extract_Package_Declaration_Lists
2079 (Pack_Decl : Node_Id;
2080 Body_List : out List_Id;
2081 Call_List : out List_Id;
2082 Spec_List : out List_Id);
2083 -- Obtain the various declarative lists of package declaration Pack_Decl
2084 -- needed to insert the initial condition procedure and the call to it.
2085 -- The lists are as follows:
2087 -- * Body_List - used to insert the initial condition procedure body
2089 -- * Call_List - used to insert the call to the initial condition
2090 -- procedure.
2092 -- * Spec_List - used to insert the initial condition procedure spec
2094 --------------------------------
2095 -- Extract_Package_Body_Lists --
2096 --------------------------------
2098 procedure Extract_Package_Body_Lists
2099 (Pack_Body : Node_Id;
2100 Body_List : out List_Id;
2101 Call_List : out List_Id;
2102 Spec_List : out List_Id)
2104 Pack_Spec : constant Entity_Id := Corresponding_Spec (Pack_Body);
2106 Dummy_1 : List_Id;
2107 Dummy_2 : List_Id;
2108 HSS : Node_Id;
2110 begin
2111 pragma Assert (Present (Pack_Spec));
2113 -- The different parts of the invariant procedure are inserted as
2114 -- follows:
2116 -- package Pack is package body Pack is
2117 -- <IC spec> <IC body>
2118 -- private begin
2119 -- ... <IC call>
2120 -- end Pack; end Pack;
2122 -- The initial condition procedure spec is inserted in the visible
2123 -- declaration of the corresponding package spec.
2125 Extract_Package_Declaration_Lists
2126 (Pack_Decl => Unit_Declaration_Node (Pack_Spec),
2127 Body_List => Dummy_1,
2128 Call_List => Dummy_2,
2129 Spec_List => Spec_List);
2131 -- The initial condition procedure body is added to the declarations
2132 -- of the package body.
2134 Body_List := Declarations (Pack_Body);
2136 if No (Body_List) then
2137 Body_List := New_List;
2138 Set_Declarations (Pack_Body, Body_List);
2139 end if;
2141 -- The call to the initial condition procedure is inserted in the
2142 -- statements of the package body.
2144 HSS := Handled_Statement_Sequence (Pack_Body);
2146 if No (HSS) then
2147 HSS :=
2148 Make_Handled_Sequence_Of_Statements (Sloc (Pack_Body),
2149 Statements => New_List);
2150 Set_Handled_Statement_Sequence (Pack_Body, HSS);
2151 end if;
2153 Call_List := Statements (HSS);
2154 end Extract_Package_Body_Lists;
2156 ---------------------------------------
2157 -- Extract_Package_Declaration_Lists --
2158 ---------------------------------------
2160 procedure Extract_Package_Declaration_Lists
2161 (Pack_Decl : Node_Id;
2162 Body_List : out List_Id;
2163 Call_List : out List_Id;
2164 Spec_List : out List_Id)
2166 Pack_Spec : constant Node_Id := Specification (Pack_Decl);
2168 begin
2169 -- The different parts of the invariant procedure are inserted as
2170 -- follows:
2172 -- package Pack is
2173 -- <IC spec>
2174 -- <IC body>
2175 -- private
2176 -- <IC call>
2177 -- end Pack;
2179 -- The initial condition procedure spec and body are inserted in the
2180 -- visible declarations of the package spec.
2182 Body_List := Visible_Declarations (Pack_Spec);
2184 if No (Body_List) then
2185 Body_List := New_List;
2186 Set_Visible_Declarations (Pack_Spec, Body_List);
2187 end if;
2189 Spec_List := Body_List;
2191 -- The call to the initial procedure is inserted in the private
2192 -- declarations of the package spec.
2194 Call_List := Private_Declarations (Pack_Spec);
2196 if No (Call_List) then
2197 Call_List := New_List;
2198 Set_Private_Declarations (Pack_Spec, Call_List);
2199 end if;
2200 end Extract_Package_Declaration_Lists;
2202 -- Local variables
2204 IC_Prag : constant Node_Id :=
2205 Get_Pragma (Pack_Id, Pragma_Initial_Condition);
2207 Body_List : List_Id;
2208 Call : Node_Id;
2209 Call_List : List_Id;
2210 Call_Loc : Source_Ptr;
2211 Expr : Node_Id;
2212 Loc : Source_Ptr;
2213 Proc_Body : Node_Id;
2214 Proc_Body_Id : Entity_Id;
2215 Proc_Decl : Node_Id;
2216 Proc_Id : Entity_Id;
2217 Spec_List : List_Id;
2219 -- Start of processing for Expand_Pragma_Initial_Condition
2221 begin
2222 -- Nothing to do when the package is not subject to an Initial_Condition
2223 -- pragma.
2225 if No (IC_Prag) then
2226 return;
2227 end if;
2229 Expr := Get_Pragma_Arg (First (Pragma_Argument_Associations (IC_Prag)));
2230 Loc := Sloc (IC_Prag);
2232 -- Nothing to do when the pragma is ignored because its semantics are
2233 -- suppressed.
2235 if Is_Ignored (IC_Prag) then
2236 return;
2238 -- Nothing to do when the pragma or its argument are illegal because
2239 -- there is no valid expression to check.
2241 elsif Error_Posted (IC_Prag) or else Error_Posted (Expr) then
2242 return;
2243 end if;
2245 -- Obtain the various lists of the context where the individual pieces
2246 -- of the initial condition procedure are to be inserted.
2248 if Nkind (N) = N_Package_Body then
2249 Extract_Package_Body_Lists
2250 (Pack_Body => N,
2251 Body_List => Body_List,
2252 Call_List => Call_List,
2253 Spec_List => Spec_List);
2255 elsif Nkind (N) = N_Package_Declaration then
2256 Extract_Package_Declaration_Lists
2257 (Pack_Decl => N,
2258 Body_List => Body_List,
2259 Call_List => Call_List,
2260 Spec_List => Spec_List);
2262 -- This routine should not be used on anything other than packages
2264 else
2265 pragma Assert (False);
2266 return;
2267 end if;
2269 Proc_Id :=
2270 Make_Defining_Identifier (Loc,
2271 Chars => New_External_Name (Chars (Pack_Id), "Initial_Condition"));
2273 Mutate_Ekind (Proc_Id, E_Procedure);
2274 Set_Is_Initial_Condition_Procedure (Proc_Id);
2276 -- Generate:
2277 -- procedure <Pack_Id>Initial_Condition;
2279 Proc_Decl :=
2280 Make_Subprogram_Declaration (Loc,
2281 Make_Procedure_Specification (Loc,
2282 Defining_Unit_Name => Proc_Id));
2284 Append_To (Spec_List, Proc_Decl);
2286 -- The initial condition procedure requires debug info when initial
2287 -- condition is subject to Source Coverage Obligations.
2289 if Generate_SCO then
2290 Set_Debug_Info_Needed (Proc_Id);
2291 end if;
2293 -- Generate:
2294 -- procedure <Pack_Id>Initial_Condition is
2295 -- begin
2296 -- pragma Check (Initial_Condition, <Expr>);
2297 -- end <Pack_Id>Initial_Condition;
2299 Proc_Body :=
2300 Make_Subprogram_Body (Loc,
2301 Specification =>
2302 Copy_Subprogram_Spec (Specification (Proc_Decl)),
2303 Declarations => Empty_List,
2304 Handled_Statement_Sequence =>
2305 Make_Handled_Sequence_Of_Statements (Loc,
2306 Statements => New_List (
2307 Make_Pragma (Loc,
2308 Chars => Name_Check,
2309 Pragma_Argument_Associations => New_List (
2310 Make_Pragma_Argument_Association (Loc,
2311 Expression =>
2312 Make_Identifier (Loc, Name_Initial_Condition)),
2313 Make_Pragma_Argument_Association (Loc,
2314 Expression => New_Copy_Tree (Expr)))))));
2316 Append_To (Body_List, Proc_Body);
2318 -- The initial condition procedure requires debug info when initial
2319 -- condition is subject to Source Coverage Obligations.
2321 Proc_Body_Id := Defining_Entity (Proc_Body);
2323 if Generate_SCO then
2324 Set_Debug_Info_Needed (Proc_Body_Id);
2325 end if;
2327 -- The location of the initial condition procedure call must be as close
2328 -- as possible to the intended semantic location of the check because
2329 -- the ABE mechanism relies heavily on accurate locations.
2331 Call_Loc := End_Keyword_Location (N);
2333 -- Generate:
2334 -- <Pack_Id>Initial_Condition;
2336 Call :=
2337 Make_Procedure_Call_Statement (Call_Loc,
2338 Name => New_Occurrence_Of (Proc_Id, Call_Loc));
2340 Append_To (Call_List, Call);
2342 Analyze (Proc_Decl);
2343 Analyze (Proc_Body);
2344 Analyze (Call);
2345 end Expand_Pragma_Initial_Condition;
2347 ------------------------------------
2348 -- Expand_Pragma_Inspection_Point --
2349 ------------------------------------
2351 -- If no argument is given, then we supply a default argument list that
2352 -- includes all objects declared at the source level in all subprograms
2353 -- that enclose the inspection point pragma.
2355 procedure Expand_Pragma_Inspection_Point (N : Node_Id) is
2356 Loc : constant Source_Ptr := Sloc (N);
2357 A : List_Id;
2358 Assoc : Node_Id;
2359 S : Entity_Id;
2360 E : Entity_Id;
2362 Remove_Inspection_Point : Boolean := False;
2363 begin
2364 if No (Pragma_Argument_Associations (N)) then
2365 A := New_List;
2366 S := Current_Scope;
2368 while S /= Standard_Standard loop
2369 E := First_Entity (S);
2370 while Present (E) loop
2371 if Comes_From_Source (E)
2372 and then Is_Object (E)
2373 and then not Is_Entry_Formal (E)
2374 and then not Is_Formal_Object (E)
2375 and then Ekind (E) /= E_Component
2376 and then Ekind (E) /= E_Discriminant
2377 then
2378 Append_To (A,
2379 Make_Pragma_Argument_Association (Loc,
2380 Expression => New_Occurrence_Of (E, Loc)));
2381 end if;
2383 Next_Entity (E);
2384 end loop;
2386 S := Scope (S);
2387 end loop;
2389 Set_Pragma_Argument_Associations (N, A);
2390 end if;
2392 -- Expand the arguments of the pragma. Expanding an entity reference
2393 -- is a noop, except in a protected operation, where a reference may
2394 -- have to be transformed into a reference to the corresponding prival.
2395 -- Are there other pragmas that may require this ???
2397 Assoc := First (Pragma_Argument_Associations (N));
2398 while Present (Assoc) loop
2399 Expand (Expression (Assoc));
2400 Next (Assoc);
2401 end loop;
2403 -- If any of the references have a freeze node, it must appear before
2404 -- pragma Inspection_Point, otherwise the entity won't be available when
2405 -- Gigi processes Inspection_Point.
2406 -- When this requirement isn't met, turn the pragma into a no-op.
2408 Assoc := First (Pragma_Argument_Associations (N));
2409 while Present (Assoc) loop
2411 if Present (Freeze_Node (Entity (Expression (Assoc)))) and then
2412 not Is_Frozen (Entity (Expression (Assoc)))
2413 then
2414 Error_Msg_NE ("??inspection point references unfrozen object &",
2415 Assoc,
2416 Entity (Expression (Assoc)));
2417 Remove_Inspection_Point := True;
2418 end if;
2420 Next (Assoc);
2421 end loop;
2423 if Remove_Inspection_Point then
2424 Error_Msg_N ("\pragma will be ignored", N);
2426 -- We can't just remove the pragma from the tree as it might be
2427 -- iterated over by the caller. Turn it into a null statement
2428 -- instead.
2430 Rewrite (N, Make_Null_Statement (Sloc (N)));
2431 end if;
2432 end Expand_Pragma_Inspection_Point;
2434 --------------------------------------
2435 -- Expand_Pragma_Interrupt_Priority --
2436 --------------------------------------
2438 -- Supply default argument if none exists (System.Interrupt_Priority'Last)
2440 procedure Expand_Pragma_Interrupt_Priority (N : Node_Id) is
2441 Loc : constant Source_Ptr := Sloc (N);
2442 begin
2443 if No (Pragma_Argument_Associations (N)) then
2444 Set_Pragma_Argument_Associations (N, New_List (
2445 Make_Pragma_Argument_Association (Loc,
2446 Expression =>
2447 Make_Attribute_Reference (Loc,
2448 Prefix =>
2449 New_Occurrence_Of (RTE (RE_Interrupt_Priority), Loc),
2450 Attribute_Name => Name_Last))));
2451 end if;
2452 end Expand_Pragma_Interrupt_Priority;
2454 --------------------------------
2455 -- Expand_Pragma_Loop_Variant --
2456 --------------------------------
2458 -- Pragma Loop_Variant is expanded in the following manner:
2460 -- Original code
2462 -- for | while ... loop
2463 -- <preceding source statements>
2464 -- pragma Loop_Variant
2465 -- (Increases => Incr_Expr,
2466 -- Decreases => Decr_Expr);
2467 -- <succeeding source statements>
2468 -- end loop;
2470 -- Expanded code
2472 -- Curr_1 : <type of Incr_Expr>;
2473 -- Curr_2 : <type of Decr_Expr>;
2474 -- Old_1 : <type of Incr_Expr>;
2475 -- Old_2 : <type of Decr_Expr>;
2476 -- Flag : Boolean := False;
2478 -- for | while ... loop
2479 -- <preceding source statements>
2481 -- if Flag then
2482 -- Old_1 := Curr_1;
2483 -- Old_2 := Curr_2;
2484 -- end if;
2486 -- Curr_1 := <Incr_Expr>;
2487 -- Curr_2 := <Decr_Expr>;
2489 -- if Flag then
2490 -- if Curr_1 /= Old_1 then
2491 -- pragma Check (Loop_Variant, Curr_1 > Old_1);
2492 -- else
2493 -- pragma Check (Loop_Variant, Curr_2 < Old_2);
2494 -- end if;
2495 -- else
2496 -- Flag := True;
2497 -- end if;
2499 -- <succeeding source statements>
2500 -- end loop;
2502 procedure Expand_Pragma_Loop_Variant (N : Node_Id) is
2503 Loc : constant Source_Ptr := Sloc (N);
2504 Last_Var : constant Node_Id :=
2505 Last (Pragma_Argument_Associations (N));
2507 Curr_Assign : List_Id := No_List;
2508 Flag_Id : Entity_Id := Empty;
2509 If_Stmt : Node_Id := Empty;
2510 Old_Assign : List_Id := No_List;
2511 Loop_Scop : Entity_Id;
2512 Loop_Stmt : Node_Id;
2513 Variant : Node_Id;
2515 procedure Process_Variant (Variant : Node_Id; Is_Last : Boolean);
2516 -- Process a single increasing / decreasing termination variant. Flag
2517 -- Is_Last should be set when processing the last variant.
2519 ---------------------
2520 -- Process_Variant --
2521 ---------------------
2523 procedure Process_Variant (Variant : Node_Id; Is_Last : Boolean) is
2524 Expr : constant Node_Id := Expression (Variant);
2525 Expr_Typ : constant Entity_Id := Etype (Expr);
2526 Loc : constant Source_Ptr := Sloc (Expr);
2527 Loop_Loc : constant Source_Ptr := Sloc (Loop_Stmt);
2528 Curr_Id : Entity_Id;
2529 Old_Id : Entity_Id;
2530 Prag : Node_Id;
2532 begin
2533 -- All temporaries generated in this routine must be inserted before
2534 -- the related loop statement. Ensure that the proper scope is on the
2535 -- stack when analyzing the temporaries. Note that we also use the
2536 -- Sloc of the related loop.
2538 Push_Scope (Scope (Loop_Scop));
2540 -- Step 1: Create the declaration of the flag which controls the
2541 -- behavior of the assertion on the first iteration of the loop.
2543 if No (Flag_Id) then
2545 -- Generate:
2546 -- Flag : Boolean := False;
2548 Flag_Id := Make_Temporary (Loop_Loc, 'F');
2550 Insert_Action (Loop_Stmt,
2551 Make_Object_Declaration (Loop_Loc,
2552 Defining_Identifier => Flag_Id,
2553 Object_Definition =>
2554 New_Occurrence_Of (Standard_Boolean, Loop_Loc),
2555 Expression =>
2556 New_Occurrence_Of (Standard_False, Loop_Loc)));
2558 -- Prevent an unwanted optimization where the Current_Value of
2559 -- the flag eliminates the if statement which stores the variant
2560 -- values coming from the previous iteration.
2562 -- Flag : Boolean := False;
2563 -- loop
2564 -- if Flag then -- condition rewritten to False
2565 -- Old_N := Curr_N; -- and if statement eliminated
2566 -- end if;
2567 -- . . .
2568 -- Flag := True;
2569 -- end loop;
2571 Set_Current_Value (Flag_Id, Empty);
2572 end if;
2574 -- Step 2: Create the temporaries which store the old and current
2575 -- values of the associated expression.
2577 -- Generate:
2578 -- Curr : <type of Expr>;
2580 Curr_Id := Make_Temporary (Loc, 'C');
2582 Insert_Action (Loop_Stmt,
2583 Make_Object_Declaration (Loop_Loc,
2584 Defining_Identifier => Curr_Id,
2585 Object_Definition => New_Occurrence_Of (Expr_Typ, Loop_Loc)));
2587 -- Generate:
2588 -- Old : <type of Expr>;
2590 Old_Id := Make_Temporary (Loc, 'P');
2592 Insert_Action (Loop_Stmt,
2593 Make_Object_Declaration (Loop_Loc,
2594 Defining_Identifier => Old_Id,
2595 Object_Definition => New_Occurrence_Of (Expr_Typ, Loop_Loc)));
2597 -- Restore original scope after all temporaries have been analyzed
2599 Pop_Scope;
2601 -- Step 3: Store value of the expression from the previous iteration
2603 -- Generate:
2604 -- Old := Curr;
2606 Append_New_To (Old_Assign,
2607 Make_Assignment_Statement (Loc,
2608 Name => New_Occurrence_Of (Old_Id, Loc),
2609 Expression => New_Occurrence_Of (Curr_Id, Loc)));
2611 -- Step 4: Store the current value of the expression
2613 -- Generate:
2614 -- Curr := <Expr>;
2616 Append_New_To (Curr_Assign,
2617 Make_Assignment_Statement (Loc,
2618 Name => New_Occurrence_Of (Curr_Id, Loc),
2619 Expression => Relocate_Node (Expr)));
2621 -- Step 5: Create corresponding assertion to verify change of value
2623 -- Generate:
2624 -- pragma Check (Loop_Variant, Curr <|> Old);
2626 Prag :=
2627 Make_Pragma (Loc,
2628 Chars => Name_Check,
2629 Pragma_Argument_Associations => New_List (
2630 Make_Pragma_Argument_Association (Loc,
2631 Expression => Make_Identifier (Loc, Name_Loop_Variant)),
2632 Make_Pragma_Argument_Association (Loc,
2633 Expression =>
2634 Make_Variant_Comparison (Loc,
2635 Mode => Chars (Variant),
2636 Curr_Val => New_Occurrence_Of (Curr_Id, Loc),
2637 Old_Val => New_Occurrence_Of (Old_Id, Loc)))));
2639 -- Generate:
2640 -- if Curr /= Old then
2641 -- <Prag>;
2643 if No (If_Stmt) then
2645 -- When there is just one termination variant, do not compare the
2646 -- old and current value for equality, just check the pragma.
2648 if Is_Last then
2649 If_Stmt := Prag;
2650 else
2651 If_Stmt :=
2652 Make_If_Statement (Loc,
2653 Condition =>
2654 Make_Op_Ne (Loc,
2655 Left_Opnd => New_Occurrence_Of (Curr_Id, Loc),
2656 Right_Opnd => New_Occurrence_Of (Old_Id, Loc)),
2657 Then_Statements => New_List (Prag));
2658 end if;
2660 -- Generate:
2661 -- else
2662 -- <Prag>;
2663 -- end if;
2665 elsif Is_Last then
2666 Set_Else_Statements (If_Stmt, New_List (Prag));
2668 -- Generate:
2669 -- elsif Curr /= Old then
2670 -- <Prag>;
2672 else
2673 if Elsif_Parts (If_Stmt) = No_List then
2674 Set_Elsif_Parts (If_Stmt, New_List);
2675 end if;
2677 Append_To (Elsif_Parts (If_Stmt),
2678 Make_Elsif_Part (Loc,
2679 Condition =>
2680 Make_Op_Ne (Loc,
2681 Left_Opnd => New_Occurrence_Of (Curr_Id, Loc),
2682 Right_Opnd => New_Occurrence_Of (Old_Id, Loc)),
2683 Then_Statements => New_List (Prag)));
2684 end if;
2685 end Process_Variant;
2687 -- Start of processing for Expand_Pragma_Loop_Variant
2689 begin
2690 -- If pragma is not enabled, rewrite as Null statement. If pragma is
2691 -- disabled, it has already been rewritten as a Null statement.
2693 if Is_Ignored (N) then
2694 Rewrite (N, Make_Null_Statement (Loc));
2695 Analyze (N);
2696 return;
2697 end if;
2699 -- The expansion of Loop_Variant is quite distributed as it produces
2700 -- various statements to capture and compare the arguments. To preserve
2701 -- the original context, set the Is_Assertion_Expr flag. This aids the
2702 -- Ghost legality checks when verifying the placement of a reference to
2703 -- a Ghost entity.
2705 In_Assertion_Expr := In_Assertion_Expr + 1;
2707 -- Locate the enclosing loop for which this assertion applies. In the
2708 -- case of Ada 2012 array iteration, we might be dealing with nested
2709 -- loops. Only the outermost loop has an identifier.
2711 Loop_Stmt := N;
2712 while Present (Loop_Stmt) loop
2713 if Nkind (Loop_Stmt) = N_Loop_Statement
2714 and then Present (Identifier (Loop_Stmt))
2715 then
2716 exit;
2717 end if;
2719 Loop_Stmt := Parent (Loop_Stmt);
2720 end loop;
2722 Loop_Scop := Entity (Identifier (Loop_Stmt));
2724 -- Create the circuitry which verifies individual variants
2726 Variant := First (Pragma_Argument_Associations (N));
2727 while Present (Variant) loop
2728 Process_Variant (Variant, Is_Last => Variant = Last_Var);
2729 Next (Variant);
2730 end loop;
2732 -- Construct the segment which stores the old values of all expressions.
2733 -- Generate:
2734 -- if Flag then
2735 -- <Old_Assign>
2736 -- end if;
2738 Insert_Action (N,
2739 Make_If_Statement (Loc,
2740 Condition => New_Occurrence_Of (Flag_Id, Loc),
2741 Then_Statements => Old_Assign));
2743 -- Update the values of all expressions
2745 Insert_Actions (N, Curr_Assign);
2747 -- Add the assertion circuitry to test all changes in expressions.
2748 -- Generate:
2749 -- if Flag then
2750 -- <If_Stmt>
2751 -- else
2752 -- Flag := True;
2753 -- end if;
2755 Insert_Action (N,
2756 Make_If_Statement (Loc,
2757 Condition => New_Occurrence_Of (Flag_Id, Loc),
2758 Then_Statements => New_List (If_Stmt),
2759 Else_Statements => New_List (
2760 Make_Assignment_Statement (Loc,
2761 Name => New_Occurrence_Of (Flag_Id, Loc),
2762 Expression => New_Occurrence_Of (Standard_True, Loc)))));
2764 -- Note: the pragma has been completely transformed into a sequence of
2765 -- corresponding declarations and statements. We leave it in the tree
2766 -- for documentation purposes. It will be ignored by the backend.
2768 In_Assertion_Expr := In_Assertion_Expr - 1;
2769 end Expand_Pragma_Loop_Variant;
2771 --------------------------------
2772 -- Expand_Pragma_Psect_Object --
2773 --------------------------------
2775 -- Convert to Common_Object, and expand the resulting pragma
2777 procedure Expand_Pragma_Psect_Object (N : Node_Id)
2778 renames Expand_Pragma_Common_Object;
2780 -------------------------------------
2781 -- Expand_Pragma_Relative_Deadline --
2782 -------------------------------------
2784 procedure Expand_Pragma_Relative_Deadline (N : Node_Id) is
2785 P : constant Node_Id := Parent (N);
2786 Loc : constant Source_Ptr := Sloc (N);
2788 begin
2789 -- Expand the pragma only in the case of the main subprogram. For tasks
2790 -- the expansion is done in exp_ch9. Generate a call to Set_Deadline
2791 -- at Clock plus the relative deadline specified in the pragma. Time
2792 -- values are translated into Duration to allow for non-private
2793 -- addition operation.
2795 if Nkind (P) = N_Subprogram_Body then
2796 Rewrite
2798 Make_Procedure_Call_Statement (Loc,
2799 Name => New_Occurrence_Of (RTE (RE_Set_Deadline), Loc),
2800 Parameter_Associations => New_List (
2801 Unchecked_Convert_To (RTE (RO_RT_Time),
2802 Make_Op_Add (Loc,
2803 Left_Opnd =>
2804 Make_Function_Call (Loc,
2805 New_Occurrence_Of (RTE (RO_RT_To_Duration), Loc),
2806 New_List
2807 (Make_Function_Call
2808 (Loc, New_Occurrence_Of (RTE (RE_Clock), Loc)))),
2809 Right_Opnd =>
2810 Unchecked_Convert_To (
2811 Standard_Duration,
2812 Arg_N (N, 1)))))));
2814 Analyze (N);
2815 end if;
2816 end Expand_Pragma_Relative_Deadline;
2818 --------------------------------------
2819 -- Expand_Pragma_Subprogram_Variant --
2820 --------------------------------------
2822 -- Aspect Subprogram_Variant is expanded in the following manner:
2824 -- Original code
2826 -- procedure Proc (Param : T) with
2827 -- with Variant (Increases => Incr_Expr,
2828 -- Decreases => Decr_Expr)
2829 -- <declarations>
2830 -- is
2831 -- <source statements>
2832 -- Proc (New_Param_Value);
2833 -- end Proc;
2835 -- Expanded code
2837 -- procedure Proc (Param : T) is
2838 -- Old_Incr : constant <type of Incr_Expr> := <Incr_Expr>;
2839 -- Old_Decr : constant <type of Decr_Expr> := <Decr_Expr> ;
2841 -- procedure Variants (Param : T);
2843 -- procedure Variants (Param : T) is
2844 -- Curr_Incr : constant <type of Incr_Expr> := <Incr_Expr>;
2845 -- Curr_Decr : constant <type of Decr_Expr> := <Decr_Expr>;
2846 -- begin
2847 -- if Curr_Incr /= Old_Incr then
2848 -- pragma Check (Variant, Curr_Incr > Old_Incr);
2849 -- else
2850 -- pragma Check (Variant, Curr_Decr < Old_Decr);
2851 -- end if;
2852 -- end Variants;
2854 -- <declarations>
2855 -- begin
2856 -- <source statements>
2857 -- Variants (New_Param_Value);
2858 -- Proc (New_Param_Value);
2859 -- end Proc;
2861 procedure Expand_Pragma_Subprogram_Variant
2862 (Prag : Node_Id;
2863 Subp_Id : Entity_Id;
2864 Body_Decls : List_Id)
2866 Curr_Decls : List_Id;
2867 If_Stmt : Node_Id := Empty;
2869 function Formal_Param_Map
2870 (Old_Subp : Entity_Id;
2871 New_Subp : Entity_Id) return Elist_Id;
2872 -- Given two subprogram entities Old_Subp and New_Subp with the same
2873 -- number of formal parameters return a list of the form:
2875 -- old formal 1
2876 -- new formal 1
2877 -- old formal 2
2878 -- new formal 2
2879 -- ...
2881 -- as required by New_Copy_Tree to replace references to formal
2882 -- parameters of Old_Subp with references to formal parameters of
2883 -- New_Subp.
2885 procedure Process_Variant
2886 (Variant : Node_Id;
2887 Formal_Map : Elist_Id;
2888 Prev_Decl : in out Node_Id;
2889 Is_Last : Boolean);
2890 -- Process a single increasing / decreasing termination variant given by
2891 -- a component association Variant. Formal_Map is a list of formal
2892 -- parameters of the annotated subprogram and of the internal procedure
2893 -- that verifies the variant in the format required by New_Copy_Tree.
2894 -- The Old_... object created by this routine will be appended after
2895 -- Prev_Decl and is stored in this parameter for a next call to this
2896 -- routine. Is_Last is True when there are no more variants to process.
2898 ----------------------
2899 -- Formal_Param_Map --
2900 ----------------------
2902 function Formal_Param_Map
2903 (Old_Subp : Entity_Id;
2904 New_Subp : Entity_Id) return Elist_Id
2906 Old_Formal : Entity_Id := First_Formal (Old_Subp);
2907 New_Formal : Entity_Id := First_Formal (New_Subp);
2909 Param_Map : Elist_Id;
2910 begin
2911 if Present (Old_Formal) then
2912 Param_Map := New_Elmt_List;
2913 while Present (Old_Formal) and then Present (New_Formal) loop
2914 Append_Elmt (Old_Formal, Param_Map);
2915 Append_Elmt (New_Formal, Param_Map);
2917 Next_Formal (Old_Formal);
2918 Next_Formal (New_Formal);
2919 end loop;
2921 return Param_Map;
2922 else
2923 return No_Elist;
2924 end if;
2925 end Formal_Param_Map;
2927 ---------------------
2928 -- Process_Variant --
2929 ---------------------
2931 procedure Process_Variant
2932 (Variant : Node_Id;
2933 Formal_Map : Elist_Id;
2934 Prev_Decl : in out Node_Id;
2935 Is_Last : Boolean)
2937 Expr : constant Node_Id := Expression (Variant);
2938 Expr_Typ : constant Entity_Id := Etype (Expr);
2939 Loc : constant Source_Ptr := Sloc (Expr);
2941 Old_Id : Entity_Id;
2942 Old_Decl : Node_Id;
2943 Curr_Id : Entity_Id;
2944 Curr_Decl : Node_Id;
2945 Prag : Node_Id;
2947 begin
2948 -- Create temporaries that store the old values of the associated
2949 -- expression.
2951 -- Generate:
2952 -- Old : constant <type of Expr> := <Expr>;
2954 Old_Id := Make_Temporary (Loc, 'P');
2956 Old_Decl :=
2957 Make_Object_Declaration (Loc,
2958 Defining_Identifier => Old_Id,
2959 Constant_Present => True,
2960 Object_Definition => New_Occurrence_Of (Expr_Typ, Loc),
2961 Expression => New_Copy_Tree (Expr));
2963 Insert_After_And_Analyze (Prev_Decl, Old_Decl);
2965 Prev_Decl := Old_Decl;
2967 -- Generate:
2968 -- Curr : constant <type of Expr> := <Expr>;
2970 Curr_Id := Make_Temporary (Loc, 'C');
2972 Curr_Decl :=
2973 Make_Object_Declaration (Loc,
2974 Defining_Identifier => Curr_Id,
2975 Constant_Present => True,
2976 Object_Definition => New_Occurrence_Of (Expr_Typ, Loc),
2977 Expression =>
2978 New_Copy_Tree (Expr, Map => Formal_Map));
2980 Append (Curr_Decl, Curr_Decls);
2982 -- Generate:
2983 -- pragma Check (Variant, Curr <|> Old);
2985 Prag :=
2986 Make_Pragma (Loc,
2987 Chars => Name_Check,
2988 Pragma_Argument_Associations => New_List (
2989 Make_Pragma_Argument_Association (Loc,
2990 Expression =>
2991 Make_Identifier (Loc,
2992 Name_Subprogram_Variant)),
2993 Make_Pragma_Argument_Association (Loc,
2994 Expression =>
2995 Make_Variant_Comparison (Loc,
2996 Mode => Chars (First (Choices (Variant))),
2997 Curr_Val => New_Occurrence_Of (Curr_Id, Loc),
2998 Old_Val => New_Occurrence_Of (Old_Id, Loc)))));
3000 -- Generate:
3001 -- if Curr /= Old then
3002 -- <Prag>;
3004 if No (If_Stmt) then
3006 -- When there is just one termination variant, do not compare
3007 -- the old and current value for equality, just check the
3008 -- pragma.
3010 if Is_Last then
3011 If_Stmt := Prag;
3012 else
3013 If_Stmt :=
3014 Make_If_Statement (Loc,
3015 Condition =>
3016 Make_Op_Ne (Loc,
3017 Left_Opnd => New_Occurrence_Of (Curr_Id, Loc),
3018 Right_Opnd => New_Occurrence_Of (Old_Id, Loc)),
3019 Then_Statements => New_List (Prag));
3020 end if;
3022 -- Generate:
3023 -- else
3024 -- <Prag>;
3025 -- end if;
3027 elsif Is_Last then
3028 Set_Else_Statements (If_Stmt, New_List (Prag));
3030 -- Generate:
3031 -- elsif Curr /= Old then
3032 -- <Prag>;
3034 else
3035 if Elsif_Parts (If_Stmt) = No_List then
3036 Set_Elsif_Parts (If_Stmt, New_List);
3037 end if;
3039 Append_To (Elsif_Parts (If_Stmt),
3040 Make_Elsif_Part (Loc,
3041 Condition =>
3042 Make_Op_Ne (Loc,
3043 Left_Opnd => New_Occurrence_Of (Curr_Id, Loc),
3044 Right_Opnd => New_Occurrence_Of (Old_Id, Loc)),
3045 Then_Statements => New_List (Prag)));
3046 end if;
3047 end Process_Variant;
3049 -- Local variables
3051 Loc : constant Source_Ptr := Sloc (Prag);
3053 Aggr : Node_Id;
3054 Formal_Map : Elist_Id;
3055 Last : Node_Id;
3056 Last_Variant : Node_Id;
3057 Proc_Bod : Node_Id;
3058 Proc_Decl : Node_Id;
3059 Proc_Id : Entity_Id;
3060 Proc_Spec : Node_Id;
3061 Variant : Node_Id;
3063 begin
3064 -- Do nothing if pragma is not present or is disabled
3066 if Is_Ignored (Prag) then
3067 return;
3068 end if;
3070 Aggr := Expression (First (Pragma_Argument_Associations (Prag)));
3072 -- The expansion of Subprogram Variant is quite distributed as it
3073 -- produces various statements to capture and compare the arguments.
3074 -- To preserve the original context, set the Is_Assertion_Expr flag.
3075 -- This aids the Ghost legality checks when verifying the placement
3076 -- of a reference to a Ghost entity.
3078 In_Assertion_Expr := In_Assertion_Expr + 1;
3080 -- Create declaration of the procedure that compares values of the
3081 -- variant expressions captured at the start of subprogram with their
3082 -- values at the recursive call of the subprogram.
3084 Proc_Id := Make_Defining_Identifier (Loc, Name_uVariants);
3086 Proc_Spec :=
3087 Make_Procedure_Specification
3088 (Loc,
3089 Defining_Unit_Name => Proc_Id,
3090 Parameter_Specifications => Copy_Parameter_List (Subp_Id));
3092 Proc_Decl :=
3093 Make_Subprogram_Declaration (Loc, Proc_Spec);
3095 Insert_Before_First_Source_Declaration (Proc_Decl, Body_Decls);
3096 Analyze (Proc_Decl);
3098 -- Create a mapping between formals of the annotated subprogram (which
3099 -- are used to compute values of the variant expression at the start of
3100 -- subprogram) and formals of the internal procedure (which are used to
3101 -- compute values of of the variant expression at the recursive call).
3103 Formal_Map :=
3104 Formal_Param_Map (Old_Subp => Subp_Id, New_Subp => Proc_Id);
3106 -- Process invidual increasing / decreasing variants
3108 Last := Proc_Decl;
3109 Curr_Decls := New_List;
3110 Last_Variant := Nlists.Last (Component_Associations (Aggr));
3112 Variant := First (Component_Associations (Aggr));
3113 while Present (Variant) loop
3114 Process_Variant
3115 (Variant => Variant,
3116 Formal_Map => Formal_Map,
3117 Prev_Decl => Last,
3118 Is_Last => Variant = Last_Variant);
3119 Next (Variant);
3120 end loop;
3122 -- Create a subprogram body with declarations of objects that capture
3123 -- the current values of variant expressions at a recursive call and an
3124 -- if-then-else statement that compares current with old values.
3126 Proc_Bod :=
3127 Make_Subprogram_Body (Loc,
3128 Specification =>
3129 Copy_Subprogram_Spec (Proc_Spec),
3130 Declarations => Curr_Decls,
3131 Handled_Statement_Sequence =>
3132 Make_Handled_Sequence_Of_Statements (Loc,
3133 Statements => New_List (If_Stmt),
3134 End_Label => Make_Identifier (Loc, Chars (Proc_Id))));
3136 Insert_After_And_Analyze (Last, Proc_Bod);
3138 -- Restore assertion context
3140 In_Assertion_Expr := In_Assertion_Expr - 1;
3142 -- Rewrite the aspect expression, which is no longer needed, with
3143 -- a reference to the procedure that has just been created. We will
3144 -- generate a call to this procedure at each recursive call of the
3145 -- subprogram that has been annotated with Subprogram_Variant.
3147 Rewrite (Aggr, New_Occurrence_Of (Proc_Id, Loc));
3148 end Expand_Pragma_Subprogram_Variant;
3150 -------------------------------------------
3151 -- Expand_Pragma_Suppress_Initialization --
3152 -------------------------------------------
3154 procedure Expand_Pragma_Suppress_Initialization (N : Node_Id) is
3155 Def_Id : constant Entity_Id := Entity (Arg_N (N, 1));
3157 begin
3158 -- Variable case (we have to undo any initialization already done)
3160 if Ekind (Def_Id) = E_Variable then
3161 Undo_Initialization (Def_Id, N);
3162 end if;
3163 end Expand_Pragma_Suppress_Initialization;
3165 -------------------------
3166 -- Undo_Initialization --
3167 -------------------------
3169 procedure Undo_Initialization (Def_Id : Entity_Id; N : Node_Id) is
3170 Init_Call : Node_Id;
3172 begin
3173 -- When applied to a variable, the default initialization must not be
3174 -- done. As it is already done when the pragma is found, we just get rid
3175 -- of the call to the initialization procedure which followed the object
3176 -- declaration. The call is inserted after the declaration, but validity
3177 -- checks may also have been inserted and thus the initialization call
3178 -- does not necessarily appear immediately after the object declaration.
3180 -- We can't use the freezing mechanism for this purpose, since we have
3181 -- to elaborate the initialization expression when it is first seen (so
3182 -- this elaboration cannot be deferred to the freeze point).
3184 -- Find and remove generated initialization call for object, if any
3186 Init_Call := Remove_Init_Call (Def_Id, Rep_Clause => N);
3188 -- Any default initialization expression should be removed (e.g.
3189 -- null defaults for access objects, zero initialization of packed
3190 -- bit arrays). Imported objects aren't allowed to have explicit
3191 -- initialization, so the expression must have been generated by
3192 -- the compiler.
3194 if No (Init_Call) and then Present (Expression (Parent (Def_Id))) then
3195 Set_Expression (Parent (Def_Id), Empty);
3196 end if;
3198 -- The object may not have any initialization, but in the presence of
3199 -- Initialize_Scalars code is inserted after then declaration, which
3200 -- must now be removed as well. The code carries the same source
3201 -- location as the declaration itself.
3203 if Initialize_Scalars and then Is_Array_Type (Etype (Def_Id)) then
3204 declare
3205 Init : Node_Id;
3206 Nxt : Node_Id;
3207 begin
3208 Init := Next (Parent (Def_Id));
3209 while not Comes_From_Source (Init)
3210 and then Sloc (Init) = Sloc (Def_Id)
3211 loop
3212 Nxt := Next (Init);
3213 Remove (Init);
3214 Init := Nxt;
3215 end loop;
3216 end;
3217 end if;
3218 end Undo_Initialization;
3220 end Exp_Prag;