PR target/81369
[official-gcc.git] / gcc / ada / sem_prag.adb
blob6aad5d49a54d2dc17a30119ade58d124b07ef3c4
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- S E M _ P R A G --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2017, 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 -- This unit contains the semantic processing for all pragmas, both language
27 -- and implementation defined. For most pragmas, the parser only does the
28 -- most basic job of checking the syntax, so Sem_Prag also contains the code
29 -- to complete the syntax checks. Certain pragmas are handled partially or
30 -- completely by the parser (see Par.Prag for further details).
32 with Aspects; use Aspects;
33 with Atree; use Atree;
34 with Casing; use Casing;
35 with Checks; use Checks;
36 with Contracts; use Contracts;
37 with Csets; use Csets;
38 with Debug; use Debug;
39 with Einfo; use Einfo;
40 with Elists; use Elists;
41 with Errout; use Errout;
42 with Exp_Dist; use Exp_Dist;
43 with Exp_Util; use Exp_Util;
44 with Freeze; use Freeze;
45 with Ghost; use Ghost;
46 with Gnatvsn; use Gnatvsn;
47 with Lib; use Lib;
48 with Lib.Writ; use Lib.Writ;
49 with Lib.Xref; use Lib.Xref;
50 with Namet.Sp; use Namet.Sp;
51 with Nlists; use Nlists;
52 with Nmake; use Nmake;
53 with Output; use Output;
54 with Par_SCO; use Par_SCO;
55 with Restrict; use Restrict;
56 with Rident; use Rident;
57 with Rtsfind; use Rtsfind;
58 with Sem; use Sem;
59 with Sem_Aux; use Sem_Aux;
60 with Sem_Ch3; use Sem_Ch3;
61 with Sem_Ch6; use Sem_Ch6;
62 with Sem_Ch8; use Sem_Ch8;
63 with Sem_Ch12; use Sem_Ch12;
64 with Sem_Ch13; use Sem_Ch13;
65 with Sem_Disp; use Sem_Disp;
66 with Sem_Dist; use Sem_Dist;
67 with Sem_Elim; use Sem_Elim;
68 with Sem_Eval; use Sem_Eval;
69 with Sem_Intr; use Sem_Intr;
70 with Sem_Mech; use Sem_Mech;
71 with Sem_Res; use Sem_Res;
72 with Sem_Type; use Sem_Type;
73 with Sem_Util; use Sem_Util;
74 with Sem_Warn; use Sem_Warn;
75 with Stand; use Stand;
76 with Sinfo; use Sinfo;
77 with Sinfo.CN; use Sinfo.CN;
78 with Sinput; use Sinput;
79 with Stringt; use Stringt;
80 with Stylesw; use Stylesw;
81 with Table;
82 with Targparm; use Targparm;
83 with Tbuild; use Tbuild;
84 with Ttypes;
85 with Uintp; use Uintp;
86 with Uname; use Uname;
87 with Urealp; use Urealp;
88 with Validsw; use Validsw;
89 with Warnsw; use Warnsw;
91 package body Sem_Prag is
93 ----------------------------------------------
94 -- Common Handling of Import-Export Pragmas --
95 ----------------------------------------------
97 -- In the following section, a number of Import_xxx and Export_xxx pragmas
98 -- are defined by GNAT. These are compatible with the DEC pragmas of the
99 -- same name, and all have the following common form and processing:
101 -- pragma Export_xxx
102 -- [Internal =>] LOCAL_NAME
103 -- [, [External =>] EXTERNAL_SYMBOL]
104 -- [, other optional parameters ]);
106 -- pragma Import_xxx
107 -- [Internal =>] LOCAL_NAME
108 -- [, [External =>] EXTERNAL_SYMBOL]
109 -- [, other optional parameters ]);
111 -- EXTERNAL_SYMBOL ::=
112 -- IDENTIFIER
113 -- | static_string_EXPRESSION
115 -- The internal LOCAL_NAME designates the entity that is imported or
116 -- exported, and must refer to an entity in the current declarative
117 -- part (as required by the rules for LOCAL_NAME).
119 -- The external linker name is designated by the External parameter if
120 -- given, or the Internal parameter if not (if there is no External
121 -- parameter, the External parameter is a copy of the Internal name).
123 -- If the External parameter is given as a string, then this string is
124 -- treated as an external name (exactly as though it had been given as an
125 -- External_Name parameter for a normal Import pragma).
127 -- If the External parameter is given as an identifier (or there is no
128 -- External parameter, so that the Internal identifier is used), then
129 -- the external name is the characters of the identifier, translated
130 -- to all lower case letters.
132 -- Note: the external name specified or implied by any of these special
133 -- Import_xxx or Export_xxx pragmas override an external or link name
134 -- specified in a previous Import or Export pragma.
136 -- Note: these and all other DEC-compatible GNAT pragmas allow full use of
137 -- named notation, following the standard rules for subprogram calls, i.e.
138 -- parameters can be given in any order if named notation is used, and
139 -- positional and named notation can be mixed, subject to the rule that all
140 -- positional parameters must appear first.
142 -- Note: All these pragmas are implemented exactly following the DEC design
143 -- and implementation and are intended to be fully compatible with the use
144 -- of these pragmas in the DEC Ada compiler.
146 --------------------------------------------
147 -- Checking for Duplicated External Names --
148 --------------------------------------------
150 -- It is suspicious if two separate Export pragmas use the same external
151 -- name. The following table is used to diagnose this situation so that
152 -- an appropriate warning can be issued.
154 -- The Node_Id stored is for the N_String_Literal node created to hold
155 -- the value of the external name. The Sloc of this node is used to
156 -- cross-reference the location of the duplication.
158 package Externals is new Table.Table (
159 Table_Component_Type => Node_Id,
160 Table_Index_Type => Int,
161 Table_Low_Bound => 0,
162 Table_Initial => 100,
163 Table_Increment => 100,
164 Table_Name => "Name_Externals");
166 -------------------------------------
167 -- Local Subprograms and Variables --
168 -------------------------------------
170 function Adjust_External_Name_Case (N : Node_Id) return Node_Id;
171 -- This routine is used for possible casing adjustment of an explicit
172 -- external name supplied as a string literal (the node N), according to
173 -- the casing requirement of Opt.External_Name_Casing. If this is set to
174 -- As_Is, then the string literal is returned unchanged, but if it is set
175 -- to Uppercase or Lowercase, then a new string literal with appropriate
176 -- casing is constructed.
178 procedure Analyze_Part_Of
179 (Indic : Node_Id;
180 Item_Id : Entity_Id;
181 Encap : Node_Id;
182 Encap_Id : out Entity_Id;
183 Legal : out Boolean);
184 -- Subsidiary to Analyze_Part_Of_In_Decl_Part, Analyze_Part_Of_Option and
185 -- Analyze_Pragma. Perform full analysis of indicator Part_Of. Indic is the
186 -- Part_Of indicator. Item_Id is the entity of an abstract state, object or
187 -- package instantiation. Encap denotes the encapsulating state or single
188 -- concurrent type. Encap_Id is the entity of Encap. Flag Legal is set when
189 -- the indicator is legal.
191 function Appears_In (List : Elist_Id; Item_Id : Entity_Id) return Boolean;
192 -- Subsidiary to analysis of pragmas Depends, Global and Refined_Depends.
193 -- Query whether a particular item appears in a mixed list of nodes and
194 -- entities. It is assumed that all nodes in the list have entities.
196 procedure Check_Postcondition_Use_In_Inlined_Subprogram
197 (Prag : Node_Id;
198 Spec_Id : Entity_Id);
199 -- Subsidiary to the analysis of pragmas Contract_Cases, Postcondition,
200 -- Precondition, Refined_Post and Test_Case. Emit a warning when pragma
201 -- Prag is associated with subprogram Spec_Id subject to Inline_Always.
203 procedure Check_State_And_Constituent_Use
204 (States : Elist_Id;
205 Constits : Elist_Id;
206 Context : Node_Id);
207 -- Subsidiary to the analysis of pragmas [Refined_]Depends, [Refined_]
208 -- Global and Initializes. Determine whether a state from list States and a
209 -- corresponding constituent from list Constits (if any) appear in the same
210 -- context denoted by Context. If this is the case, emit an error.
212 procedure Contract_Freeze_Error
213 (Contract_Id : Entity_Id;
214 Freeze_Id : Entity_Id);
215 -- Subsidiary to the analysis of pragmas Contract_Cases, Part_Of, Post, and
216 -- Pre. Emit a freezing-related error message where Freeze_Id is the entity
217 -- of a body which caused contract "freezing" and Contract_Id denotes the
218 -- entity of the affected contstruct.
220 procedure Duplication_Error (Prag : Node_Id; Prev : Node_Id);
221 -- Subsidiary to all Find_Related_xxx routines. Emit an error on pragma
222 -- Prag that duplicates previous pragma Prev.
224 function Find_Encapsulating_State
225 (States : Elist_Id;
226 Constit_Id : Entity_Id) return Entity_Id;
227 -- Given the entity of a constituent Constit_Id, find the corresponding
228 -- encapsulating state which appears in States. The routine returns Empty
229 -- if no such state is found.
231 function Find_Related_Context
232 (Prag : Node_Id;
233 Do_Checks : Boolean := False) return Node_Id;
234 -- Subsidiary to the analysis of pragmas
235 -- Async_Readers
236 -- Async_Writers
237 -- Constant_After_Elaboration
238 -- Effective_Reads
239 -- Effective_Writers
240 -- Part_Of
241 -- Find the first source declaration or statement found while traversing
242 -- the previous node chain starting from pragma Prag. If flag Do_Checks is
243 -- set, the routine reports duplicate pragmas. The routine returns Empty
244 -- when reaching the start of the node chain.
246 function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id;
247 -- If Def_Id refers to a renamed subprogram, then the base subprogram (the
248 -- original one, following the renaming chain) is returned. Otherwise the
249 -- entity is returned unchanged. Should be in Einfo???
251 function Get_SPARK_Mode_Type (N : Name_Id) return SPARK_Mode_Type;
252 -- Subsidiary to the analysis of pragma SPARK_Mode as well as subprogram
253 -- Get_SPARK_Mode_From_Annotation. Convert a name into a corresponding
254 -- value of type SPARK_Mode_Type.
256 function Has_Extra_Parentheses (Clause : Node_Id) return Boolean;
257 -- Subsidiary to the analysis of pragmas Depends and Refined_Depends.
258 -- Determine whether dependency clause Clause is surrounded by extra
259 -- parentheses. If this is the case, issue an error message.
261 function Is_CCT_Instance
262 (Ref_Id : Entity_Id;
263 Context_Id : Entity_Id) return Boolean;
264 -- Subsidiary to the analysis of pragmas [Refined_]Depends and [Refined_]
265 -- Global. Determine whether entity Ref_Id denotes the current instance of
266 -- a concurrent type. Context_Id denotes the associated context where the
267 -- pragma appears.
269 function Is_Unconstrained_Or_Tagged_Item (Item : Entity_Id) return Boolean;
270 -- Subsidiary to Collect_Subprogram_Inputs_Outputs and the analysis of
271 -- pragma Depends. Determine whether the type of dependency item Item is
272 -- tagged, unconstrained array, unconstrained record or a record with at
273 -- least one unconstrained component.
275 procedure Record_Possible_Body_Reference
276 (State_Id : Entity_Id;
277 Ref : Node_Id);
278 -- Subsidiary to the analysis of pragmas [Refined_]Depends and [Refined_]
279 -- Global. Given an abstract state denoted by State_Id and a reference Ref
280 -- to it, determine whether the reference appears in a package body that
281 -- will eventually refine the state. If this is the case, record the
282 -- reference for future checks (see Analyze_Refined_State_In_Decls).
284 procedure Resolve_State (N : Node_Id);
285 -- Handle the overloading of state names by functions. When N denotes a
286 -- function, this routine finds the corresponding state and sets the entity
287 -- of N to that of the state.
289 procedure Rewrite_Assertion_Kind
290 (N : Node_Id;
291 From_Policy : Boolean := False);
292 -- If N is Pre'Class, Post'Class, Invariant'Class, or Type_Invariant'Class,
293 -- then it is rewritten as an identifier with the corresponding special
294 -- name _Pre, _Post, _Invariant, or _Type_Invariant. Used by pragmas Check
295 -- and Check_Policy. If the names are Precondition or Postcondition, this
296 -- combination is deprecated in favor of Assertion_Policy and Ada2012
297 -- Aspect names. The parameter From_Policy indicates that the pragma
298 -- is the old non-standard Check_Policy and not a rewritten pragma.
300 procedure Set_Elab_Unit_Name (N : Node_Id; With_Item : Node_Id);
301 -- Place semantic information on the argument of an Elaborate/Elaborate_All
302 -- pragma. Entity name for unit and its parents is taken from item in
303 -- previous with_clause that mentions the unit.
305 Dummy : Integer := 0;
306 pragma Volatile (Dummy);
307 -- Dummy volatile integer used in bodies of ip/rv to prevent optimization
309 procedure ip;
310 pragma No_Inline (ip);
311 -- A dummy procedure called when pragma Inspection_Point is analyzed. This
312 -- is just to help debugging the front end. If a pragma Inspection_Point
313 -- is added to a source program, then breaking on ip will get you to that
314 -- point in the program.
316 procedure rv;
317 pragma No_Inline (rv);
318 -- This is a dummy function called by the processing for pragma Reviewable.
319 -- It is there for assisting front end debugging. By placing a Reviewable
320 -- pragma in the source program, a breakpoint on rv catches this place in
321 -- the source, allowing convenient stepping to the point of interest.
323 -------------------------------
324 -- Adjust_External_Name_Case --
325 -------------------------------
327 function Adjust_External_Name_Case (N : Node_Id) return Node_Id is
328 CC : Char_Code;
330 begin
331 -- Adjust case of literal if required
333 if Opt.External_Name_Exp_Casing = As_Is then
334 return N;
336 else
337 -- Copy existing string
339 Start_String;
341 -- Set proper casing
343 for J in 1 .. String_Length (Strval (N)) loop
344 CC := Get_String_Char (Strval (N), J);
346 if Opt.External_Name_Exp_Casing = Uppercase
347 and then CC >= Get_Char_Code ('a')
348 and then CC <= Get_Char_Code ('z')
349 then
350 Store_String_Char (CC - 32);
352 elsif Opt.External_Name_Exp_Casing = Lowercase
353 and then CC >= Get_Char_Code ('A')
354 and then CC <= Get_Char_Code ('Z')
355 then
356 Store_String_Char (CC + 32);
358 else
359 Store_String_Char (CC);
360 end if;
361 end loop;
363 return
364 Make_String_Literal (Sloc (N),
365 Strval => End_String);
366 end if;
367 end Adjust_External_Name_Case;
369 -----------------------------------------
370 -- Analyze_Contract_Cases_In_Decl_Part --
371 -----------------------------------------
373 -- WARNING: This routine manages Ghost regions. Return statements must be
374 -- replaced by gotos which jump to the end of the routine and restore the
375 -- Ghost mode.
377 procedure Analyze_Contract_Cases_In_Decl_Part
378 (N : Node_Id;
379 Freeze_Id : Entity_Id := Empty)
381 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
382 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
384 Others_Seen : Boolean := False;
385 -- This flag is set when an "others" choice is encountered. It is used
386 -- to detect multiple illegal occurrences of "others".
388 procedure Analyze_Contract_Case (CCase : Node_Id);
389 -- Verify the legality of a single contract case
391 ---------------------------
392 -- Analyze_Contract_Case --
393 ---------------------------
395 procedure Analyze_Contract_Case (CCase : Node_Id) is
396 Case_Guard : Node_Id;
397 Conseq : Node_Id;
398 Errors : Nat;
399 Extra_Guard : Node_Id;
401 begin
402 if Nkind (CCase) = N_Component_Association then
403 Case_Guard := First (Choices (CCase));
404 Conseq := Expression (CCase);
406 -- Each contract case must have exactly one case guard
408 Extra_Guard := Next (Case_Guard);
410 if Present (Extra_Guard) then
411 Error_Msg_N
412 ("contract case must have exactly one case guard",
413 Extra_Guard);
414 end if;
416 -- Check placement of OTHERS if available (SPARK RM 6.1.3(1))
418 if Nkind (Case_Guard) = N_Others_Choice then
419 if Others_Seen then
420 Error_Msg_N
421 ("only one others choice allowed in contract cases",
422 Case_Guard);
423 else
424 Others_Seen := True;
425 end if;
427 elsif Others_Seen then
428 Error_Msg_N
429 ("others must be the last choice in contract cases", N);
430 end if;
432 -- Preanalyze the case guard and consequence
434 if Nkind (Case_Guard) /= N_Others_Choice then
435 Errors := Serious_Errors_Detected;
436 Preanalyze_Assert_Expression (Case_Guard, Standard_Boolean);
438 -- Emit a clarification message when the case guard contains
439 -- at least one undefined reference, possibly due to contract
440 -- "freezing".
442 if Errors /= Serious_Errors_Detected
443 and then Present (Freeze_Id)
444 and then Has_Undefined_Reference (Case_Guard)
445 then
446 Contract_Freeze_Error (Spec_Id, Freeze_Id);
447 end if;
448 end if;
450 Errors := Serious_Errors_Detected;
451 Preanalyze_Assert_Expression (Conseq, Standard_Boolean);
453 -- Emit a clarification message when the consequence contains
454 -- at least one undefined reference, possibly due to contract
455 -- "freezing".
457 if Errors /= Serious_Errors_Detected
458 and then Present (Freeze_Id)
459 and then Has_Undefined_Reference (Conseq)
460 then
461 Contract_Freeze_Error (Spec_Id, Freeze_Id);
462 end if;
464 -- The contract case is malformed
466 else
467 Error_Msg_N ("wrong syntax in contract case", CCase);
468 end if;
469 end Analyze_Contract_Case;
471 -- Local variables
473 CCases : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
475 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
476 -- Save the Ghost mode to restore on exit
478 CCase : Node_Id;
479 Restore_Scope : Boolean := False;
481 -- Start of processing for Analyze_Contract_Cases_In_Decl_Part
483 begin
484 -- Do not analyze the pragma multiple times
486 if Is_Analyzed_Pragma (N) then
487 return;
488 end if;
490 -- Set the Ghost mode in effect from the pragma. Due to the delayed
491 -- analysis of the pragma, the Ghost mode at point of declaration and
492 -- point of analysis may not necessarily be the same. Use the mode in
493 -- effect at the point of declaration.
495 Set_Ghost_Mode (N);
497 -- Single and multiple contract cases must appear in aggregate form. If
498 -- this is not the case, then either the parser of the analysis of the
499 -- pragma failed to produce an aggregate.
501 pragma Assert (Nkind (CCases) = N_Aggregate);
503 if Present (Component_Associations (CCases)) then
505 -- Ensure that the formal parameters are visible when analyzing all
506 -- clauses. This falls out of the general rule of aspects pertaining
507 -- to subprogram declarations.
509 if not In_Open_Scopes (Spec_Id) then
510 Restore_Scope := True;
511 Push_Scope (Spec_Id);
513 if Is_Generic_Subprogram (Spec_Id) then
514 Install_Generic_Formals (Spec_Id);
515 else
516 Install_Formals (Spec_Id);
517 end if;
518 end if;
520 CCase := First (Component_Associations (CCases));
521 while Present (CCase) loop
522 Analyze_Contract_Case (CCase);
523 Next (CCase);
524 end loop;
526 if Restore_Scope then
527 End_Scope;
528 end if;
530 -- Currently it is not possible to inline pre/postconditions on a
531 -- subprogram subject to pragma Inline_Always.
533 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
535 -- Otherwise the pragma is illegal
537 else
538 Error_Msg_N ("wrong syntax for constract cases", N);
539 end if;
541 Set_Is_Analyzed_Pragma (N);
543 Restore_Ghost_Mode (Saved_GM);
544 end Analyze_Contract_Cases_In_Decl_Part;
546 ----------------------------------
547 -- Analyze_Depends_In_Decl_Part --
548 ----------------------------------
550 procedure Analyze_Depends_In_Decl_Part (N : Node_Id) is
551 Loc : constant Source_Ptr := Sloc (N);
552 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
553 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
555 All_Inputs_Seen : Elist_Id := No_Elist;
556 -- A list containing the entities of all the inputs processed so far.
557 -- The list is populated with unique entities because the same input
558 -- may appear in multiple input lists.
560 All_Outputs_Seen : Elist_Id := No_Elist;
561 -- A list containing the entities of all the outputs processed so far.
562 -- The list is populated with unique entities because output items are
563 -- unique in a dependence relation.
565 Constits_Seen : Elist_Id := No_Elist;
566 -- A list containing the entities of all constituents processed so far.
567 -- It aids in detecting illegal usage of a state and a corresponding
568 -- constituent in pragma [Refinde_]Depends.
570 Global_Seen : Boolean := False;
571 -- A flag set when pragma Global has been processed
573 Null_Output_Seen : Boolean := False;
574 -- A flag used to track the legality of a null output
576 Result_Seen : Boolean := False;
577 -- A flag set when Spec_Id'Result is processed
579 States_Seen : Elist_Id := No_Elist;
580 -- A list containing the entities of all states processed so far. It
581 -- helps in detecting illegal usage of a state and a corresponding
582 -- constituent in pragma [Refined_]Depends.
584 Subp_Inputs : Elist_Id := No_Elist;
585 Subp_Outputs : Elist_Id := No_Elist;
586 -- Two lists containing the full set of inputs and output of the related
587 -- subprograms. Note that these lists contain both nodes and entities.
589 Task_Input_Seen : Boolean := False;
590 Task_Output_Seen : Boolean := False;
591 -- Flags used to track the implicit dependence of a task unit on itself
593 procedure Add_Item_To_Name_Buffer (Item_Id : Entity_Id);
594 -- Subsidiary routine to Check_Role and Check_Usage. Add the item kind
595 -- to the name buffer. The individual kinds are as follows:
596 -- E_Abstract_State - "state"
597 -- E_Constant - "constant"
598 -- E_Discriminant - "discriminant"
599 -- E_Generic_In_Out_Parameter - "generic parameter"
600 -- E_Generic_In_Parameter - "generic parameter"
601 -- E_In_Parameter - "parameter"
602 -- E_In_Out_Parameter - "parameter"
603 -- E_Loop_Parameter - "loop parameter"
604 -- E_Out_Parameter - "parameter"
605 -- E_Protected_Type - "current instance of protected type"
606 -- E_Task_Type - "current instance of task type"
607 -- E_Variable - "global"
609 procedure Analyze_Dependency_Clause
610 (Clause : Node_Id;
611 Is_Last : Boolean);
612 -- Verify the legality of a single dependency clause. Flag Is_Last
613 -- denotes whether Clause is the last clause in the relation.
615 procedure Check_Function_Return;
616 -- Verify that Funtion'Result appears as one of the outputs
617 -- (SPARK RM 6.1.5(10)).
619 procedure Check_Role
620 (Item : Node_Id;
621 Item_Id : Entity_Id;
622 Is_Input : Boolean;
623 Self_Ref : Boolean);
624 -- Ensure that an item fulfills its designated input and/or output role
625 -- as specified by pragma Global (if any) or the enclosing context. If
626 -- this is not the case, emit an error. Item and Item_Id denote the
627 -- attributes of an item. Flag Is_Input should be set when item comes
628 -- from an input list. Flag Self_Ref should be set when the item is an
629 -- output and the dependency clause has operator "+".
631 procedure Check_Usage
632 (Subp_Items : Elist_Id;
633 Used_Items : Elist_Id;
634 Is_Input : Boolean);
635 -- Verify that all items from Subp_Items appear in Used_Items. Emit an
636 -- error if this is not the case.
638 procedure Normalize_Clause (Clause : Node_Id);
639 -- Remove a self-dependency "+" from the input list of a clause
641 -----------------------------
642 -- Add_Item_To_Name_Buffer --
643 -----------------------------
645 procedure Add_Item_To_Name_Buffer (Item_Id : Entity_Id) is
646 begin
647 if Ekind (Item_Id) = E_Abstract_State then
648 Add_Str_To_Name_Buffer ("state");
650 elsif Ekind (Item_Id) = E_Constant then
651 Add_Str_To_Name_Buffer ("constant");
653 elsif Ekind (Item_Id) = E_Discriminant then
654 Add_Str_To_Name_Buffer ("discriminant");
656 elsif Ekind_In (Item_Id, E_Generic_In_Out_Parameter,
657 E_Generic_In_Parameter)
658 then
659 Add_Str_To_Name_Buffer ("generic parameter");
661 elsif Is_Formal (Item_Id) then
662 Add_Str_To_Name_Buffer ("parameter");
664 elsif Ekind (Item_Id) = E_Loop_Parameter then
665 Add_Str_To_Name_Buffer ("loop parameter");
667 elsif Ekind (Item_Id) = E_Protected_Type
668 or else Is_Single_Protected_Object (Item_Id)
669 then
670 Add_Str_To_Name_Buffer ("current instance of protected type");
672 elsif Ekind (Item_Id) = E_Task_Type
673 or else Is_Single_Task_Object (Item_Id)
674 then
675 Add_Str_To_Name_Buffer ("current instance of task type");
677 elsif Ekind (Item_Id) = E_Variable then
678 Add_Str_To_Name_Buffer ("global");
680 -- The routine should not be called with non-SPARK items
682 else
683 raise Program_Error;
684 end if;
685 end Add_Item_To_Name_Buffer;
687 -------------------------------
688 -- Analyze_Dependency_Clause --
689 -------------------------------
691 procedure Analyze_Dependency_Clause
692 (Clause : Node_Id;
693 Is_Last : Boolean)
695 procedure Analyze_Input_List (Inputs : Node_Id);
696 -- Verify the legality of a single input list
698 procedure Analyze_Input_Output
699 (Item : Node_Id;
700 Is_Input : Boolean;
701 Self_Ref : Boolean;
702 Top_Level : Boolean;
703 Seen : in out Elist_Id;
704 Null_Seen : in out Boolean;
705 Non_Null_Seen : in out Boolean);
706 -- Verify the legality of a single input or output item. Flag
707 -- Is_Input should be set whenever Item is an input, False when it
708 -- denotes an output. Flag Self_Ref should be set when the item is an
709 -- output and the dependency clause has a "+". Flag Top_Level should
710 -- be set whenever Item appears immediately within an input or output
711 -- list. Seen is a collection of all abstract states, objects and
712 -- formals processed so far. Flag Null_Seen denotes whether a null
713 -- input or output has been encountered. Flag Non_Null_Seen denotes
714 -- whether a non-null input or output has been encountered.
716 ------------------------
717 -- Analyze_Input_List --
718 ------------------------
720 procedure Analyze_Input_List (Inputs : Node_Id) is
721 Inputs_Seen : Elist_Id := No_Elist;
722 -- A list containing the entities of all inputs that appear in the
723 -- current input list.
725 Non_Null_Input_Seen : Boolean := False;
726 Null_Input_Seen : Boolean := False;
727 -- Flags used to check the legality of an input list
729 Input : Node_Id;
731 begin
732 -- Multiple inputs appear as an aggregate
734 if Nkind (Inputs) = N_Aggregate then
735 if Present (Component_Associations (Inputs)) then
736 SPARK_Msg_N
737 ("nested dependency relations not allowed", Inputs);
739 elsif Present (Expressions (Inputs)) then
740 Input := First (Expressions (Inputs));
741 while Present (Input) loop
742 Analyze_Input_Output
743 (Item => Input,
744 Is_Input => True,
745 Self_Ref => False,
746 Top_Level => False,
747 Seen => Inputs_Seen,
748 Null_Seen => Null_Input_Seen,
749 Non_Null_Seen => Non_Null_Input_Seen);
751 Next (Input);
752 end loop;
754 -- Syntax error, always report
756 else
757 Error_Msg_N ("malformed input dependency list", Inputs);
758 end if;
760 -- Process a solitary input
762 else
763 Analyze_Input_Output
764 (Item => Inputs,
765 Is_Input => True,
766 Self_Ref => False,
767 Top_Level => False,
768 Seen => Inputs_Seen,
769 Null_Seen => Null_Input_Seen,
770 Non_Null_Seen => Non_Null_Input_Seen);
771 end if;
773 -- Detect an illegal dependency clause of the form
775 -- (null =>[+] null)
777 if Null_Output_Seen and then Null_Input_Seen then
778 SPARK_Msg_N
779 ("null dependency clause cannot have a null input list",
780 Inputs);
781 end if;
782 end Analyze_Input_List;
784 --------------------------
785 -- Analyze_Input_Output --
786 --------------------------
788 procedure Analyze_Input_Output
789 (Item : Node_Id;
790 Is_Input : Boolean;
791 Self_Ref : Boolean;
792 Top_Level : Boolean;
793 Seen : in out Elist_Id;
794 Null_Seen : in out Boolean;
795 Non_Null_Seen : in out Boolean)
797 procedure Current_Task_Instance_Seen;
798 -- Set the appropriate global flag when the current instance of a
799 -- task unit is encountered.
801 --------------------------------
802 -- Current_Task_Instance_Seen --
803 --------------------------------
805 procedure Current_Task_Instance_Seen is
806 begin
807 if Is_Input then
808 Task_Input_Seen := True;
809 else
810 Task_Output_Seen := True;
811 end if;
812 end Current_Task_Instance_Seen;
814 -- Local variables
816 Is_Output : constant Boolean := not Is_Input;
817 Grouped : Node_Id;
818 Item_Id : Entity_Id;
820 -- Start of processing for Analyze_Input_Output
822 begin
823 -- Multiple input or output items appear as an aggregate
825 if Nkind (Item) = N_Aggregate then
826 if not Top_Level then
827 SPARK_Msg_N ("nested grouping of items not allowed", Item);
829 elsif Present (Component_Associations (Item)) then
830 SPARK_Msg_N
831 ("nested dependency relations not allowed", Item);
833 -- Recursively analyze the grouped items
835 elsif Present (Expressions (Item)) then
836 Grouped := First (Expressions (Item));
837 while Present (Grouped) loop
838 Analyze_Input_Output
839 (Item => Grouped,
840 Is_Input => Is_Input,
841 Self_Ref => Self_Ref,
842 Top_Level => False,
843 Seen => Seen,
844 Null_Seen => Null_Seen,
845 Non_Null_Seen => Non_Null_Seen);
847 Next (Grouped);
848 end loop;
850 -- Syntax error, always report
852 else
853 Error_Msg_N ("malformed dependency list", Item);
854 end if;
856 -- Process attribute 'Result in the context of a dependency clause
858 elsif Is_Attribute_Result (Item) then
859 Non_Null_Seen := True;
861 Analyze (Item);
863 -- Attribute 'Result is allowed to appear on the output side of
864 -- a dependency clause (SPARK RM 6.1.5(6)).
866 if Is_Input then
867 SPARK_Msg_N ("function result cannot act as input", Item);
869 elsif Null_Seen then
870 SPARK_Msg_N
871 ("cannot mix null and non-null dependency items", Item);
873 else
874 Result_Seen := True;
875 end if;
877 -- Detect multiple uses of null in a single dependency list or
878 -- throughout the whole relation. Verify the placement of a null
879 -- output list relative to the other clauses (SPARK RM 6.1.5(12)).
881 elsif Nkind (Item) = N_Null then
882 if Null_Seen then
883 SPARK_Msg_N
884 ("multiple null dependency relations not allowed", Item);
886 elsif Non_Null_Seen then
887 SPARK_Msg_N
888 ("cannot mix null and non-null dependency items", Item);
890 else
891 Null_Seen := True;
893 if Is_Output then
894 if not Is_Last then
895 SPARK_Msg_N
896 ("null output list must be the last clause in a "
897 & "dependency relation", Item);
899 -- Catch a useless dependence of the form:
900 -- null =>+ ...
902 elsif Self_Ref then
903 SPARK_Msg_N
904 ("useless dependence, null depends on itself", Item);
905 end if;
906 end if;
907 end if;
909 -- Default case
911 else
912 Non_Null_Seen := True;
914 if Null_Seen then
915 SPARK_Msg_N ("cannot mix null and non-null items", Item);
916 end if;
918 Analyze (Item);
919 Resolve_State (Item);
921 -- Find the entity of the item. If this is a renaming, climb
922 -- the renaming chain to reach the root object. Renamings of
923 -- non-entire objects do not yield an entity (Empty).
925 Item_Id := Entity_Of (Item);
927 if Present (Item_Id) then
929 -- Constants
931 if Ekind_In (Item_Id, E_Constant, E_Loop_Parameter)
932 or else
934 -- Current instances of concurrent types
936 Ekind_In (Item_Id, E_Protected_Type, E_Task_Type)
937 or else
939 -- Formal parameters
941 Ekind_In (Item_Id, E_Generic_In_Out_Parameter,
942 E_Generic_In_Parameter,
943 E_In_Parameter,
944 E_In_Out_Parameter,
945 E_Out_Parameter)
946 or else
948 -- States, variables
950 Ekind_In (Item_Id, E_Abstract_State, E_Variable)
951 then
952 -- The item denotes a concurrent type. Note that single
953 -- protected/task types are not considered here because
954 -- they behave as objects in the context of pragma
955 -- [Refined_]Depends.
957 if Ekind_In (Item_Id, E_Protected_Type, E_Task_Type) then
959 -- This use is legal as long as the concurrent type is
960 -- the current instance of an enclosing type.
962 if Is_CCT_Instance (Item_Id, Spec_Id) then
964 -- The dependence of a task unit on itself is
965 -- implicit and may or may not be explicitly
966 -- specified (SPARK RM 6.1.4).
968 if Ekind (Item_Id) = E_Task_Type then
969 Current_Task_Instance_Seen;
970 end if;
972 -- Otherwise this is not the current instance
974 else
975 SPARK_Msg_N
976 ("invalid use of subtype mark in dependency "
977 & "relation", Item);
978 end if;
980 -- The dependency of a task unit on itself is implicit
981 -- and may or may not be explicitly specified
982 -- (SPARK RM 6.1.4).
984 elsif Is_Single_Task_Object (Item_Id)
985 and then Is_CCT_Instance (Item_Id, Spec_Id)
986 then
987 Current_Task_Instance_Seen;
988 end if;
990 -- Ensure that the item fulfills its role as input and/or
991 -- output as specified by pragma Global or the enclosing
992 -- context.
994 Check_Role (Item, Item_Id, Is_Input, Self_Ref);
996 -- Detect multiple uses of the same state, variable or
997 -- formal parameter. If this is not the case, add the
998 -- item to the list of processed relations.
1000 if Contains (Seen, Item_Id) then
1001 SPARK_Msg_NE
1002 ("duplicate use of item &", Item, Item_Id);
1003 else
1004 Append_New_Elmt (Item_Id, Seen);
1005 end if;
1007 -- Detect illegal use of an input related to a null
1008 -- output. Such input items cannot appear in other
1009 -- input lists (SPARK RM 6.1.5(13)).
1011 if Is_Input
1012 and then Null_Output_Seen
1013 and then Contains (All_Inputs_Seen, Item_Id)
1014 then
1015 SPARK_Msg_N
1016 ("input of a null output list cannot appear in "
1017 & "multiple input lists", Item);
1018 end if;
1020 -- Add an input or a self-referential output to the list
1021 -- of all processed inputs.
1023 if Is_Input or else Self_Ref then
1024 Append_New_Elmt (Item_Id, All_Inputs_Seen);
1025 end if;
1027 -- State related checks (SPARK RM 6.1.5(3))
1029 if Ekind (Item_Id) = E_Abstract_State then
1031 -- Package and subprogram bodies are instantiated
1032 -- individually in a separate compiler pass. Due to
1033 -- this mode of instantiation, the refinement of a
1034 -- state may no longer be visible when a subprogram
1035 -- body contract is instantiated. Since the generic
1036 -- template is legal, do not perform this check in
1037 -- the instance to circumvent this oddity.
1039 if Is_Generic_Instance (Spec_Id) then
1040 null;
1042 -- An abstract state with visible refinement cannot
1043 -- appear in pragma [Refined_]Depends as its place
1044 -- must be taken by some of its constituents
1045 -- (SPARK RM 6.1.4(7)).
1047 elsif Has_Visible_Refinement (Item_Id) then
1048 SPARK_Msg_NE
1049 ("cannot mention state & in dependence relation",
1050 Item, Item_Id);
1051 SPARK_Msg_N ("\use its constituents instead", Item);
1052 return;
1054 -- If the reference to the abstract state appears in
1055 -- an enclosing package body that will eventually
1056 -- refine the state, record the reference for future
1057 -- checks.
1059 else
1060 Record_Possible_Body_Reference
1061 (State_Id => Item_Id,
1062 Ref => Item);
1063 end if;
1064 end if;
1066 -- When the item renames an entire object, replace the
1067 -- item with a reference to the object.
1069 if Entity (Item) /= Item_Id then
1070 Rewrite (Item,
1071 New_Occurrence_Of (Item_Id, Sloc (Item)));
1072 Analyze (Item);
1073 end if;
1075 -- Add the entity of the current item to the list of
1076 -- processed items.
1078 if Ekind (Item_Id) = E_Abstract_State then
1079 Append_New_Elmt (Item_Id, States_Seen);
1081 -- The variable may eventually become a constituent of a
1082 -- single protected/task type. Record the reference now
1083 -- and verify its legality when analyzing the contract of
1084 -- the variable (SPARK RM 9.3).
1086 elsif Ekind (Item_Id) = E_Variable then
1087 Record_Possible_Part_Of_Reference
1088 (Var_Id => Item_Id,
1089 Ref => Item);
1090 end if;
1092 if Ekind_In (Item_Id, E_Abstract_State,
1093 E_Constant,
1094 E_Variable)
1095 and then Present (Encapsulating_State (Item_Id))
1096 then
1097 Append_New_Elmt (Item_Id, Constits_Seen);
1098 end if;
1100 -- All other input/output items are illegal
1101 -- (SPARK RM 6.1.5(1)).
1103 else
1104 SPARK_Msg_N
1105 ("item must denote parameter, variable, state or "
1106 & "current instance of concurren type", Item);
1107 end if;
1109 -- All other input/output items are illegal
1110 -- (SPARK RM 6.1.5(1)). This is a syntax error, always report.
1112 else
1113 Error_Msg_N
1114 ("item must denote parameter, variable, state or current "
1115 & "instance of concurrent type", Item);
1116 end if;
1117 end if;
1118 end Analyze_Input_Output;
1120 -- Local variables
1122 Inputs : Node_Id;
1123 Output : Node_Id;
1124 Self_Ref : Boolean;
1126 Non_Null_Output_Seen : Boolean := False;
1127 -- Flag used to check the legality of an output list
1129 -- Start of processing for Analyze_Dependency_Clause
1131 begin
1132 Inputs := Expression (Clause);
1133 Self_Ref := False;
1135 -- An input list with a self-dependency appears as operator "+" where
1136 -- the actuals inputs are the right operand.
1138 if Nkind (Inputs) = N_Op_Plus then
1139 Inputs := Right_Opnd (Inputs);
1140 Self_Ref := True;
1141 end if;
1143 -- Process the output_list of a dependency_clause
1145 Output := First (Choices (Clause));
1146 while Present (Output) loop
1147 Analyze_Input_Output
1148 (Item => Output,
1149 Is_Input => False,
1150 Self_Ref => Self_Ref,
1151 Top_Level => True,
1152 Seen => All_Outputs_Seen,
1153 Null_Seen => Null_Output_Seen,
1154 Non_Null_Seen => Non_Null_Output_Seen);
1156 Next (Output);
1157 end loop;
1159 -- Process the input_list of a dependency_clause
1161 Analyze_Input_List (Inputs);
1162 end Analyze_Dependency_Clause;
1164 ---------------------------
1165 -- Check_Function_Return --
1166 ---------------------------
1168 procedure Check_Function_Return is
1169 begin
1170 if Ekind_In (Spec_Id, E_Function, E_Generic_Function)
1171 and then not Result_Seen
1172 then
1173 SPARK_Msg_NE
1174 ("result of & must appear in exactly one output list",
1175 N, Spec_Id);
1176 end if;
1177 end Check_Function_Return;
1179 ----------------
1180 -- Check_Role --
1181 ----------------
1183 procedure Check_Role
1184 (Item : Node_Id;
1185 Item_Id : Entity_Id;
1186 Is_Input : Boolean;
1187 Self_Ref : Boolean)
1189 procedure Find_Role
1190 (Item_Is_Input : out Boolean;
1191 Item_Is_Output : out Boolean);
1192 -- Find the input/output role of Item_Id. Flags Item_Is_Input and
1193 -- Item_Is_Output are set depending on the role.
1195 procedure Role_Error
1196 (Item_Is_Input : Boolean;
1197 Item_Is_Output : Boolean);
1198 -- Emit an error message concerning the incorrect use of Item in
1199 -- pragma [Refined_]Depends. Flags Item_Is_Input and Item_Is_Output
1200 -- denote whether the item is an input and/or an output.
1202 ---------------
1203 -- Find_Role --
1204 ---------------
1206 procedure Find_Role
1207 (Item_Is_Input : out Boolean;
1208 Item_Is_Output : out Boolean)
1210 begin
1211 Item_Is_Input := False;
1212 Item_Is_Output := False;
1214 -- Abstract states
1216 if Ekind (Item_Id) = E_Abstract_State then
1218 -- When pragma Global is present, the mode of the state may be
1219 -- further constrained by setting a more restrictive mode.
1221 if Global_Seen then
1222 if Appears_In (Subp_Inputs, Item_Id) then
1223 Item_Is_Input := True;
1224 end if;
1226 if Appears_In (Subp_Outputs, Item_Id) then
1227 Item_Is_Output := True;
1228 end if;
1230 -- Otherwise the state has a default IN OUT mode
1232 else
1233 Item_Is_Input := True;
1234 Item_Is_Output := True;
1235 end if;
1237 -- Constants
1239 elsif Ekind_In (Item_Id, E_Constant,
1240 E_Discriminant,
1241 E_Loop_Parameter)
1242 then
1243 Item_Is_Input := True;
1245 -- Parameters
1247 elsif Ekind_In (Item_Id, E_Generic_In_Parameter,
1248 E_In_Parameter)
1249 then
1250 Item_Is_Input := True;
1252 elsif Ekind_In (Item_Id, E_Generic_In_Out_Parameter,
1253 E_In_Out_Parameter)
1254 then
1255 Item_Is_Input := True;
1256 Item_Is_Output := True;
1258 elsif Ekind (Item_Id) = E_Out_Parameter then
1259 if Scope (Item_Id) = Spec_Id then
1261 -- An OUT parameter of the related subprogram has mode IN
1262 -- if its type is unconstrained or tagged because array
1263 -- bounds, discriminants or tags can be read.
1265 if Is_Unconstrained_Or_Tagged_Item (Item_Id) then
1266 Item_Is_Input := True;
1267 end if;
1269 Item_Is_Output := True;
1271 -- An OUT parameter of an enclosing subprogram behaves as a
1272 -- read-write variable in which case the mode is IN OUT.
1274 else
1275 Item_Is_Input := True;
1276 Item_Is_Output := True;
1277 end if;
1279 -- Protected types
1281 elsif Ekind (Item_Id) = E_Protected_Type then
1283 -- A protected type acts as a formal parameter of mode IN when
1284 -- it applies to a protected function.
1286 if Ekind (Spec_Id) = E_Function then
1287 Item_Is_Input := True;
1289 -- Otherwise the protected type acts as a formal of mode IN OUT
1291 else
1292 Item_Is_Input := True;
1293 Item_Is_Output := True;
1294 end if;
1296 -- Task types
1298 elsif Ekind (Item_Id) = E_Task_Type then
1299 Item_Is_Input := True;
1300 Item_Is_Output := True;
1302 -- Variable case
1304 else pragma Assert (Ekind (Item_Id) = E_Variable);
1306 -- When pragma Global is present, the mode of the variable may
1307 -- be further constrained by setting a more restrictive mode.
1309 if Global_Seen then
1311 -- A variable has mode IN when its type is unconstrained or
1312 -- tagged because array bounds, discriminants or tags can be
1313 -- read.
1315 if Appears_In (Subp_Inputs, Item_Id)
1316 or else Is_Unconstrained_Or_Tagged_Item (Item_Id)
1317 then
1318 Item_Is_Input := True;
1319 end if;
1321 if Appears_In (Subp_Outputs, Item_Id) then
1322 Item_Is_Output := True;
1323 end if;
1325 -- Otherwise the variable has a default IN OUT mode
1327 else
1328 Item_Is_Input := True;
1329 Item_Is_Output := True;
1330 end if;
1331 end if;
1332 end Find_Role;
1334 ----------------
1335 -- Role_Error --
1336 ----------------
1338 procedure Role_Error
1339 (Item_Is_Input : Boolean;
1340 Item_Is_Output : Boolean)
1342 Error_Msg : Name_Id;
1344 begin
1345 Name_Len := 0;
1347 -- When the item is not part of the input and the output set of
1348 -- the related subprogram, then it appears as extra in pragma
1349 -- [Refined_]Depends.
1351 if not Item_Is_Input and then not Item_Is_Output then
1352 Add_Item_To_Name_Buffer (Item_Id);
1353 Add_Str_To_Name_Buffer
1354 (" & cannot appear in dependence relation");
1356 Error_Msg := Name_Find;
1357 SPARK_Msg_NE (Get_Name_String (Error_Msg), Item, Item_Id);
1359 Error_Msg_Name_1 := Chars (Spec_Id);
1360 SPARK_Msg_NE
1361 (Fix_Msg (Spec_Id, "\& is not part of the input or output "
1362 & "set of subprogram %"), Item, Item_Id);
1364 -- The mode of the item and its role in pragma [Refined_]Depends
1365 -- are in conflict. Construct a detailed message explaining the
1366 -- illegality (SPARK RM 6.1.5(5-6)).
1368 else
1369 if Item_Is_Input then
1370 Add_Str_To_Name_Buffer ("read-only");
1371 else
1372 Add_Str_To_Name_Buffer ("write-only");
1373 end if;
1375 Add_Char_To_Name_Buffer (' ');
1376 Add_Item_To_Name_Buffer (Item_Id);
1377 Add_Str_To_Name_Buffer (" & cannot appear as ");
1379 if Item_Is_Input then
1380 Add_Str_To_Name_Buffer ("output");
1381 else
1382 Add_Str_To_Name_Buffer ("input");
1383 end if;
1385 Add_Str_To_Name_Buffer (" in dependence relation");
1386 Error_Msg := Name_Find;
1387 SPARK_Msg_NE (Get_Name_String (Error_Msg), Item, Item_Id);
1388 end if;
1389 end Role_Error;
1391 -- Local variables
1393 Item_Is_Input : Boolean;
1394 Item_Is_Output : Boolean;
1396 -- Start of processing for Check_Role
1398 begin
1399 Find_Role (Item_Is_Input, Item_Is_Output);
1401 -- Input item
1403 if Is_Input then
1404 if not Item_Is_Input then
1405 Role_Error (Item_Is_Input, Item_Is_Output);
1406 end if;
1408 -- Self-referential item
1410 elsif Self_Ref then
1411 if not Item_Is_Input or else not Item_Is_Output then
1412 Role_Error (Item_Is_Input, Item_Is_Output);
1413 end if;
1415 -- Output item
1417 elsif not Item_Is_Output then
1418 Role_Error (Item_Is_Input, Item_Is_Output);
1419 end if;
1420 end Check_Role;
1422 -----------------
1423 -- Check_Usage --
1424 -----------------
1426 procedure Check_Usage
1427 (Subp_Items : Elist_Id;
1428 Used_Items : Elist_Id;
1429 Is_Input : Boolean)
1431 procedure Usage_Error (Item_Id : Entity_Id);
1432 -- Emit an error concerning the illegal usage of an item
1434 -----------------
1435 -- Usage_Error --
1436 -----------------
1438 procedure Usage_Error (Item_Id : Entity_Id) is
1439 Error_Msg : Name_Id;
1441 begin
1442 -- Input case
1444 if Is_Input then
1446 -- Unconstrained and tagged items are not part of the explicit
1447 -- input set of the related subprogram, they do not have to be
1448 -- present in a dependence relation and should not be flagged
1449 -- (SPARK RM 6.1.5(8)).
1451 if not Is_Unconstrained_Or_Tagged_Item (Item_Id) then
1452 Name_Len := 0;
1454 Add_Item_To_Name_Buffer (Item_Id);
1455 Add_Str_To_Name_Buffer
1456 (" & is missing from input dependence list");
1458 Error_Msg := Name_Find;
1459 SPARK_Msg_NE (Get_Name_String (Error_Msg), N, Item_Id);
1460 end if;
1462 -- Output case (SPARK RM 6.1.5(10))
1464 else
1465 Name_Len := 0;
1467 Add_Item_To_Name_Buffer (Item_Id);
1468 Add_Str_To_Name_Buffer
1469 (" & is missing from output dependence list");
1471 Error_Msg := Name_Find;
1472 SPARK_Msg_NE (Get_Name_String (Error_Msg), N, Item_Id);
1473 end if;
1474 end Usage_Error;
1476 -- Local variables
1478 Elmt : Elmt_Id;
1479 Item : Node_Id;
1480 Item_Id : Entity_Id;
1482 -- Start of processing for Check_Usage
1484 begin
1485 if No (Subp_Items) then
1486 return;
1487 end if;
1489 -- Each input or output of the subprogram must appear in a dependency
1490 -- relation.
1492 Elmt := First_Elmt (Subp_Items);
1493 while Present (Elmt) loop
1494 Item := Node (Elmt);
1496 if Nkind (Item) = N_Defining_Identifier then
1497 Item_Id := Item;
1498 else
1499 Item_Id := Entity_Of (Item);
1500 end if;
1502 -- The item does not appear in a dependency
1504 if Present (Item_Id)
1505 and then not Contains (Used_Items, Item_Id)
1506 then
1507 if Is_Formal (Item_Id) then
1508 Usage_Error (Item_Id);
1510 -- The current instance of a protected type behaves as a formal
1511 -- parameter (SPARK RM 6.1.4).
1513 elsif Ekind (Item_Id) = E_Protected_Type
1514 or else Is_Single_Protected_Object (Item_Id)
1515 then
1516 Usage_Error (Item_Id);
1518 -- The current instance of a task type behaves as a formal
1519 -- parameter (SPARK RM 6.1.4).
1521 elsif Ekind (Item_Id) = E_Task_Type
1522 or else Is_Single_Task_Object (Item_Id)
1523 then
1524 -- The dependence of a task unit on itself is implicit and
1525 -- may or may not be explicitly specified (SPARK RM 6.1.4).
1526 -- Emit an error if only one input/output is present.
1528 if Task_Input_Seen /= Task_Output_Seen then
1529 Usage_Error (Item_Id);
1530 end if;
1532 -- States and global objects are not used properly only when
1533 -- the subprogram is subject to pragma Global.
1535 elsif Global_Seen then
1536 Usage_Error (Item_Id);
1537 end if;
1538 end if;
1540 Next_Elmt (Elmt);
1541 end loop;
1542 end Check_Usage;
1544 ----------------------
1545 -- Normalize_Clause --
1546 ----------------------
1548 procedure Normalize_Clause (Clause : Node_Id) is
1549 procedure Create_Or_Modify_Clause
1550 (Output : Node_Id;
1551 Outputs : Node_Id;
1552 Inputs : Node_Id;
1553 After : Node_Id;
1554 In_Place : Boolean;
1555 Multiple : Boolean);
1556 -- Create a brand new clause to represent the self-reference or
1557 -- modify the input and/or output lists of an existing clause. Output
1558 -- denotes a self-referencial output. Outputs is the output list of a
1559 -- clause. Inputs is the input list of a clause. After denotes the
1560 -- clause after which the new clause is to be inserted. Flag In_Place
1561 -- should be set when normalizing the last output of an output list.
1562 -- Flag Multiple should be set when Output comes from a list with
1563 -- multiple items.
1565 -----------------------------
1566 -- Create_Or_Modify_Clause --
1567 -----------------------------
1569 procedure Create_Or_Modify_Clause
1570 (Output : Node_Id;
1571 Outputs : Node_Id;
1572 Inputs : Node_Id;
1573 After : Node_Id;
1574 In_Place : Boolean;
1575 Multiple : Boolean)
1577 procedure Propagate_Output
1578 (Output : Node_Id;
1579 Inputs : Node_Id);
1580 -- Handle the various cases of output propagation to the input
1581 -- list. Output denotes a self-referencial output item. Inputs
1582 -- is the input list of a clause.
1584 ----------------------
1585 -- Propagate_Output --
1586 ----------------------
1588 procedure Propagate_Output
1589 (Output : Node_Id;
1590 Inputs : Node_Id)
1592 function In_Input_List
1593 (Item : Entity_Id;
1594 Inputs : List_Id) return Boolean;
1595 -- Determine whether a particulat item appears in the input
1596 -- list of a clause.
1598 -------------------
1599 -- In_Input_List --
1600 -------------------
1602 function In_Input_List
1603 (Item : Entity_Id;
1604 Inputs : List_Id) return Boolean
1606 Elmt : Node_Id;
1608 begin
1609 Elmt := First (Inputs);
1610 while Present (Elmt) loop
1611 if Entity_Of (Elmt) = Item then
1612 return True;
1613 end if;
1615 Next (Elmt);
1616 end loop;
1618 return False;
1619 end In_Input_List;
1621 -- Local variables
1623 Output_Id : constant Entity_Id := Entity_Of (Output);
1624 Grouped : List_Id;
1626 -- Start of processing for Propagate_Output
1628 begin
1629 -- The clause is of the form:
1631 -- (Output =>+ null)
1633 -- Remove null input and replace it with a copy of the output:
1635 -- (Output => Output)
1637 if Nkind (Inputs) = N_Null then
1638 Rewrite (Inputs, New_Copy_Tree (Output));
1640 -- The clause is of the form:
1642 -- (Output =>+ (Input1, ..., InputN))
1644 -- Determine whether the output is not already mentioned in the
1645 -- input list and if not, add it to the list of inputs:
1647 -- (Output => (Output, Input1, ..., InputN))
1649 elsif Nkind (Inputs) = N_Aggregate then
1650 Grouped := Expressions (Inputs);
1652 if not In_Input_List
1653 (Item => Output_Id,
1654 Inputs => Grouped)
1655 then
1656 Prepend_To (Grouped, New_Copy_Tree (Output));
1657 end if;
1659 -- The clause is of the form:
1661 -- (Output =>+ Input)
1663 -- If the input does not mention the output, group the two
1664 -- together:
1666 -- (Output => (Output, Input))
1668 elsif Entity_Of (Inputs) /= Output_Id then
1669 Rewrite (Inputs,
1670 Make_Aggregate (Loc,
1671 Expressions => New_List (
1672 New_Copy_Tree (Output),
1673 New_Copy_Tree (Inputs))));
1674 end if;
1675 end Propagate_Output;
1677 -- Local variables
1679 Loc : constant Source_Ptr := Sloc (Clause);
1680 New_Clause : Node_Id;
1682 -- Start of processing for Create_Or_Modify_Clause
1684 begin
1685 -- A null output depending on itself does not require any
1686 -- normalization.
1688 if Nkind (Output) = N_Null then
1689 return;
1691 -- A function result cannot depend on itself because it cannot
1692 -- appear in the input list of a relation (SPARK RM 6.1.5(10)).
1694 elsif Is_Attribute_Result (Output) then
1695 SPARK_Msg_N ("function result cannot depend on itself", Output);
1696 return;
1697 end if;
1699 -- When performing the transformation in place, simply add the
1700 -- output to the list of inputs (if not already there). This
1701 -- case arises when dealing with the last output of an output
1702 -- list. Perform the normalization in place to avoid generating
1703 -- a malformed tree.
1705 if In_Place then
1706 Propagate_Output (Output, Inputs);
1708 -- A list with multiple outputs is slowly trimmed until only
1709 -- one element remains. When this happens, replace aggregate
1710 -- with the element itself.
1712 if Multiple then
1713 Remove (Output);
1714 Rewrite (Outputs, Output);
1715 end if;
1717 -- Default case
1719 else
1720 -- Unchain the output from its output list as it will appear in
1721 -- a new clause. Note that we cannot simply rewrite the output
1722 -- as null because this will violate the semantics of pragma
1723 -- Depends.
1725 Remove (Output);
1727 -- Generate a new clause of the form:
1728 -- (Output => Inputs)
1730 New_Clause :=
1731 Make_Component_Association (Loc,
1732 Choices => New_List (Output),
1733 Expression => New_Copy_Tree (Inputs));
1735 -- The new clause contains replicated content that has already
1736 -- been analyzed. There is not need to reanalyze or renormalize
1737 -- it again.
1739 Set_Analyzed (New_Clause);
1741 Propagate_Output
1742 (Output => First (Choices (New_Clause)),
1743 Inputs => Expression (New_Clause));
1745 Insert_After (After, New_Clause);
1746 end if;
1747 end Create_Or_Modify_Clause;
1749 -- Local variables
1751 Outputs : constant Node_Id := First (Choices (Clause));
1752 Inputs : Node_Id;
1753 Last_Output : Node_Id;
1754 Next_Output : Node_Id;
1755 Output : Node_Id;
1757 -- Start of processing for Normalize_Clause
1759 begin
1760 -- A self-dependency appears as operator "+". Remove the "+" from the
1761 -- tree by moving the real inputs to their proper place.
1763 if Nkind (Expression (Clause)) = N_Op_Plus then
1764 Rewrite (Expression (Clause), Right_Opnd (Expression (Clause)));
1765 Inputs := Expression (Clause);
1767 -- Multiple outputs appear as an aggregate
1769 if Nkind (Outputs) = N_Aggregate then
1770 Last_Output := Last (Expressions (Outputs));
1772 Output := First (Expressions (Outputs));
1773 while Present (Output) loop
1775 -- Normalization may remove an output from its list,
1776 -- preserve the subsequent output now.
1778 Next_Output := Next (Output);
1780 Create_Or_Modify_Clause
1781 (Output => Output,
1782 Outputs => Outputs,
1783 Inputs => Inputs,
1784 After => Clause,
1785 In_Place => Output = Last_Output,
1786 Multiple => True);
1788 Output := Next_Output;
1789 end loop;
1791 -- Solitary output
1793 else
1794 Create_Or_Modify_Clause
1795 (Output => Outputs,
1796 Outputs => Empty,
1797 Inputs => Inputs,
1798 After => Empty,
1799 In_Place => True,
1800 Multiple => False);
1801 end if;
1802 end if;
1803 end Normalize_Clause;
1805 -- Local variables
1807 Deps : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
1808 Subp_Id : constant Entity_Id := Defining_Entity (Subp_Decl);
1810 Clause : Node_Id;
1811 Errors : Nat;
1812 Last_Clause : Node_Id;
1813 Restore_Scope : Boolean := False;
1815 -- Start of processing for Analyze_Depends_In_Decl_Part
1817 begin
1818 -- Do not analyze the pragma multiple times
1820 if Is_Analyzed_Pragma (N) then
1821 return;
1822 end if;
1824 -- Empty dependency list
1826 if Nkind (Deps) = N_Null then
1828 -- Gather all states, objects and formal parameters that the
1829 -- subprogram may depend on. These items are obtained from the
1830 -- parameter profile or pragma [Refined_]Global (if available).
1832 Collect_Subprogram_Inputs_Outputs
1833 (Subp_Id => Subp_Id,
1834 Subp_Inputs => Subp_Inputs,
1835 Subp_Outputs => Subp_Outputs,
1836 Global_Seen => Global_Seen);
1838 -- Verify that every input or output of the subprogram appear in a
1839 -- dependency.
1841 Check_Usage (Subp_Inputs, All_Inputs_Seen, True);
1842 Check_Usage (Subp_Outputs, All_Outputs_Seen, False);
1843 Check_Function_Return;
1845 -- Dependency clauses appear as component associations of an aggregate
1847 elsif Nkind (Deps) = N_Aggregate then
1849 -- Do not attempt to perform analysis of a syntactically illegal
1850 -- clause as this will lead to misleading errors.
1852 if Has_Extra_Parentheses (Deps) then
1853 return;
1854 end if;
1856 if Present (Component_Associations (Deps)) then
1857 Last_Clause := Last (Component_Associations (Deps));
1859 -- Gather all states, objects and formal parameters that the
1860 -- subprogram may depend on. These items are obtained from the
1861 -- parameter profile or pragma [Refined_]Global (if available).
1863 Collect_Subprogram_Inputs_Outputs
1864 (Subp_Id => Subp_Id,
1865 Subp_Inputs => Subp_Inputs,
1866 Subp_Outputs => Subp_Outputs,
1867 Global_Seen => Global_Seen);
1869 -- When pragma [Refined_]Depends appears on a single concurrent
1870 -- type, it is relocated to the anonymous object.
1872 if Is_Single_Concurrent_Object (Spec_Id) then
1873 null;
1875 -- Ensure that the formal parameters are visible when analyzing
1876 -- all clauses. This falls out of the general rule of aspects
1877 -- pertaining to subprogram declarations.
1879 elsif not In_Open_Scopes (Spec_Id) then
1880 Restore_Scope := True;
1881 Push_Scope (Spec_Id);
1883 if Ekind (Spec_Id) = E_Task_Type then
1884 if Has_Discriminants (Spec_Id) then
1885 Install_Discriminants (Spec_Id);
1886 end if;
1888 elsif Is_Generic_Subprogram (Spec_Id) then
1889 Install_Generic_Formals (Spec_Id);
1891 else
1892 Install_Formals (Spec_Id);
1893 end if;
1894 end if;
1896 Clause := First (Component_Associations (Deps));
1897 while Present (Clause) loop
1898 Errors := Serious_Errors_Detected;
1900 -- The normalization mechanism may create extra clauses that
1901 -- contain replicated input and output names. There is no need
1902 -- to reanalyze them.
1904 if not Analyzed (Clause) then
1905 Set_Analyzed (Clause);
1907 Analyze_Dependency_Clause
1908 (Clause => Clause,
1909 Is_Last => Clause = Last_Clause);
1910 end if;
1912 -- Do not normalize a clause if errors were detected (count
1913 -- of Serious_Errors has increased) because the inputs and/or
1914 -- outputs may denote illegal items. Normalization is disabled
1915 -- in ASIS mode as it alters the tree by introducing new nodes
1916 -- similar to expansion.
1918 if Serious_Errors_Detected = Errors and then not ASIS_Mode then
1919 Normalize_Clause (Clause);
1920 end if;
1922 Next (Clause);
1923 end loop;
1925 if Restore_Scope then
1926 End_Scope;
1927 end if;
1929 -- Verify that every input or output of the subprogram appear in a
1930 -- dependency.
1932 Check_Usage (Subp_Inputs, All_Inputs_Seen, True);
1933 Check_Usage (Subp_Outputs, All_Outputs_Seen, False);
1934 Check_Function_Return;
1936 -- The dependency list is malformed. This is a syntax error, always
1937 -- report.
1939 else
1940 Error_Msg_N ("malformed dependency relation", Deps);
1941 return;
1942 end if;
1944 -- The top level dependency relation is malformed. This is a syntax
1945 -- error, always report.
1947 else
1948 Error_Msg_N ("malformed dependency relation", Deps);
1949 goto Leave;
1950 end if;
1952 -- Ensure that a state and a corresponding constituent do not appear
1953 -- together in pragma [Refined_]Depends.
1955 Check_State_And_Constituent_Use
1956 (States => States_Seen,
1957 Constits => Constits_Seen,
1958 Context => N);
1960 <<Leave>>
1961 Set_Is_Analyzed_Pragma (N);
1962 end Analyze_Depends_In_Decl_Part;
1964 --------------------------------------------
1965 -- Analyze_External_Property_In_Decl_Part --
1966 --------------------------------------------
1968 procedure Analyze_External_Property_In_Decl_Part
1969 (N : Node_Id;
1970 Expr_Val : out Boolean)
1972 Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
1973 Obj_Decl : constant Node_Id := Find_Related_Context (N);
1974 Obj_Id : constant Entity_Id := Defining_Entity (Obj_Decl);
1975 Expr : Node_Id;
1977 begin
1978 Expr_Val := False;
1980 -- Do not analyze the pragma multiple times
1982 if Is_Analyzed_Pragma (N) then
1983 return;
1984 end if;
1986 Error_Msg_Name_1 := Pragma_Name (N);
1988 -- An external property pragma must apply to an effectively volatile
1989 -- object other than a formal subprogram parameter (SPARK RM 7.1.3(2)).
1990 -- The check is performed at the end of the declarative region due to a
1991 -- possible out-of-order arrangement of pragmas:
1993 -- Obj : ...;
1994 -- pragma Async_Readers (Obj);
1995 -- pragma Volatile (Obj);
1997 if not Is_Effectively_Volatile (Obj_Id) then
1998 SPARK_Msg_N
1999 ("external property % must apply to a volatile object", N);
2000 end if;
2002 -- Ensure that the Boolean expression (if present) is static. A missing
2003 -- argument defaults the value to True (SPARK RM 7.1.2(5)).
2005 Expr_Val := True;
2007 if Present (Arg1) then
2008 Expr := Get_Pragma_Arg (Arg1);
2010 if Is_OK_Static_Expression (Expr) then
2011 Expr_Val := Is_True (Expr_Value (Expr));
2012 end if;
2013 end if;
2015 Set_Is_Analyzed_Pragma (N);
2016 end Analyze_External_Property_In_Decl_Part;
2018 ---------------------------------
2019 -- Analyze_Global_In_Decl_Part --
2020 ---------------------------------
2022 procedure Analyze_Global_In_Decl_Part (N : Node_Id) is
2023 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
2024 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
2025 Subp_Id : constant Entity_Id := Defining_Entity (Subp_Decl);
2027 Constits_Seen : Elist_Id := No_Elist;
2028 -- A list containing the entities of all constituents processed so far.
2029 -- It aids in detecting illegal usage of a state and a corresponding
2030 -- constituent in pragma [Refinde_]Global.
2032 Seen : Elist_Id := No_Elist;
2033 -- A list containing the entities of all the items processed so far. It
2034 -- plays a role in detecting distinct entities.
2036 States_Seen : Elist_Id := No_Elist;
2037 -- A list containing the entities of all states processed so far. It
2038 -- helps in detecting illegal usage of a state and a corresponding
2039 -- constituent in pragma [Refined_]Global.
2041 In_Out_Seen : Boolean := False;
2042 Input_Seen : Boolean := False;
2043 Output_Seen : Boolean := False;
2044 Proof_Seen : Boolean := False;
2045 -- Flags used to verify the consistency of modes
2047 procedure Analyze_Global_List
2048 (List : Node_Id;
2049 Global_Mode : Name_Id := Name_Input);
2050 -- Verify the legality of a single global list declaration. Global_Mode
2051 -- denotes the current mode in effect.
2053 -------------------------
2054 -- Analyze_Global_List --
2055 -------------------------
2057 procedure Analyze_Global_List
2058 (List : Node_Id;
2059 Global_Mode : Name_Id := Name_Input)
2061 procedure Analyze_Global_Item
2062 (Item : Node_Id;
2063 Global_Mode : Name_Id);
2064 -- Verify the legality of a single global item declaration denoted by
2065 -- Item. Global_Mode denotes the current mode in effect.
2067 procedure Check_Duplicate_Mode
2068 (Mode : Node_Id;
2069 Status : in out Boolean);
2070 -- Flag Status denotes whether a particular mode has been seen while
2071 -- processing a global list. This routine verifies that Mode is not a
2072 -- duplicate mode and sets the flag Status (SPARK RM 6.1.4(9)).
2074 procedure Check_Mode_Restriction_In_Enclosing_Context
2075 (Item : Node_Id;
2076 Item_Id : Entity_Id);
2077 -- Verify that an item of mode In_Out or Output does not appear as an
2078 -- input in the Global aspect of an enclosing subprogram. If this is
2079 -- the case, emit an error. Item and Item_Id are respectively the
2080 -- item and its entity.
2082 procedure Check_Mode_Restriction_In_Function (Mode : Node_Id);
2083 -- Mode denotes either In_Out or Output. Depending on the kind of the
2084 -- related subprogram, emit an error if those two modes apply to a
2085 -- function (SPARK RM 6.1.4(10)).
2087 -------------------------
2088 -- Analyze_Global_Item --
2089 -------------------------
2091 procedure Analyze_Global_Item
2092 (Item : Node_Id;
2093 Global_Mode : Name_Id)
2095 Item_Id : Entity_Id;
2097 begin
2098 -- Detect one of the following cases
2100 -- with Global => (null, Name)
2101 -- with Global => (Name_1, null, Name_2)
2102 -- with Global => (Name, null)
2104 if Nkind (Item) = N_Null then
2105 SPARK_Msg_N ("cannot mix null and non-null global items", Item);
2106 return;
2107 end if;
2109 Analyze (Item);
2110 Resolve_State (Item);
2112 -- Find the entity of the item. If this is a renaming, climb the
2113 -- renaming chain to reach the root object. Renamings of non-
2114 -- entire objects do not yield an entity (Empty).
2116 Item_Id := Entity_Of (Item);
2118 if Present (Item_Id) then
2120 -- A global item may denote a formal parameter of an enclosing
2121 -- subprogram (SPARK RM 6.1.4(6)). Do this check first to
2122 -- provide a better error diagnostic.
2124 if Is_Formal (Item_Id) then
2125 if Scope (Item_Id) = Spec_Id then
2126 SPARK_Msg_NE
2127 (Fix_Msg (Spec_Id, "global item cannot reference "
2128 & "parameter of subprogram &"), Item, Spec_Id);
2129 return;
2130 end if;
2132 -- A global item may denote a concurrent type as long as it is
2133 -- the current instance of an enclosing protected or task type
2134 -- (SPARK RM 6.1.4).
2136 elsif Ekind_In (Item_Id, E_Protected_Type, E_Task_Type) then
2137 if Is_CCT_Instance (Item_Id, Spec_Id) then
2139 -- Pragma [Refined_]Global associated with a protected
2140 -- subprogram cannot mention the current instance of a
2141 -- protected type because the instance behaves as a
2142 -- formal parameter.
2144 if Ekind (Item_Id) = E_Protected_Type then
2145 Error_Msg_Name_1 := Chars (Item_Id);
2146 SPARK_Msg_NE
2147 (Fix_Msg (Spec_Id, "global item of subprogram & "
2148 & "cannot reference current instance of protected "
2149 & "type %"), Item, Spec_Id);
2150 return;
2152 -- Pragma [Refined_]Global associated with a task type
2153 -- cannot mention the current instance of a task type
2154 -- because the instance behaves as a formal parameter.
2156 else pragma Assert (Ekind (Item_Id) = E_Task_Type);
2157 Error_Msg_Name_1 := Chars (Item_Id);
2158 SPARK_Msg_NE
2159 (Fix_Msg (Spec_Id, "global item of subprogram & "
2160 & "cannot reference current instance of task type "
2161 & "%"), Item, Spec_Id);
2162 return;
2163 end if;
2165 -- Otherwise the global item denotes a subtype mark that is
2166 -- not a current instance.
2168 else
2169 SPARK_Msg_N
2170 ("invalid use of subtype mark in global list", Item);
2171 return;
2172 end if;
2174 -- A global item may denote the anonymous object created for a
2175 -- single protected/task type as long as the current instance
2176 -- is the same single type (SPARK RM 6.1.4).
2178 elsif Is_Single_Concurrent_Object (Item_Id)
2179 and then Is_CCT_Instance (Item_Id, Spec_Id)
2180 then
2181 -- Pragma [Refined_]Global associated with a protected
2182 -- subprogram cannot mention the current instance of a
2183 -- protected type because the instance behaves as a formal
2184 -- parameter.
2186 if Is_Single_Protected_Object (Item_Id) then
2187 Error_Msg_Name_1 := Chars (Item_Id);
2188 SPARK_Msg_NE
2189 (Fix_Msg (Spec_Id, "global item of subprogram & cannot "
2190 & "reference current instance of protected type %"),
2191 Item, Spec_Id);
2192 return;
2194 -- Pragma [Refined_]Global associated with a task type
2195 -- cannot mention the current instance of a task type
2196 -- because the instance behaves as a formal parameter.
2198 else pragma Assert (Is_Single_Task_Object (Item_Id));
2199 Error_Msg_Name_1 := Chars (Item_Id);
2200 SPARK_Msg_NE
2201 (Fix_Msg (Spec_Id, "global item of subprogram & cannot "
2202 & "reference current instance of task type %"),
2203 Item, Spec_Id);
2204 return;
2205 end if;
2207 -- A formal object may act as a global item inside a generic
2209 elsif Is_Formal_Object (Item_Id) then
2210 null;
2212 -- The only legal references are those to abstract states,
2213 -- objects and various kinds of constants (SPARK RM 6.1.4(4)).
2215 elsif not Ekind_In (Item_Id, E_Abstract_State,
2216 E_Constant,
2217 E_Loop_Parameter,
2218 E_Variable)
2219 then
2220 SPARK_Msg_N
2221 ("global item must denote object, state or current "
2222 & "instance of concurrent type", Item);
2223 return;
2224 end if;
2226 -- State related checks
2228 if Ekind (Item_Id) = E_Abstract_State then
2230 -- Package and subprogram bodies are instantiated
2231 -- individually in a separate compiler pass. Due to this
2232 -- mode of instantiation, the refinement of a state may
2233 -- no longer be visible when a subprogram body contract
2234 -- is instantiated. Since the generic template is legal,
2235 -- do not perform this check in the instance to circumvent
2236 -- this oddity.
2238 if Is_Generic_Instance (Spec_Id) then
2239 null;
2241 -- An abstract state with visible refinement cannot appear
2242 -- in pragma [Refined_]Global as its place must be taken by
2243 -- some of its constituents (SPARK RM 6.1.4(7)).
2245 elsif Has_Visible_Refinement (Item_Id) then
2246 SPARK_Msg_NE
2247 ("cannot mention state & in global refinement",
2248 Item, Item_Id);
2249 SPARK_Msg_N ("\use its constituents instead", Item);
2250 return;
2252 -- An external state cannot appear as a global item of a
2253 -- nonvolatile function (SPARK RM 7.1.3(8)).
2255 elsif Is_External_State (Item_Id)
2256 and then Ekind_In (Spec_Id, E_Function, E_Generic_Function)
2257 and then not Is_Volatile_Function (Spec_Id)
2258 then
2259 SPARK_Msg_NE
2260 ("external state & cannot act as global item of "
2261 & "nonvolatile function", Item, Item_Id);
2262 return;
2264 -- If the reference to the abstract state appears in an
2265 -- enclosing package body that will eventually refine the
2266 -- state, record the reference for future checks.
2268 else
2269 Record_Possible_Body_Reference
2270 (State_Id => Item_Id,
2271 Ref => Item);
2272 end if;
2274 -- Constant related checks
2276 elsif Ekind (Item_Id) = E_Constant then
2278 -- A constant is a read-only item, therefore it cannot act
2279 -- as an output.
2281 if Nam_In (Global_Mode, Name_In_Out, Name_Output) then
2282 SPARK_Msg_NE
2283 ("constant & cannot act as output", Item, Item_Id);
2284 return;
2285 end if;
2287 -- Loop parameter related checks
2289 elsif Ekind (Item_Id) = E_Loop_Parameter then
2291 -- A loop parameter is a read-only item, therefore it cannot
2292 -- act as an output.
2294 if Nam_In (Global_Mode, Name_In_Out, Name_Output) then
2295 SPARK_Msg_NE
2296 ("loop parameter & cannot act as output",
2297 Item, Item_Id);
2298 return;
2299 end if;
2301 -- Variable related checks. These are only relevant when
2302 -- SPARK_Mode is on as they are not standard Ada legality
2303 -- rules.
2305 elsif SPARK_Mode = On
2306 and then Ekind (Item_Id) = E_Variable
2307 and then Is_Effectively_Volatile (Item_Id)
2308 then
2309 -- An effectively volatile object cannot appear as a global
2310 -- item of a nonvolatile function (SPARK RM 7.1.3(8)).
2312 if Ekind_In (Spec_Id, E_Function, E_Generic_Function)
2313 and then not Is_Volatile_Function (Spec_Id)
2314 then
2315 Error_Msg_NE
2316 ("volatile object & cannot act as global item of a "
2317 & "function", Item, Item_Id);
2318 return;
2320 -- An effectively volatile object with external property
2321 -- Effective_Reads set to True must have mode Output or
2322 -- In_Out (SPARK RM 7.1.3(10)).
2324 elsif Effective_Reads_Enabled (Item_Id)
2325 and then Global_Mode = Name_Input
2326 then
2327 Error_Msg_NE
2328 ("volatile object & with property Effective_Reads must "
2329 & "have mode In_Out or Output", Item, Item_Id);
2330 return;
2331 end if;
2332 end if;
2334 -- When the item renames an entire object, replace the item
2335 -- with a reference to the object.
2337 if Entity (Item) /= Item_Id then
2338 Rewrite (Item, New_Occurrence_Of (Item_Id, Sloc (Item)));
2339 Analyze (Item);
2340 end if;
2342 -- Some form of illegal construct masquerading as a name
2343 -- (SPARK RM 6.1.4(4)).
2345 else
2346 Error_Msg_N
2347 ("global item must denote object, state or current instance "
2348 & "of concurrent type", Item);
2349 return;
2350 end if;
2352 -- Verify that an output does not appear as an input in an
2353 -- enclosing subprogram.
2355 if Nam_In (Global_Mode, Name_In_Out, Name_Output) then
2356 Check_Mode_Restriction_In_Enclosing_Context (Item, Item_Id);
2357 end if;
2359 -- The same entity might be referenced through various way.
2360 -- Check the entity of the item rather than the item itself
2361 -- (SPARK RM 6.1.4(10)).
2363 if Contains (Seen, Item_Id) then
2364 SPARK_Msg_N ("duplicate global item", Item);
2366 -- Add the entity of the current item to the list of processed
2367 -- items.
2369 else
2370 Append_New_Elmt (Item_Id, Seen);
2372 if Ekind (Item_Id) = E_Abstract_State then
2373 Append_New_Elmt (Item_Id, States_Seen);
2375 -- The variable may eventually become a constituent of a single
2376 -- protected/task type. Record the reference now and verify its
2377 -- legality when analyzing the contract of the variable
2378 -- (SPARK RM 9.3).
2380 elsif Ekind (Item_Id) = E_Variable then
2381 Record_Possible_Part_Of_Reference
2382 (Var_Id => Item_Id,
2383 Ref => Item);
2384 end if;
2386 if Ekind_In (Item_Id, E_Abstract_State, E_Constant, E_Variable)
2387 and then Present (Encapsulating_State (Item_Id))
2388 then
2389 Append_New_Elmt (Item_Id, Constits_Seen);
2390 end if;
2391 end if;
2392 end Analyze_Global_Item;
2394 --------------------------
2395 -- Check_Duplicate_Mode --
2396 --------------------------
2398 procedure Check_Duplicate_Mode
2399 (Mode : Node_Id;
2400 Status : in out Boolean)
2402 begin
2403 if Status then
2404 SPARK_Msg_N ("duplicate global mode", Mode);
2405 end if;
2407 Status := True;
2408 end Check_Duplicate_Mode;
2410 -------------------------------------------------
2411 -- Check_Mode_Restriction_In_Enclosing_Context --
2412 -------------------------------------------------
2414 procedure Check_Mode_Restriction_In_Enclosing_Context
2415 (Item : Node_Id;
2416 Item_Id : Entity_Id)
2418 Context : Entity_Id;
2419 Dummy : Boolean;
2420 Inputs : Elist_Id := No_Elist;
2421 Outputs : Elist_Id := No_Elist;
2423 begin
2424 -- Traverse the scope stack looking for enclosing subprograms
2425 -- subject to pragma [Refined_]Global.
2427 Context := Scope (Subp_Id);
2428 while Present (Context) and then Context /= Standard_Standard loop
2429 if Is_Subprogram (Context)
2430 and then
2431 (Present (Get_Pragma (Context, Pragma_Global))
2432 or else
2433 Present (Get_Pragma (Context, Pragma_Refined_Global)))
2434 then
2435 Collect_Subprogram_Inputs_Outputs
2436 (Subp_Id => Context,
2437 Subp_Inputs => Inputs,
2438 Subp_Outputs => Outputs,
2439 Global_Seen => Dummy);
2441 -- The item is classified as In_Out or Output but appears as
2442 -- an Input in an enclosing subprogram (SPARK RM 6.1.4(11)).
2444 if Appears_In (Inputs, Item_Id)
2445 and then not Appears_In (Outputs, Item_Id)
2446 then
2447 SPARK_Msg_NE
2448 ("global item & cannot have mode In_Out or Output",
2449 Item, Item_Id);
2451 SPARK_Msg_NE
2452 (Fix_Msg (Subp_Id, "\item already appears as input of "
2453 & "subprogram &"), Item, Context);
2455 -- Stop the traversal once an error has been detected
2457 exit;
2458 end if;
2459 end if;
2461 Context := Scope (Context);
2462 end loop;
2463 end Check_Mode_Restriction_In_Enclosing_Context;
2465 ----------------------------------------
2466 -- Check_Mode_Restriction_In_Function --
2467 ----------------------------------------
2469 procedure Check_Mode_Restriction_In_Function (Mode : Node_Id) is
2470 begin
2471 if Ekind_In (Spec_Id, E_Function, E_Generic_Function) then
2472 SPARK_Msg_N
2473 ("global mode & is not applicable to functions", Mode);
2474 end if;
2475 end Check_Mode_Restriction_In_Function;
2477 -- Local variables
2479 Assoc : Node_Id;
2480 Item : Node_Id;
2481 Mode : Node_Id;
2483 -- Start of processing for Analyze_Global_List
2485 begin
2486 if Nkind (List) = N_Null then
2487 Set_Analyzed (List);
2489 -- Single global item declaration
2491 elsif Nkind_In (List, N_Expanded_Name,
2492 N_Identifier,
2493 N_Selected_Component)
2494 then
2495 Analyze_Global_Item (List, Global_Mode);
2497 -- Simple global list or moded global list declaration
2499 elsif Nkind (List) = N_Aggregate then
2500 Set_Analyzed (List);
2502 -- The declaration of a simple global list appear as a collection
2503 -- of expressions.
2505 if Present (Expressions (List)) then
2506 if Present (Component_Associations (List)) then
2507 SPARK_Msg_N
2508 ("cannot mix moded and non-moded global lists", List);
2509 end if;
2511 Item := First (Expressions (List));
2512 while Present (Item) loop
2513 Analyze_Global_Item (Item, Global_Mode);
2514 Next (Item);
2515 end loop;
2517 -- The declaration of a moded global list appears as a collection
2518 -- of component associations where individual choices denote
2519 -- modes.
2521 elsif Present (Component_Associations (List)) then
2522 if Present (Expressions (List)) then
2523 SPARK_Msg_N
2524 ("cannot mix moded and non-moded global lists", List);
2525 end if;
2527 Assoc := First (Component_Associations (List));
2528 while Present (Assoc) loop
2529 Mode := First (Choices (Assoc));
2531 if Nkind (Mode) = N_Identifier then
2532 if Chars (Mode) = Name_In_Out then
2533 Check_Duplicate_Mode (Mode, In_Out_Seen);
2534 Check_Mode_Restriction_In_Function (Mode);
2536 elsif Chars (Mode) = Name_Input then
2537 Check_Duplicate_Mode (Mode, Input_Seen);
2539 elsif Chars (Mode) = Name_Output then
2540 Check_Duplicate_Mode (Mode, Output_Seen);
2541 Check_Mode_Restriction_In_Function (Mode);
2543 elsif Chars (Mode) = Name_Proof_In then
2544 Check_Duplicate_Mode (Mode, Proof_Seen);
2546 else
2547 SPARK_Msg_N ("invalid mode selector", Mode);
2548 end if;
2550 else
2551 SPARK_Msg_N ("invalid mode selector", Mode);
2552 end if;
2554 -- Items in a moded list appear as a collection of
2555 -- expressions. Reuse the existing machinery to analyze
2556 -- them.
2558 Analyze_Global_List
2559 (List => Expression (Assoc),
2560 Global_Mode => Chars (Mode));
2562 Next (Assoc);
2563 end loop;
2565 -- Invalid tree
2567 else
2568 raise Program_Error;
2569 end if;
2571 -- Any other attempt to declare a global item is illegal. This is a
2572 -- syntax error, always report.
2574 else
2575 Error_Msg_N ("malformed global list", List);
2576 end if;
2577 end Analyze_Global_List;
2579 -- Local variables
2581 Items : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
2583 Restore_Scope : Boolean := False;
2585 -- Start of processing for Analyze_Global_In_Decl_Part
2587 begin
2588 -- Do not analyze the pragma multiple times
2590 if Is_Analyzed_Pragma (N) then
2591 return;
2592 end if;
2594 -- There is nothing to be done for a null global list
2596 if Nkind (Items) = N_Null then
2597 Set_Analyzed (Items);
2599 -- Analyze the various forms of global lists and items. Note that some
2600 -- of these may be malformed in which case the analysis emits error
2601 -- messages.
2603 else
2604 -- When pragma [Refined_]Global appears on a single concurrent type,
2605 -- it is relocated to the anonymous object.
2607 if Is_Single_Concurrent_Object (Spec_Id) then
2608 null;
2610 -- Ensure that the formal parameters are visible when processing an
2611 -- item. This falls out of the general rule of aspects pertaining to
2612 -- subprogram declarations.
2614 elsif not In_Open_Scopes (Spec_Id) then
2615 Restore_Scope := True;
2616 Push_Scope (Spec_Id);
2618 if Ekind (Spec_Id) = E_Task_Type then
2619 if Has_Discriminants (Spec_Id) then
2620 Install_Discriminants (Spec_Id);
2621 end if;
2623 elsif Is_Generic_Subprogram (Spec_Id) then
2624 Install_Generic_Formals (Spec_Id);
2626 else
2627 Install_Formals (Spec_Id);
2628 end if;
2629 end if;
2631 Analyze_Global_List (Items);
2633 if Restore_Scope then
2634 End_Scope;
2635 end if;
2636 end if;
2638 -- Ensure that a state and a corresponding constituent do not appear
2639 -- together in pragma [Refined_]Global.
2641 Check_State_And_Constituent_Use
2642 (States => States_Seen,
2643 Constits => Constits_Seen,
2644 Context => N);
2646 Set_Is_Analyzed_Pragma (N);
2647 end Analyze_Global_In_Decl_Part;
2649 --------------------------------------------
2650 -- Analyze_Initial_Condition_In_Decl_Part --
2651 --------------------------------------------
2653 -- WARNING: This routine manages Ghost regions. Return statements must be
2654 -- replaced by gotos which jump to the end of the routine and restore the
2655 -- Ghost mode.
2657 procedure Analyze_Initial_Condition_In_Decl_Part (N : Node_Id) is
2658 Pack_Decl : constant Node_Id := Find_Related_Package_Or_Body (N);
2659 Pack_Id : constant Entity_Id := Defining_Entity (Pack_Decl);
2660 Expr : constant Node_Id := Expression (Get_Argument (N, Pack_Id));
2662 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
2663 -- Save the Ghost mode to restore on exit
2665 begin
2666 -- Do not analyze the pragma multiple times
2668 if Is_Analyzed_Pragma (N) then
2669 return;
2670 end if;
2672 -- Set the Ghost mode in effect from the pragma. Due to the delayed
2673 -- analysis of the pragma, the Ghost mode at point of declaration and
2674 -- point of analysis may not necessarily be the same. Use the mode in
2675 -- effect at the point of declaration.
2677 Set_Ghost_Mode (N);
2679 -- The expression is preanalyzed because it has not been moved to its
2680 -- final place yet. A direct analysis may generate side effects and this
2681 -- is not desired at this point.
2683 Preanalyze_Assert_Expression (Expr, Standard_Boolean);
2684 Set_Is_Analyzed_Pragma (N);
2686 Restore_Ghost_Mode (Saved_GM);
2687 end Analyze_Initial_Condition_In_Decl_Part;
2689 --------------------------------------
2690 -- Analyze_Initializes_In_Decl_Part --
2691 --------------------------------------
2693 procedure Analyze_Initializes_In_Decl_Part (N : Node_Id) is
2694 Pack_Decl : constant Node_Id := Find_Related_Package_Or_Body (N);
2695 Pack_Id : constant Entity_Id := Defining_Entity (Pack_Decl);
2697 Constits_Seen : Elist_Id := No_Elist;
2698 -- A list containing the entities of all constituents processed so far.
2699 -- It aids in detecting illegal usage of a state and a corresponding
2700 -- constituent in pragma Initializes.
2702 Items_Seen : Elist_Id := No_Elist;
2703 -- A list of all initialization items processed so far. This list is
2704 -- used to detect duplicate items.
2706 Non_Null_Seen : Boolean := False;
2707 Null_Seen : Boolean := False;
2708 -- Flags used to check the legality of a null initialization list
2710 States_And_Objs : Elist_Id := No_Elist;
2711 -- A list of all abstract states and objects declared in the visible
2712 -- declarations of the related package. This list is used to detect the
2713 -- legality of initialization items.
2715 States_Seen : Elist_Id := No_Elist;
2716 -- A list containing the entities of all states processed so far. It
2717 -- helps in detecting illegal usage of a state and a corresponding
2718 -- constituent in pragma Initializes.
2720 procedure Analyze_Initialization_Item (Item : Node_Id);
2721 -- Verify the legality of a single initialization item
2723 procedure Analyze_Initialization_Item_With_Inputs (Item : Node_Id);
2724 -- Verify the legality of a single initialization item followed by a
2725 -- list of input items.
2727 procedure Collect_States_And_Objects;
2728 -- Inspect the visible declarations of the related package and gather
2729 -- the entities of all abstract states and objects in States_And_Objs.
2731 ---------------------------------
2732 -- Analyze_Initialization_Item --
2733 ---------------------------------
2735 procedure Analyze_Initialization_Item (Item : Node_Id) is
2736 Item_Id : Entity_Id;
2738 begin
2739 -- Null initialization list
2741 if Nkind (Item) = N_Null then
2742 if Null_Seen then
2743 SPARK_Msg_N ("multiple null initializations not allowed", Item);
2745 elsif Non_Null_Seen then
2746 SPARK_Msg_N
2747 ("cannot mix null and non-null initialization items", Item);
2748 else
2749 Null_Seen := True;
2750 end if;
2752 -- Initialization item
2754 else
2755 Non_Null_Seen := True;
2757 if Null_Seen then
2758 SPARK_Msg_N
2759 ("cannot mix null and non-null initialization items", Item);
2760 end if;
2762 Analyze (Item);
2763 Resolve_State (Item);
2765 if Is_Entity_Name (Item) then
2766 Item_Id := Entity_Of (Item);
2768 if Ekind_In (Item_Id, E_Abstract_State,
2769 E_Constant,
2770 E_Variable)
2771 then
2772 -- The state or variable must be declared in the visible
2773 -- declarations of the package (SPARK RM 7.1.5(7)).
2775 if not Contains (States_And_Objs, Item_Id) then
2776 Error_Msg_Name_1 := Chars (Pack_Id);
2777 SPARK_Msg_NE
2778 ("initialization item & must appear in the visible "
2779 & "declarations of package %", Item, Item_Id);
2781 -- Detect a duplicate use of the same initialization item
2782 -- (SPARK RM 7.1.5(5)).
2784 elsif Contains (Items_Seen, Item_Id) then
2785 SPARK_Msg_N ("duplicate initialization item", Item);
2787 -- The item is legal, add it to the list of processed states
2788 -- and variables.
2790 else
2791 Append_New_Elmt (Item_Id, Items_Seen);
2793 if Ekind (Item_Id) = E_Abstract_State then
2794 Append_New_Elmt (Item_Id, States_Seen);
2795 end if;
2797 if Present (Encapsulating_State (Item_Id)) then
2798 Append_New_Elmt (Item_Id, Constits_Seen);
2799 end if;
2800 end if;
2802 -- The item references something that is not a state or object
2803 -- (SPARK RM 7.1.5(3)).
2805 else
2806 SPARK_Msg_N
2807 ("initialization item must denote object or state", Item);
2808 end if;
2810 -- Some form of illegal construct masquerading as a name
2811 -- (SPARK RM 7.1.5(3)). This is a syntax error, always report.
2813 else
2814 Error_Msg_N
2815 ("initialization item must denote object or state", Item);
2816 end if;
2817 end if;
2818 end Analyze_Initialization_Item;
2820 ---------------------------------------------
2821 -- Analyze_Initialization_Item_With_Inputs --
2822 ---------------------------------------------
2824 procedure Analyze_Initialization_Item_With_Inputs (Item : Node_Id) is
2825 Inputs_Seen : Elist_Id := No_Elist;
2826 -- A list of all inputs processed so far. This list is used to detect
2827 -- duplicate uses of an input.
2829 Non_Null_Seen : Boolean := False;
2830 Null_Seen : Boolean := False;
2831 -- Flags used to check the legality of an input list
2833 procedure Analyze_Input_Item (Input : Node_Id);
2834 -- Verify the legality of a single input item
2836 ------------------------
2837 -- Analyze_Input_Item --
2838 ------------------------
2840 procedure Analyze_Input_Item (Input : Node_Id) is
2841 Input_Id : Entity_Id;
2842 Input_OK : Boolean := True;
2844 begin
2845 -- Null input list
2847 if Nkind (Input) = N_Null then
2848 if Null_Seen then
2849 SPARK_Msg_N
2850 ("multiple null initializations not allowed", Item);
2852 elsif Non_Null_Seen then
2853 SPARK_Msg_N
2854 ("cannot mix null and non-null initialization item", Item);
2855 else
2856 Null_Seen := True;
2857 end if;
2859 -- Input item
2861 else
2862 Non_Null_Seen := True;
2864 if Null_Seen then
2865 SPARK_Msg_N
2866 ("cannot mix null and non-null initialization item", Item);
2867 end if;
2869 Analyze (Input);
2870 Resolve_State (Input);
2872 if Is_Entity_Name (Input) then
2873 Input_Id := Entity_Of (Input);
2875 if Ekind_In (Input_Id, E_Abstract_State,
2876 E_Constant,
2877 E_Generic_In_Out_Parameter,
2878 E_Generic_In_Parameter,
2879 E_In_Parameter,
2880 E_In_Out_Parameter,
2881 E_Out_Parameter,
2882 E_Variable)
2883 then
2884 -- The input cannot denote states or objects declared
2885 -- within the related package (SPARK RM 7.1.5(4)).
2887 if Within_Scope (Input_Id, Current_Scope) then
2889 -- Do not consider generic formal parameters or their
2890 -- respective mappings to generic formals. Even though
2891 -- the formals appear within the scope of the package,
2892 -- it is allowed for an initialization item to depend
2893 -- on an input item.
2895 if Ekind_In (Input_Id, E_Generic_In_Out_Parameter,
2896 E_Generic_In_Parameter)
2897 then
2898 null;
2900 elsif Ekind_In (Input_Id, E_Constant, E_Variable)
2901 and then Present (Corresponding_Generic_Association
2902 (Declaration_Node (Input_Id)))
2903 then
2904 null;
2906 else
2907 Input_OK := False;
2908 Error_Msg_Name_1 := Chars (Pack_Id);
2909 SPARK_Msg_NE
2910 ("input item & cannot denote a visible object or "
2911 & "state of package %", Input, Input_Id);
2912 end if;
2913 end if;
2915 -- Detect a duplicate use of the same input item
2916 -- (SPARK RM 7.1.5(5)).
2918 if Contains (Inputs_Seen, Input_Id) then
2919 Input_OK := False;
2920 SPARK_Msg_N ("duplicate input item", Input);
2921 end if;
2923 -- Input is legal, add it to the list of processed inputs
2925 if Input_OK then
2926 Append_New_Elmt (Input_Id, Inputs_Seen);
2928 if Ekind (Input_Id) = E_Abstract_State then
2929 Append_New_Elmt (Input_Id, States_Seen);
2930 end if;
2932 if Ekind_In (Input_Id, E_Abstract_State,
2933 E_Constant,
2934 E_Variable)
2935 and then Present (Encapsulating_State (Input_Id))
2936 then
2937 Append_New_Elmt (Input_Id, Constits_Seen);
2938 end if;
2939 end if;
2941 -- The input references something that is not a state or an
2942 -- object (SPARK RM 7.1.5(3)).
2944 else
2945 SPARK_Msg_N
2946 ("input item must denote object or state", Input);
2947 end if;
2949 -- Some form of illegal construct masquerading as a name
2950 -- (SPARK RM 7.1.5(3)). This is a syntax error, always report.
2952 else
2953 Error_Msg_N
2954 ("input item must denote object or state", Input);
2955 end if;
2956 end if;
2957 end Analyze_Input_Item;
2959 -- Local variables
2961 Inputs : constant Node_Id := Expression (Item);
2962 Elmt : Node_Id;
2963 Input : Node_Id;
2965 Name_Seen : Boolean := False;
2966 -- A flag used to detect multiple item names
2968 -- Start of processing for Analyze_Initialization_Item_With_Inputs
2970 begin
2971 -- Inspect the name of an item with inputs
2973 Elmt := First (Choices (Item));
2974 while Present (Elmt) loop
2975 if Name_Seen then
2976 SPARK_Msg_N ("only one item allowed in initialization", Elmt);
2977 else
2978 Name_Seen := True;
2979 Analyze_Initialization_Item (Elmt);
2980 end if;
2982 Next (Elmt);
2983 end loop;
2985 -- Multiple input items appear as an aggregate
2987 if Nkind (Inputs) = N_Aggregate then
2988 if Present (Expressions (Inputs)) then
2989 Input := First (Expressions (Inputs));
2990 while Present (Input) loop
2991 Analyze_Input_Item (Input);
2992 Next (Input);
2993 end loop;
2994 end if;
2996 if Present (Component_Associations (Inputs)) then
2997 SPARK_Msg_N
2998 ("inputs must appear in named association form", Inputs);
2999 end if;
3001 -- Single input item
3003 else
3004 Analyze_Input_Item (Inputs);
3005 end if;
3006 end Analyze_Initialization_Item_With_Inputs;
3008 --------------------------------
3009 -- Collect_States_And_Objects --
3010 --------------------------------
3012 procedure Collect_States_And_Objects is
3013 Pack_Spec : constant Node_Id := Specification (Pack_Decl);
3014 Decl : Node_Id;
3016 begin
3017 -- Collect the abstract states defined in the package (if any)
3019 if Present (Abstract_States (Pack_Id)) then
3020 States_And_Objs := New_Copy_Elist (Abstract_States (Pack_Id));
3021 end if;
3023 -- Collect all objects the appear in the visible declarations of the
3024 -- related package.
3026 if Present (Visible_Declarations (Pack_Spec)) then
3027 Decl := First (Visible_Declarations (Pack_Spec));
3028 while Present (Decl) loop
3029 if Comes_From_Source (Decl)
3030 and then Nkind (Decl) = N_Object_Declaration
3031 then
3032 Append_New_Elmt (Defining_Entity (Decl), States_And_Objs);
3033 end if;
3035 Next (Decl);
3036 end loop;
3037 end if;
3038 end Collect_States_And_Objects;
3040 -- Local variables
3042 Inits : constant Node_Id := Expression (Get_Argument (N, Pack_Id));
3043 Init : Node_Id;
3045 -- Start of processing for Analyze_Initializes_In_Decl_Part
3047 begin
3048 -- Do not analyze the pragma multiple times
3050 if Is_Analyzed_Pragma (N) then
3051 return;
3052 end if;
3054 -- Nothing to do when the initialization list is empty
3056 if Nkind (Inits) = N_Null then
3057 return;
3058 end if;
3060 -- Single and multiple initialization clauses appear as an aggregate. If
3061 -- this is not the case, then either the parser or the analysis of the
3062 -- pragma failed to produce an aggregate.
3064 pragma Assert (Nkind (Inits) = N_Aggregate);
3066 -- Initialize the various lists used during analysis
3068 Collect_States_And_Objects;
3070 if Present (Expressions (Inits)) then
3071 Init := First (Expressions (Inits));
3072 while Present (Init) loop
3073 Analyze_Initialization_Item (Init);
3074 Next (Init);
3075 end loop;
3076 end if;
3078 if Present (Component_Associations (Inits)) then
3079 Init := First (Component_Associations (Inits));
3080 while Present (Init) loop
3081 Analyze_Initialization_Item_With_Inputs (Init);
3082 Next (Init);
3083 end loop;
3084 end if;
3086 -- Ensure that a state and a corresponding constituent do not appear
3087 -- together in pragma Initializes.
3089 Check_State_And_Constituent_Use
3090 (States => States_Seen,
3091 Constits => Constits_Seen,
3092 Context => N);
3094 Set_Is_Analyzed_Pragma (N);
3095 end Analyze_Initializes_In_Decl_Part;
3097 ---------------------
3098 -- Analyze_Part_Of --
3099 ---------------------
3101 procedure Analyze_Part_Of
3102 (Indic : Node_Id;
3103 Item_Id : Entity_Id;
3104 Encap : Node_Id;
3105 Encap_Id : out Entity_Id;
3106 Legal : out Boolean)
3108 Encap_Typ : Entity_Id;
3109 Item_Decl : Node_Id;
3110 Pack_Id : Entity_Id;
3111 Placement : State_Space_Kind;
3112 Parent_Unit : Entity_Id;
3114 begin
3115 -- Assume that the indicator is illegal
3117 Encap_Id := Empty;
3118 Legal := False;
3120 if Nkind_In (Encap, N_Expanded_Name,
3121 N_Identifier,
3122 N_Selected_Component)
3123 then
3124 Analyze (Encap);
3125 Resolve_State (Encap);
3127 Encap_Id := Entity (Encap);
3129 -- The encapsulator is an abstract state
3131 if Ekind (Encap_Id) = E_Abstract_State then
3132 null;
3134 -- The encapsulator is a single concurrent type (SPARK RM 9.3)
3136 elsif Is_Single_Concurrent_Object (Encap_Id) then
3137 null;
3139 -- Otherwise the encapsulator is not a legal choice
3141 else
3142 SPARK_Msg_N
3143 ("indicator Part_Of must denote abstract state, single "
3144 & "protected type or single task type", Encap);
3145 return;
3146 end if;
3148 -- This is a syntax error, always report
3150 else
3151 Error_Msg_N
3152 ("indicator Part_Of must denote abstract state, single protected "
3153 & "type or single task type", Encap);
3154 return;
3155 end if;
3157 -- Catch a case where indicator Part_Of denotes the abstract view of a
3158 -- variable which appears as an abstract state (SPARK RM 10.1.2 2).
3160 if From_Limited_With (Encap_Id)
3161 and then Present (Non_Limited_View (Encap_Id))
3162 and then Ekind (Non_Limited_View (Encap_Id)) = E_Variable
3163 then
3164 SPARK_Msg_N ("indicator Part_Of must denote abstract state", Encap);
3165 SPARK_Msg_N ("\& denotes abstract view of object", Encap);
3166 return;
3167 end if;
3169 -- The encapsulator is an abstract state
3171 if Ekind (Encap_Id) = E_Abstract_State then
3173 -- Determine where the object, package instantiation or state lives
3174 -- with respect to the enclosing packages or package bodies.
3176 Find_Placement_In_State_Space
3177 (Item_Id => Item_Id,
3178 Placement => Placement,
3179 Pack_Id => Pack_Id);
3181 -- The item appears in a non-package construct with a declarative
3182 -- part (subprogram, block, etc). As such, the item is not allowed
3183 -- to be a part of an encapsulating state because the item is not
3184 -- visible.
3186 if Placement = Not_In_Package then
3187 SPARK_Msg_N
3188 ("indicator Part_Of cannot appear in this context "
3189 & "(SPARK RM 7.2.6(5))", Indic);
3190 Error_Msg_Name_1 := Chars (Scope (Encap_Id));
3191 SPARK_Msg_NE
3192 ("\& is not part of the hidden state of package %",
3193 Indic, Item_Id);
3195 -- The item appears in the visible state space of some package. In
3196 -- general this scenario does not warrant Part_Of except when the
3197 -- package is a private child unit and the encapsulating state is
3198 -- declared in a parent unit or a public descendant of that parent
3199 -- unit.
3201 elsif Placement = Visible_State_Space then
3202 if Is_Child_Unit (Pack_Id)
3203 and then Is_Private_Descendant (Pack_Id)
3204 then
3205 -- A variable or state abstraction which is part of the visible
3206 -- state of a private child unit (or one of its public
3207 -- descendants) must have its Part_Of indicator specified. The
3208 -- Part_Of indicator must denote a state abstraction declared
3209 -- by either the parent unit of the private unit or by a public
3210 -- descendant of that parent unit.
3212 -- Find nearest private ancestor (which can be the current unit
3213 -- itself).
3215 Parent_Unit := Pack_Id;
3216 while Present (Parent_Unit) loop
3217 exit when
3218 Private_Present
3219 (Parent (Unit_Declaration_Node (Parent_Unit)));
3220 Parent_Unit := Scope (Parent_Unit);
3221 end loop;
3223 Parent_Unit := Scope (Parent_Unit);
3225 if not Is_Child_Or_Sibling (Pack_Id, Scope (Encap_Id)) then
3226 SPARK_Msg_NE
3227 ("indicator Part_Of must denote abstract state or public "
3228 & "descendant of & (SPARK RM 7.2.6(3))",
3229 Indic, Parent_Unit);
3231 elsif Scope (Encap_Id) = Parent_Unit
3232 or else
3233 (Is_Ancestor_Package (Parent_Unit, Scope (Encap_Id))
3234 and then not Is_Private_Descendant (Scope (Encap_Id)))
3235 then
3236 null;
3238 else
3239 SPARK_Msg_NE
3240 ("indicator Part_Of must denote abstract state or public "
3241 & "descendant of & (SPARK RM 7.2.6(3))",
3242 Indic, Parent_Unit);
3243 end if;
3245 -- Indicator Part_Of is not needed when the related package is not
3246 -- a private child unit or a public descendant thereof.
3248 else
3249 SPARK_Msg_N
3250 ("indicator Part_Of cannot appear in this context "
3251 & "(SPARK RM 7.2.6(5))", Indic);
3252 Error_Msg_Name_1 := Chars (Pack_Id);
3253 SPARK_Msg_NE
3254 ("\& is declared in the visible part of package %",
3255 Indic, Item_Id);
3256 end if;
3258 -- When the item appears in the private state space of a package, the
3259 -- encapsulating state must be declared in the same package.
3261 elsif Placement = Private_State_Space then
3262 if Scope (Encap_Id) /= Pack_Id then
3263 SPARK_Msg_NE
3264 ("indicator Part_Of must designate an abstract state of "
3265 & "package & (SPARK RM 7.2.6(2))", Indic, Pack_Id);
3266 Error_Msg_Name_1 := Chars (Pack_Id);
3267 SPARK_Msg_NE
3268 ("\& is declared in the private part of package %",
3269 Indic, Item_Id);
3270 end if;
3272 -- Items declared in the body state space of a package do not need
3273 -- Part_Of indicators as the refinement has already been seen.
3275 else
3276 SPARK_Msg_N
3277 ("indicator Part_Of cannot appear in this context "
3278 & "(SPARK RM 7.2.6(5))", Indic);
3280 if Scope (Encap_Id) = Pack_Id then
3281 Error_Msg_Name_1 := Chars (Pack_Id);
3282 SPARK_Msg_NE
3283 ("\& is declared in the body of package %", Indic, Item_Id);
3284 end if;
3285 end if;
3287 -- The encapsulator is a single concurrent type
3289 else
3290 Encap_Typ := Etype (Encap_Id);
3292 -- Only abstract states and variables can act as constituents of an
3293 -- encapsulating single concurrent type.
3295 if Ekind_In (Item_Id, E_Abstract_State, E_Variable) then
3296 null;
3298 -- The constituent is a constant
3300 elsif Ekind (Item_Id) = E_Constant then
3301 Error_Msg_Name_1 := Chars (Encap_Id);
3302 SPARK_Msg_NE
3303 (Fix_Msg (Encap_Typ, "constant & cannot act as constituent of "
3304 & "single protected type %"), Indic, Item_Id);
3306 -- The constituent is a package instantiation
3308 else
3309 Error_Msg_Name_1 := Chars (Encap_Id);
3310 SPARK_Msg_NE
3311 (Fix_Msg (Encap_Typ, "package instantiation & cannot act as "
3312 & "constituent of single protected type %"), Indic, Item_Id);
3313 end if;
3315 -- When the item denotes an abstract state of a nested package, use
3316 -- the declaration of the package to detect proper placement.
3318 -- package Pack is
3319 -- task T;
3320 -- package Nested
3321 -- with Abstract_State => (State with Part_Of => T)
3323 if Ekind (Item_Id) = E_Abstract_State then
3324 Item_Decl := Unit_Declaration_Node (Scope (Item_Id));
3325 else
3326 Item_Decl := Declaration_Node (Item_Id);
3327 end if;
3329 -- Both the item and its encapsulating single concurrent type must
3330 -- appear in the same declarative region (SPARK RM 9.3). Note that
3331 -- privacy is ignored.
3333 if Parent (Item_Decl) /= Parent (Declaration_Node (Encap_Id)) then
3334 Error_Msg_Name_1 := Chars (Encap_Id);
3335 SPARK_Msg_NE
3336 (Fix_Msg (Encap_Typ, "constituent & must be declared "
3337 & "immediately within the same region as single protected "
3338 & "type %"), Indic, Item_Id);
3339 end if;
3340 end if;
3342 Legal := True;
3343 end Analyze_Part_Of;
3345 ----------------------------------
3346 -- Analyze_Part_Of_In_Decl_Part --
3347 ----------------------------------
3349 procedure Analyze_Part_Of_In_Decl_Part
3350 (N : Node_Id;
3351 Freeze_Id : Entity_Id := Empty)
3353 Encap : constant Node_Id :=
3354 Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
3355 Errors : constant Nat := Serious_Errors_Detected;
3356 Var_Decl : constant Node_Id := Find_Related_Context (N);
3357 Var_Id : constant Entity_Id := Defining_Entity (Var_Decl);
3358 Constits : Elist_Id;
3359 Encap_Id : Entity_Id;
3360 Legal : Boolean;
3362 begin
3363 -- Detect any discrepancies between the placement of the variable with
3364 -- respect to general state space and the encapsulating state or single
3365 -- concurrent type.
3367 Analyze_Part_Of
3368 (Indic => N,
3369 Item_Id => Var_Id,
3370 Encap => Encap,
3371 Encap_Id => Encap_Id,
3372 Legal => Legal);
3374 -- The Part_Of indicator turns the variable into a constituent of the
3375 -- encapsulating state or single concurrent type.
3377 if Legal then
3378 pragma Assert (Present (Encap_Id));
3379 Constits := Part_Of_Constituents (Encap_Id);
3381 if No (Constits) then
3382 Constits := New_Elmt_List;
3383 Set_Part_Of_Constituents (Encap_Id, Constits);
3384 end if;
3386 Append_Elmt (Var_Id, Constits);
3387 Set_Encapsulating_State (Var_Id, Encap_Id);
3389 -- A Part_Of constituent partially refines an abstract state. This
3390 -- property does not apply to protected or task units.
3392 if Ekind (Encap_Id) = E_Abstract_State then
3393 Set_Has_Partial_Visible_Refinement (Encap_Id);
3394 end if;
3395 end if;
3397 -- Emit a clarification message when the encapsulator is undefined,
3398 -- possibly due to contract "freezing".
3400 if Errors /= Serious_Errors_Detected
3401 and then Present (Freeze_Id)
3402 and then Has_Undefined_Reference (Encap)
3403 then
3404 Contract_Freeze_Error (Var_Id, Freeze_Id);
3405 end if;
3406 end Analyze_Part_Of_In_Decl_Part;
3408 --------------------
3409 -- Analyze_Pragma --
3410 --------------------
3412 procedure Analyze_Pragma (N : Node_Id) is
3413 Loc : constant Source_Ptr := Sloc (N);
3415 Pname : Name_Id := Pragma_Name (N);
3416 -- Name of the source pragma, or name of the corresponding aspect for
3417 -- pragmas which originate in a source aspect. In the latter case, the
3418 -- name may be different from the pragma name.
3420 Prag_Id : constant Pragma_Id := Get_Pragma_Id (Pname);
3422 Pragma_Exit : exception;
3423 -- This exception is used to exit pragma processing completely. It
3424 -- is used when an error is detected, and no further processing is
3425 -- required. It is also used if an earlier error has left the tree in
3426 -- a state where the pragma should not be processed.
3428 Arg_Count : Nat;
3429 -- Number of pragma argument associations
3431 Arg1 : Node_Id;
3432 Arg2 : Node_Id;
3433 Arg3 : Node_Id;
3434 Arg4 : Node_Id;
3435 -- First four pragma arguments (pragma argument association nodes, or
3436 -- Empty if the corresponding argument does not exist).
3438 type Name_List is array (Natural range <>) of Name_Id;
3439 type Args_List is array (Natural range <>) of Node_Id;
3440 -- Types used for arguments to Check_Arg_Order and Gather_Associations
3442 -----------------------
3443 -- Local Subprograms --
3444 -----------------------
3446 procedure Acquire_Warning_Match_String (Arg : Node_Id);
3447 -- Used by pragma Warnings (Off, string), and Warn_As_Error (string) to
3448 -- get the given string argument, and place it in Name_Buffer, adding
3449 -- leading and trailing asterisks if they are not already present. The
3450 -- caller has already checked that Arg is a static string expression.
3452 procedure Ada_2005_Pragma;
3453 -- Called for pragmas defined in Ada 2005, that are not in Ada 95. In
3454 -- Ada 95 mode, these are implementation defined pragmas, so should be
3455 -- caught by the No_Implementation_Pragmas restriction.
3457 procedure Ada_2012_Pragma;
3458 -- Called for pragmas defined in Ada 2012, that are not in Ada 95 or 05.
3459 -- In Ada 95 or 05 mode, these are implementation defined pragmas, so
3460 -- should be caught by the No_Implementation_Pragmas restriction.
3462 procedure Analyze_Depends_Global
3463 (Spec_Id : out Entity_Id;
3464 Subp_Decl : out Node_Id;
3465 Legal : out Boolean);
3466 -- Subsidiary to the analysis of pragmas Depends and Global. Verify the
3467 -- legality of the placement and related context of the pragma. Spec_Id
3468 -- is the entity of the related subprogram. Subp_Decl is the declaration
3469 -- of the related subprogram. Sets flag Legal when the pragma is legal.
3471 procedure Analyze_If_Present (Id : Pragma_Id);
3472 -- Inspect the remainder of the list containing pragma N and look for
3473 -- a pragma that matches Id. If found, analyze the pragma.
3475 procedure Analyze_Pre_Post_Condition;
3476 -- Subsidiary to the analysis of pragmas Precondition and Postcondition
3478 procedure Analyze_Refined_Depends_Global_Post
3479 (Spec_Id : out Entity_Id;
3480 Body_Id : out Entity_Id;
3481 Legal : out Boolean);
3482 -- Subsidiary routine to the analysis of body pragmas Refined_Depends,
3483 -- Refined_Global and Refined_Post. Verify the legality of the placement
3484 -- and related context of the pragma. Spec_Id is the entity of the
3485 -- related subprogram. Body_Id is the entity of the subprogram body.
3486 -- Flag Legal is set when the pragma is legal.
3488 procedure Analyze_Unmodified_Or_Unused (Is_Unused : Boolean := False);
3489 -- Perform full analysis of pragma Unmodified and the write aspect of
3490 -- pragma Unused. Flag Is_Unused should be set when verifying the
3491 -- semantics of pragma Unused.
3493 procedure Analyze_Unreferenced_Or_Unused (Is_Unused : Boolean := False);
3494 -- Perform full analysis of pragma Unreferenced and the read aspect of
3495 -- pragma Unused. Flag Is_Unused should be set when verifying the
3496 -- semantics of pragma Unused.
3498 procedure Check_Ada_83_Warning;
3499 -- Issues a warning message for the current pragma if operating in Ada
3500 -- 83 mode (used for language pragmas that are not a standard part of
3501 -- Ada 83). This procedure does not raise Pragma_Exit. Also notes use
3502 -- of 95 pragma.
3504 procedure Check_Arg_Count (Required : Nat);
3505 -- Check argument count for pragma is equal to given parameter. If not,
3506 -- then issue an error message and raise Pragma_Exit.
3508 -- Note: all routines whose name is Check_Arg_Is_xxx take an argument
3509 -- Arg which can either be a pragma argument association, in which case
3510 -- the check is applied to the expression of the association or an
3511 -- expression directly.
3513 procedure Check_Arg_Is_External_Name (Arg : Node_Id);
3514 -- Check that an argument has the right form for an EXTERNAL_NAME
3515 -- parameter of an extended import/export pragma. The rule is that the
3516 -- name must be an identifier or string literal (in Ada 83 mode) or a
3517 -- static string expression (in Ada 95 mode).
3519 procedure Check_Arg_Is_Identifier (Arg : Node_Id);
3520 -- Check the specified argument Arg to make sure that it is an
3521 -- identifier. If not give error and raise Pragma_Exit.
3523 procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id);
3524 -- Check the specified argument Arg to make sure that it is an integer
3525 -- literal. If not give error and raise Pragma_Exit.
3527 procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id);
3528 -- Check the specified argument Arg to make sure that it has the proper
3529 -- syntactic form for a local name and meets the semantic requirements
3530 -- for a local name. The local name is analyzed as part of the
3531 -- processing for this call. In addition, the local name is required
3532 -- to represent an entity at the library level.
3534 procedure Check_Arg_Is_Local_Name (Arg : Node_Id);
3535 -- Check the specified argument Arg to make sure that it has the proper
3536 -- syntactic form for a local name and meets the semantic requirements
3537 -- for a local name. The local name is analyzed as part of the
3538 -- processing for this call.
3540 procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id);
3541 -- Check the specified argument Arg to make sure that it is a valid
3542 -- locking policy name. If not give error and raise Pragma_Exit.
3544 procedure Check_Arg_Is_Partition_Elaboration_Policy (Arg : Node_Id);
3545 -- Check the specified argument Arg to make sure that it is a valid
3546 -- elaboration policy name. If not give error and raise Pragma_Exit.
3548 procedure Check_Arg_Is_One_Of
3549 (Arg : Node_Id;
3550 N1, N2 : Name_Id);
3551 procedure Check_Arg_Is_One_Of
3552 (Arg : Node_Id;
3553 N1, N2, N3 : Name_Id);
3554 procedure Check_Arg_Is_One_Of
3555 (Arg : Node_Id;
3556 N1, N2, N3, N4 : Name_Id);
3557 procedure Check_Arg_Is_One_Of
3558 (Arg : Node_Id;
3559 N1, N2, N3, N4, N5 : Name_Id);
3560 -- Check the specified argument Arg to make sure that it is an
3561 -- identifier whose name matches either N1 or N2 (or N3, N4, N5 if
3562 -- present). If not then give error and raise Pragma_Exit.
3564 procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id);
3565 -- Check the specified argument Arg to make sure that it is a valid
3566 -- queuing policy name. If not give error and raise Pragma_Exit.
3568 procedure Check_Arg_Is_OK_Static_Expression
3569 (Arg : Node_Id;
3570 Typ : Entity_Id := Empty);
3571 -- Check the specified argument Arg to make sure that it is a static
3572 -- expression of the given type (i.e. it will be analyzed and resolved
3573 -- using this type, which can be any valid argument to Resolve, e.g.
3574 -- Any_Integer is OK). If not, given error and raise Pragma_Exit. If
3575 -- Typ is left Empty, then any static expression is allowed. Includes
3576 -- checking that the argument does not raise Constraint_Error.
3578 procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id);
3579 -- Check the specified argument Arg to make sure that it is a valid task
3580 -- dispatching policy name. If not give error and raise Pragma_Exit.
3582 procedure Check_Arg_Order (Names : Name_List);
3583 -- Checks for an instance of two arguments with identifiers for the
3584 -- current pragma which are not in the sequence indicated by Names,
3585 -- and if so, generates a fatal message about bad order of arguments.
3587 procedure Check_At_Least_N_Arguments (N : Nat);
3588 -- Check there are at least N arguments present
3590 procedure Check_At_Most_N_Arguments (N : Nat);
3591 -- Check there are no more than N arguments present
3593 procedure Check_Component
3594 (Comp : Node_Id;
3595 UU_Typ : Entity_Id;
3596 In_Variant_Part : Boolean := False);
3597 -- Examine an Unchecked_Union component for correct use of per-object
3598 -- constrained subtypes, and for restrictions on finalizable components.
3599 -- UU_Typ is the related Unchecked_Union type. Flag In_Variant_Part
3600 -- should be set when Comp comes from a record variant.
3602 procedure Check_Duplicate_Pragma (E : Entity_Id);
3603 -- Check if a rep item of the same name as the current pragma is already
3604 -- chained as a rep pragma to the given entity. If so give a message
3605 -- about the duplicate, and then raise Pragma_Exit so does not return.
3606 -- Note that if E is a type, then this routine avoids flagging a pragma
3607 -- which applies to a parent type from which E is derived.
3609 procedure Check_Duplicated_Export_Name (Nam : Node_Id);
3610 -- Nam is an N_String_Literal node containing the external name set by
3611 -- an Import or Export pragma (or extended Import or Export pragma).
3612 -- This procedure checks for possible duplications if this is the export
3613 -- case, and if found, issues an appropriate error message.
3615 procedure Check_Expr_Is_OK_Static_Expression
3616 (Expr : Node_Id;
3617 Typ : Entity_Id := Empty);
3618 -- Check the specified expression Expr to make sure that it is a static
3619 -- expression of the given type (i.e. it will be analyzed and resolved
3620 -- using this type, which can be any valid argument to Resolve, e.g.
3621 -- Any_Integer is OK). If not, given error and raise Pragma_Exit. If
3622 -- Typ is left Empty, then any static expression is allowed. Includes
3623 -- checking that the expression does not raise Constraint_Error.
3625 procedure Check_First_Subtype (Arg : Node_Id);
3626 -- Checks that Arg, whose expression is an entity name, references a
3627 -- first subtype.
3629 procedure Check_Identifier (Arg : Node_Id; Id : Name_Id);
3630 -- Checks that the given argument has an identifier, and if so, requires
3631 -- it to match the given identifier name. If there is no identifier, or
3632 -- a non-matching identifier, then an error message is given and
3633 -- Pragma_Exit is raised.
3635 procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
3636 -- Checks that the given argument has an identifier, and if so, requires
3637 -- it to match one of the given identifier names. If there is no
3638 -- identifier, or a non-matching identifier, then an error message is
3639 -- given and Pragma_Exit is raised.
3641 procedure Check_In_Main_Program;
3642 -- Common checks for pragmas that appear within a main program
3643 -- (Priority, Main_Storage, Time_Slice, Relative_Deadline, CPU).
3645 procedure Check_Interrupt_Or_Attach_Handler;
3646 -- Common processing for first argument of pragma Interrupt_Handler or
3647 -- pragma Attach_Handler.
3649 procedure Check_Loop_Pragma_Placement;
3650 -- Verify whether pragmas Loop_Invariant, Loop_Optimize and Loop_Variant
3651 -- appear immediately within a construct restricted to loops, and that
3652 -- pragmas Loop_Invariant and Loop_Variant are grouped together.
3654 procedure Check_Is_In_Decl_Part_Or_Package_Spec;
3655 -- Check that pragma appears in a declarative part, or in a package
3656 -- specification, i.e. that it does not occur in a statement sequence
3657 -- in a body.
3659 procedure Check_No_Identifier (Arg : Node_Id);
3660 -- Checks that the given argument does not have an identifier. If
3661 -- an identifier is present, then an error message is issued, and
3662 -- Pragma_Exit is raised.
3664 procedure Check_No_Identifiers;
3665 -- Checks that none of the arguments to the pragma has an identifier.
3666 -- If any argument has an identifier, then an error message is issued,
3667 -- and Pragma_Exit is raised.
3669 procedure Check_No_Link_Name;
3670 -- Checks that no link name is specified
3672 procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id);
3673 -- Checks if the given argument has an identifier, and if so, requires
3674 -- it to match the given identifier name. If there is a non-matching
3675 -- identifier, then an error message is given and Pragma_Exit is raised.
3677 procedure Check_Optional_Identifier (Arg : Node_Id; Id : String);
3678 -- Checks if the given argument has an identifier, and if so, requires
3679 -- it to match the given identifier name. If there is a non-matching
3680 -- identifier, then an error message is given and Pragma_Exit is raised.
3681 -- In this version of the procedure, the identifier name is given as
3682 -- a string with lower case letters.
3684 procedure Check_Static_Boolean_Expression (Expr : Node_Id);
3685 -- Subsidiary to the analysis of pragmas Async_Readers, Async_Writers,
3686 -- Constant_After_Elaboration, Effective_Reads, Effective_Writes,
3687 -- Extensions_Visible and Volatile_Function. Ensure that expression Expr
3688 -- is an OK static boolean expression. Emit an error if this is not the
3689 -- case.
3691 procedure Check_Static_Constraint (Constr : Node_Id);
3692 -- Constr is a constraint from an N_Subtype_Indication node from a
3693 -- component constraint in an Unchecked_Union type. This routine checks
3694 -- that the constraint is static as required by the restrictions for
3695 -- Unchecked_Union.
3697 procedure Check_Valid_Configuration_Pragma;
3698 -- Legality checks for placement of a configuration pragma
3700 procedure Check_Valid_Library_Unit_Pragma;
3701 -- Legality checks for library unit pragmas. A special case arises for
3702 -- pragmas in generic instances that come from copies of the original
3703 -- library unit pragmas in the generic templates. In the case of other
3704 -- than library level instantiations these can appear in contexts which
3705 -- would normally be invalid (they only apply to the original template
3706 -- and to library level instantiations), and they are simply ignored,
3707 -- which is implemented by rewriting them as null statements.
3709 procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id);
3710 -- Check an Unchecked_Union variant for lack of nested variants and
3711 -- presence of at least one component. UU_Typ is the related Unchecked_
3712 -- Union type.
3714 procedure Ensure_Aggregate_Form (Arg : Node_Id);
3715 -- Subsidiary routine to the processing of pragmas Abstract_State,
3716 -- Contract_Cases, Depends, Global, Initializes, Refined_Depends,
3717 -- Refined_Global and Refined_State. Transform argument Arg into
3718 -- an aggregate if not one already. N_Null is never transformed.
3719 -- Arg may denote an aspect specification or a pragma argument
3720 -- association.
3722 procedure Error_Pragma (Msg : String);
3723 pragma No_Return (Error_Pragma);
3724 -- Outputs error message for current pragma. The message contains a %
3725 -- that will be replaced with the pragma name, and the flag is placed
3726 -- on the pragma itself. Pragma_Exit is then raised. Note: this routine
3727 -- calls Fix_Error (see spec of that procedure for details).
3729 procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id);
3730 pragma No_Return (Error_Pragma_Arg);
3731 -- Outputs error message for current pragma. The message may contain
3732 -- a % that will be replaced with the pragma name. The parameter Arg
3733 -- may either be a pragma argument association, in which case the flag
3734 -- is placed on the expression of this association, or an expression,
3735 -- in which case the flag is placed directly on the expression. The
3736 -- message is placed using Error_Msg_N, so the message may also contain
3737 -- an & insertion character which will reference the given Arg value.
3738 -- After placing the message, Pragma_Exit is raised. Note: this routine
3739 -- calls Fix_Error (see spec of that procedure for details).
3741 procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id);
3742 pragma No_Return (Error_Pragma_Arg);
3743 -- Similar to above form of Error_Pragma_Arg except that two messages
3744 -- are provided, the second is a continuation comment starting with \.
3746 procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id);
3747 pragma No_Return (Error_Pragma_Arg_Ident);
3748 -- Outputs error message for current pragma. The message may contain a %
3749 -- that will be replaced with the pragma name. The parameter Arg must be
3750 -- a pragma argument association with a non-empty identifier (i.e. its
3751 -- Chars field must be set), and the error message is placed on the
3752 -- identifier. The message is placed using Error_Msg_N so the message
3753 -- may also contain an & insertion character which will reference
3754 -- the identifier. After placing the message, Pragma_Exit is raised.
3755 -- Note: this routine calls Fix_Error (see spec of that procedure for
3756 -- details).
3758 procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id);
3759 pragma No_Return (Error_Pragma_Ref);
3760 -- Outputs error message for current pragma. The message may contain
3761 -- a % that will be replaced with the pragma name. The parameter Ref
3762 -- must be an entity whose name can be referenced by & and sloc by #.
3763 -- After placing the message, Pragma_Exit is raised. Note: this routine
3764 -- calls Fix_Error (see spec of that procedure for details).
3766 function Find_Lib_Unit_Name return Entity_Id;
3767 -- Used for a library unit pragma to find the entity to which the
3768 -- library unit pragma applies, returns the entity found.
3770 procedure Find_Program_Unit_Name (Id : Node_Id);
3771 -- If the pragma is a compilation unit pragma, the id must denote the
3772 -- compilation unit in the same compilation, and the pragma must appear
3773 -- in the list of preceding or trailing pragmas. If it is a program
3774 -- unit pragma that is not a compilation unit pragma, then the
3775 -- identifier must be visible.
3777 function Find_Unique_Parameterless_Procedure
3778 (Name : Entity_Id;
3779 Arg : Node_Id) return Entity_Id;
3780 -- Used for a procedure pragma to find the unique parameterless
3781 -- procedure identified by Name, returns it if it exists, otherwise
3782 -- errors out and uses Arg as the pragma argument for the message.
3784 function Fix_Error (Msg : String) return String;
3785 -- This is called prior to issuing an error message. Msg is the normal
3786 -- error message issued in the pragma case. This routine checks for the
3787 -- case of a pragma coming from an aspect in the source, and returns a
3788 -- message suitable for the aspect case as follows:
3790 -- Each substring "pragma" is replaced by "aspect"
3792 -- If "argument of" is at the start of the error message text, it is
3793 -- replaced by "entity for".
3795 -- If "argument" is at the start of the error message text, it is
3796 -- replaced by "entity".
3798 -- So for example, "argument of pragma X must be discrete type"
3799 -- returns "entity for aspect X must be a discrete type".
3801 -- Finally Error_Msg_Name_1 is set to the name of the aspect (which may
3802 -- be different from the pragma name). If the current pragma results
3803 -- from rewriting another pragma, then Error_Msg_Name_1 is set to the
3804 -- original pragma name.
3806 procedure Gather_Associations
3807 (Names : Name_List;
3808 Args : out Args_List);
3809 -- This procedure is used to gather the arguments for a pragma that
3810 -- permits arbitrary ordering of parameters using the normal rules
3811 -- for named and positional parameters. The Names argument is a list
3812 -- of Name_Id values that corresponds to the allowed pragma argument
3813 -- association identifiers in order. The result returned in Args is
3814 -- a list of corresponding expressions that are the pragma arguments.
3815 -- Note that this is a list of expressions, not of pragma argument
3816 -- associations (Gather_Associations has completely checked all the
3817 -- optional identifiers when it returns). An entry in Args is Empty
3818 -- on return if the corresponding argument is not present.
3820 procedure GNAT_Pragma;
3821 -- Called for all GNAT defined pragmas to check the relevant restriction
3822 -- (No_Implementation_Pragmas).
3824 function Is_Before_First_Decl
3825 (Pragma_Node : Node_Id;
3826 Decls : List_Id) return Boolean;
3827 -- Return True if Pragma_Node is before the first declarative item in
3828 -- Decls where Decls is the list of declarative items.
3830 function Is_Configuration_Pragma return Boolean;
3831 -- Determines if the placement of the current pragma is appropriate
3832 -- for a configuration pragma.
3834 function Is_In_Context_Clause return Boolean;
3835 -- Returns True if pragma appears within the context clause of a unit,
3836 -- and False for any other placement (does not generate any messages).
3838 function Is_Static_String_Expression (Arg : Node_Id) return Boolean;
3839 -- Analyzes the argument, and determines if it is a static string
3840 -- expression, returns True if so, False if non-static or not String.
3841 -- A special case is that a string literal returns True in Ada 83 mode
3842 -- (which has no such thing as static string expressions). Note that
3843 -- the call analyzes its argument, so this cannot be used for the case
3844 -- where an identifier might not be declared.
3846 procedure Pragma_Misplaced;
3847 pragma No_Return (Pragma_Misplaced);
3848 -- Issue fatal error message for misplaced pragma
3850 procedure Process_Atomic_Independent_Shared_Volatile;
3851 -- Common processing for pragmas Atomic, Independent, Shared, Volatile,
3852 -- Volatile_Full_Access. Note that Shared is an obsolete Ada 83 pragma
3853 -- and treated as being identical in effect to pragma Atomic.
3855 procedure Process_Compile_Time_Warning_Or_Error;
3856 -- Common processing for Compile_Time_Error and Compile_Time_Warning
3858 procedure Process_Convention
3859 (C : out Convention_Id;
3860 Ent : out Entity_Id);
3861 -- Common processing for Convention, Interface, Import and Export.
3862 -- Checks first two arguments of pragma, and sets the appropriate
3863 -- convention value in the specified entity or entities. On return
3864 -- C is the convention, Ent is the referenced entity.
3866 procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id);
3867 -- Common processing for Disable/Enable_Atomic_Synchronization. Nam is
3868 -- Name_Suppress for Disable and Name_Unsuppress for Enable.
3870 procedure Process_Extended_Import_Export_Object_Pragma
3871 (Arg_Internal : Node_Id;
3872 Arg_External : Node_Id;
3873 Arg_Size : Node_Id);
3874 -- Common processing for the pragmas Import/Export_Object. The three
3875 -- arguments correspond to the three named parameters of the pragmas. An
3876 -- argument is empty if the corresponding parameter is not present in
3877 -- the pragma.
3879 procedure Process_Extended_Import_Export_Internal_Arg
3880 (Arg_Internal : Node_Id := Empty);
3881 -- Common processing for all extended Import and Export pragmas. The
3882 -- argument is the pragma parameter for the Internal argument. If
3883 -- Arg_Internal is empty or inappropriate, an error message is posted.
3884 -- Otherwise, on normal return, the Entity_Field of Arg_Internal is
3885 -- set to identify the referenced entity.
3887 procedure Process_Extended_Import_Export_Subprogram_Pragma
3888 (Arg_Internal : Node_Id;
3889 Arg_External : Node_Id;
3890 Arg_Parameter_Types : Node_Id;
3891 Arg_Result_Type : Node_Id := Empty;
3892 Arg_Mechanism : Node_Id;
3893 Arg_Result_Mechanism : Node_Id := Empty);
3894 -- Common processing for all extended Import and Export pragmas applying
3895 -- to subprograms. The caller omits any arguments that do not apply to
3896 -- the pragma in question (for example, Arg_Result_Type can be non-Empty
3897 -- only in the Import_Function and Export_Function cases). The argument
3898 -- names correspond to the allowed pragma association identifiers.
3900 procedure Process_Generic_List;
3901 -- Common processing for Share_Generic and Inline_Generic
3903 procedure Process_Import_Or_Interface;
3904 -- Common processing for Import or Interface
3906 procedure Process_Import_Predefined_Type;
3907 -- Processing for completing a type with pragma Import. This is used
3908 -- to declare types that match predefined C types, especially for cases
3909 -- without corresponding Ada predefined type.
3911 type Inline_Status is (Suppressed, Disabled, Enabled);
3912 -- Inline status of a subprogram, indicated as follows:
3913 -- Suppressed: inlining is suppressed for the subprogram
3914 -- Disabled: no inlining is requested for the subprogram
3915 -- Enabled: inlining is requested/required for the subprogram
3917 procedure Process_Inline (Status : Inline_Status);
3918 -- Common processing for No_Inline, Inline and Inline_Always. Parameter
3919 -- indicates the inline status specified by the pragma.
3921 procedure Process_Interface_Name
3922 (Subprogram_Def : Entity_Id;
3923 Ext_Arg : Node_Id;
3924 Link_Arg : Node_Id;
3925 Prag : Node_Id);
3926 -- Given the last two arguments of pragma Import, pragma Export, or
3927 -- pragma Interface_Name, performs validity checks and sets the
3928 -- Interface_Name field of the given subprogram entity to the
3929 -- appropriate external or link name, depending on the arguments given.
3930 -- Ext_Arg is always present, but Link_Arg may be missing. Note that
3931 -- Ext_Arg may represent the Link_Name if Link_Arg is missing, and
3932 -- appropriate named notation is used for Ext_Arg. If neither Ext_Arg
3933 -- nor Link_Arg is present, the interface name is set to the default
3934 -- from the subprogram name. In addition, the pragma itself is passed
3935 -- to analyze any expressions in the case the pragma came from an aspect
3936 -- specification.
3938 procedure Process_Interrupt_Or_Attach_Handler;
3939 -- Common processing for Interrupt and Attach_Handler pragmas
3941 procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
3942 -- Common processing for Restrictions and Restriction_Warnings pragmas.
3943 -- Warn is True for Restriction_Warnings, or for Restrictions if the
3944 -- flag Treat_Restrictions_As_Warnings is set, and False if this flag
3945 -- is not set in the Restrictions case.
3947 procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
3948 -- Common processing for Suppress and Unsuppress. The boolean parameter
3949 -- Suppress_Case is True for the Suppress case, and False for the
3950 -- Unsuppress case.
3952 procedure Record_Independence_Check (N : Node_Id; E : Entity_Id);
3953 -- Subsidiary to the analysis of pragmas Independent[_Components].
3954 -- Record such a pragma N applied to entity E for future checks.
3956 procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
3957 -- This procedure sets the Is_Exported flag for the given entity,
3958 -- checking that the entity was not previously imported. Arg is
3959 -- the argument that specified the entity. A check is also made
3960 -- for exporting inappropriate entities.
3962 procedure Set_Extended_Import_Export_External_Name
3963 (Internal_Ent : Entity_Id;
3964 Arg_External : Node_Id);
3965 -- Common processing for all extended import export pragmas. The first
3966 -- argument, Internal_Ent, is the internal entity, which has already
3967 -- been checked for validity by the caller. Arg_External is from the
3968 -- Import or Export pragma, and may be null if no External parameter
3969 -- was present. If Arg_External is present and is a non-null string
3970 -- (a null string is treated as the default), then the Interface_Name
3971 -- field of Internal_Ent is set appropriately.
3973 procedure Set_Imported (E : Entity_Id);
3974 -- This procedure sets the Is_Imported flag for the given entity,
3975 -- checking that it is not previously exported or imported.
3977 procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
3978 -- Mech is a parameter passing mechanism (see Import_Function syntax
3979 -- for MECHANISM_NAME). This routine checks that the mechanism argument
3980 -- has the right form, and if not issues an error message. If the
3981 -- argument has the right form then the Mechanism field of Ent is
3982 -- set appropriately.
3984 procedure Set_Rational_Profile;
3985 -- Activate the set of configuration pragmas and permissions that make
3986 -- up the Rational profile.
3988 procedure Set_Ravenscar_Profile (Profile : Profile_Name; N : Node_Id);
3989 -- Activate the set of configuration pragmas and restrictions that make
3990 -- up the Profile. Profile must be either GNAT_Extended_Ravenscar,
3991 -- GNAT_Ravenscar_EDF, or Ravenscar. N is the corresponding pragma node,
3992 -- which is used for error messages on any constructs violating the
3993 -- profile.
3995 ----------------------------------
3996 -- Acquire_Warning_Match_String --
3997 ----------------------------------
3999 procedure Acquire_Warning_Match_String (Arg : Node_Id) is
4000 begin
4001 String_To_Name_Buffer
4002 (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
4004 -- Add asterisk at start if not already there
4006 if Name_Len > 0 and then Name_Buffer (1) /= '*' then
4007 Name_Buffer (2 .. Name_Len + 1) :=
4008 Name_Buffer (1 .. Name_Len);
4009 Name_Buffer (1) := '*';
4010 Name_Len := Name_Len + 1;
4011 end if;
4013 -- Add asterisk at end if not already there
4015 if Name_Buffer (Name_Len) /= '*' then
4016 Name_Len := Name_Len + 1;
4017 Name_Buffer (Name_Len) := '*';
4018 end if;
4019 end Acquire_Warning_Match_String;
4021 ---------------------
4022 -- Ada_2005_Pragma --
4023 ---------------------
4025 procedure Ada_2005_Pragma is
4026 begin
4027 if Ada_Version <= Ada_95 then
4028 Check_Restriction (No_Implementation_Pragmas, N);
4029 end if;
4030 end Ada_2005_Pragma;
4032 ---------------------
4033 -- Ada_2012_Pragma --
4034 ---------------------
4036 procedure Ada_2012_Pragma is
4037 begin
4038 if Ada_Version <= Ada_2005 then
4039 Check_Restriction (No_Implementation_Pragmas, N);
4040 end if;
4041 end Ada_2012_Pragma;
4043 ----------------------------
4044 -- Analyze_Depends_Global --
4045 ----------------------------
4047 procedure Analyze_Depends_Global
4048 (Spec_Id : out Entity_Id;
4049 Subp_Decl : out Node_Id;
4050 Legal : out Boolean)
4052 begin
4053 -- Assume that the pragma is illegal
4055 Spec_Id := Empty;
4056 Subp_Decl := Empty;
4057 Legal := False;
4059 GNAT_Pragma;
4060 Check_Arg_Count (1);
4062 -- Ensure the proper placement of the pragma. Depends/Global must be
4063 -- associated with a subprogram declaration or a body that acts as a
4064 -- spec.
4066 Subp_Decl := Find_Related_Declaration_Or_Body (N, Do_Checks => True);
4068 -- Entry
4070 if Nkind (Subp_Decl) = N_Entry_Declaration then
4071 null;
4073 -- Generic subprogram
4075 elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
4076 null;
4078 -- Object declaration of a single concurrent type
4080 elsif Nkind (Subp_Decl) = N_Object_Declaration then
4081 null;
4083 -- Single task type
4085 elsif Nkind (Subp_Decl) = N_Single_Task_Declaration then
4086 null;
4088 -- Subprogram body acts as spec
4090 elsif Nkind (Subp_Decl) = N_Subprogram_Body
4091 and then No (Corresponding_Spec (Subp_Decl))
4092 then
4093 null;
4095 -- Subprogram body stub acts as spec
4097 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
4098 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
4099 then
4100 null;
4102 -- Subprogram declaration
4104 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
4105 null;
4107 -- Task type
4109 elsif Nkind (Subp_Decl) = N_Task_Type_Declaration then
4110 null;
4112 else
4113 Pragma_Misplaced;
4114 return;
4115 end if;
4117 -- If we get here, then the pragma is legal
4119 Legal := True;
4120 Spec_Id := Unique_Defining_Entity (Subp_Decl);
4122 -- When the related context is an entry, the entry must belong to a
4123 -- protected unit (SPARK RM 6.1.4(6)).
4125 if Is_Entry_Declaration (Spec_Id)
4126 and then Ekind (Scope (Spec_Id)) /= E_Protected_Type
4127 then
4128 Pragma_Misplaced;
4129 return;
4131 -- When the related context is an anonymous object created for a
4132 -- simple concurrent type, the type must be a task
4133 -- (SPARK RM 6.1.4(6)).
4135 elsif Is_Single_Concurrent_Object (Spec_Id)
4136 and then Ekind (Etype (Spec_Id)) /= E_Task_Type
4137 then
4138 Pragma_Misplaced;
4139 return;
4140 end if;
4142 -- A pragma that applies to a Ghost entity becomes Ghost for the
4143 -- purposes of legality checks and removal of ignored Ghost code.
4145 Mark_Ghost_Pragma (N, Spec_Id);
4146 Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
4147 end Analyze_Depends_Global;
4149 ------------------------
4150 -- Analyze_If_Present --
4151 ------------------------
4153 procedure Analyze_If_Present (Id : Pragma_Id) is
4154 Stmt : Node_Id;
4156 begin
4157 pragma Assert (Is_List_Member (N));
4159 -- Inspect the declarations or statements following pragma N looking
4160 -- for another pragma whose Id matches the caller's request. If it is
4161 -- available, analyze it.
4163 Stmt := Next (N);
4164 while Present (Stmt) loop
4165 if Nkind (Stmt) = N_Pragma and then Get_Pragma_Id (Stmt) = Id then
4166 Analyze_Pragma (Stmt);
4167 exit;
4169 -- The first source declaration or statement immediately following
4170 -- N ends the region where a pragma may appear.
4172 elsif Comes_From_Source (Stmt) then
4173 exit;
4174 end if;
4176 Next (Stmt);
4177 end loop;
4178 end Analyze_If_Present;
4180 --------------------------------
4181 -- Analyze_Pre_Post_Condition --
4182 --------------------------------
4184 procedure Analyze_Pre_Post_Condition is
4185 Prag_Iden : constant Node_Id := Pragma_Identifier (N);
4186 Subp_Decl : Node_Id;
4187 Subp_Id : Entity_Id;
4189 Duplicates_OK : Boolean := False;
4190 -- Flag set when a pre/postcondition allows multiple pragmas of the
4191 -- same kind.
4193 In_Body_OK : Boolean := False;
4194 -- Flag set when a pre/postcondition is allowed to appear on a body
4195 -- even though the subprogram may have a spec.
4197 Is_Pre_Post : Boolean := False;
4198 -- Flag set when the pragma is one of Pre, Pre_Class, Post or
4199 -- Post_Class.
4201 function Inherits_Class_Wide_Pre (E : Entity_Id) return Boolean;
4202 -- Implement rules in AI12-0131: an overriding operation can have
4203 -- a class-wide precondition only if one of its ancestors has an
4204 -- explicit class-wide precondition.
4206 -----------------------------
4207 -- Inherits_Class_Wide_Pre --
4208 -----------------------------
4210 function Inherits_Class_Wide_Pre (E : Entity_Id) return Boolean is
4211 Typ : constant Entity_Id := Find_Dispatching_Type (E);
4212 Cont : Node_Id;
4213 Prag : Node_Id;
4214 Prev : Entity_Id := Overridden_Operation (E);
4216 begin
4217 -- Check ancestors on the overriding operation to examine the
4218 -- preconditions that may apply to them.
4220 while Present (Prev) loop
4221 Cont := Contract (Prev);
4222 if Present (Cont) then
4223 Prag := Pre_Post_Conditions (Cont);
4224 while Present (Prag) loop
4225 if Class_Present (Prag) then
4226 return True;
4227 end if;
4229 Prag := Next_Pragma (Prag);
4230 end loop;
4231 end if;
4233 -- For a type derived from a generic formal type, the operation
4234 -- inheriting the condition is a renaming, not an overriding of
4235 -- the operation of the formal. Ditto for an inherited
4236 -- operation which has no explicit contracts.
4238 if Is_Generic_Type (Find_Dispatching_Type (Prev))
4239 or else not Comes_From_Source (Prev)
4240 then
4241 Prev := Alias (Prev);
4242 else
4243 Prev := Overridden_Operation (Prev);
4244 end if;
4245 end loop;
4247 -- If the controlling type of the subprogram has progenitors, an
4248 -- interface operation implemented by the current operation may
4249 -- have a class-wide precondition.
4251 if Has_Interfaces (Typ) then
4252 declare
4253 Elmt : Elmt_Id;
4254 Ints : Elist_Id;
4255 Prim : Entity_Id;
4256 Prim_Elmt : Elmt_Id;
4257 Prim_List : Elist_Id;
4259 begin
4260 Collect_Interfaces (Typ, Ints);
4261 Elmt := First_Elmt (Ints);
4263 -- Iterate over the primitive operations of each interface
4265 while Present (Elmt) loop
4266 Prim_List := Direct_Primitive_Operations (Node (Elmt));
4267 Prim_Elmt := First_Elmt (Prim_List);
4268 while Present (Prim_Elmt) loop
4269 Prim := Node (Prim_Elmt);
4270 if Chars (Prim) = Chars (E)
4271 and then Present (Contract (Prim))
4272 and then Class_Present
4273 (Pre_Post_Conditions (Contract (Prim)))
4274 then
4275 return True;
4276 end if;
4278 Next_Elmt (Prim_Elmt);
4279 end loop;
4281 Next_Elmt (Elmt);
4282 end loop;
4283 end;
4284 end if;
4286 return False;
4287 end Inherits_Class_Wide_Pre;
4289 -- Start of processing for Analyze_Pre_Post_Condition
4291 begin
4292 -- Change the name of pragmas Pre, Pre_Class, Post and Post_Class to
4293 -- offer uniformity among the various kinds of pre/postconditions by
4294 -- rewriting the pragma identifier. This allows the retrieval of the
4295 -- original pragma name by routine Original_Aspect_Pragma_Name.
4297 if Comes_From_Source (N) then
4298 if Nam_In (Pname, Name_Pre, Name_Pre_Class) then
4299 Is_Pre_Post := True;
4300 Set_Class_Present (N, Pname = Name_Pre_Class);
4301 Rewrite (Prag_Iden, Make_Identifier (Loc, Name_Precondition));
4303 elsif Nam_In (Pname, Name_Post, Name_Post_Class) then
4304 Is_Pre_Post := True;
4305 Set_Class_Present (N, Pname = Name_Post_Class);
4306 Rewrite (Prag_Iden, Make_Identifier (Loc, Name_Postcondition));
4307 end if;
4308 end if;
4310 -- Determine the semantics with respect to duplicates and placement
4311 -- in a body. Pragmas Precondition and Postcondition were introduced
4312 -- before aspects and are not subject to the same aspect-like rules.
4314 if Nam_In (Pname, Name_Precondition, Name_Postcondition) then
4315 Duplicates_OK := True;
4316 In_Body_OK := True;
4317 end if;
4319 GNAT_Pragma;
4321 -- Pragmas Pre, Pre_Class, Post and Post_Class allow for a single
4322 -- argument without an identifier.
4324 if Is_Pre_Post then
4325 Check_Arg_Count (1);
4326 Check_No_Identifiers;
4328 -- Pragmas Precondition and Postcondition have complex argument
4329 -- profile.
4331 else
4332 Check_At_Least_N_Arguments (1);
4333 Check_At_Most_N_Arguments (2);
4334 Check_Optional_Identifier (Arg1, Name_Check);
4336 if Present (Arg2) then
4337 Check_Optional_Identifier (Arg2, Name_Message);
4338 Preanalyze_Spec_Expression
4339 (Get_Pragma_Arg (Arg2), Standard_String);
4340 end if;
4341 end if;
4343 -- For a pragma PPC in the extended main source unit, record enabled
4344 -- status in SCO.
4345 -- ??? nothing checks that the pragma is in the main source unit
4347 if Is_Checked (N) and then not Split_PPC (N) then
4348 Set_SCO_Pragma_Enabled (Loc);
4349 end if;
4351 -- Ensure the proper placement of the pragma
4353 Subp_Decl :=
4354 Find_Related_Declaration_Or_Body
4355 (N, Do_Checks => not Duplicates_OK);
4357 -- When a pre/postcondition pragma applies to an abstract subprogram,
4358 -- its original form must be an aspect with 'Class.
4360 if Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
4361 if not From_Aspect_Specification (N) then
4362 Error_Pragma
4363 ("pragma % cannot be applied to abstract subprogram");
4365 elsif not Class_Present (N) then
4366 Error_Pragma
4367 ("aspect % requires ''Class for abstract subprogram");
4368 end if;
4370 -- Entry declaration
4372 elsif Nkind (Subp_Decl) = N_Entry_Declaration then
4373 null;
4375 -- Generic subprogram declaration
4377 elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
4378 null;
4380 -- Subprogram body
4382 elsif Nkind (Subp_Decl) = N_Subprogram_Body
4383 and then (No (Corresponding_Spec (Subp_Decl)) or In_Body_OK)
4384 then
4385 null;
4387 -- Subprogram body stub
4389 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
4390 and then (No (Corresponding_Spec_Of_Stub (Subp_Decl)) or In_Body_OK)
4391 then
4392 null;
4394 -- Subprogram declaration
4396 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
4398 -- AI05-0230: When a pre/postcondition pragma applies to a null
4399 -- procedure, its original form must be an aspect with 'Class.
4401 if Nkind (Specification (Subp_Decl)) = N_Procedure_Specification
4402 and then Null_Present (Specification (Subp_Decl))
4403 and then From_Aspect_Specification (N)
4404 and then not Class_Present (N)
4405 then
4406 Error_Pragma ("aspect % requires ''Class for null procedure");
4407 end if;
4409 -- Implement the legality checks mandated by AI12-0131:
4410 -- Pre'Class shall not be specified for an overriding primitive
4411 -- subprogram of a tagged type T unless the Pre'Class aspect is
4412 -- specified for the corresponding primitive subprogram of some
4413 -- ancestor of T.
4415 declare
4416 E : constant Entity_Id := Defining_Entity (Subp_Decl);
4418 begin
4419 if Class_Present (N)
4420 and then Pragma_Name (N) = Name_Precondition
4421 and then Present (Overridden_Operation (E))
4422 and then not Inherits_Class_Wide_Pre (E)
4423 then
4424 Error_Msg_N
4425 ("illegal class-wide precondition on overriding operation",
4426 Corresponding_Aspect (N));
4427 end if;
4428 end;
4430 -- A renaming declaration may inherit a generated pragma, its
4431 -- placement comes from expansion, not from source.
4433 elsif Nkind (Subp_Decl) = N_Subprogram_Renaming_Declaration
4434 and then not Comes_From_Source (N)
4435 then
4436 null;
4438 -- Otherwise the placement is illegal
4440 else
4441 Pragma_Misplaced;
4442 return;
4443 end if;
4445 Subp_Id := Defining_Entity (Subp_Decl);
4447 -- A pragma that applies to a Ghost entity becomes Ghost for the
4448 -- purposes of legality checks and removal of ignored Ghost code.
4450 Mark_Ghost_Pragma (N, Subp_Id);
4452 -- Chain the pragma on the contract for further processing by
4453 -- Analyze_Pre_Post_Condition_In_Decl_Part.
4455 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
4457 -- Fully analyze the pragma when it appears inside an entry or
4458 -- subprogram body because it cannot benefit from forward references.
4460 if Nkind_In (Subp_Decl, N_Entry_Body,
4461 N_Subprogram_Body,
4462 N_Subprogram_Body_Stub)
4463 then
4464 -- The legality checks of pragmas Precondition and Postcondition
4465 -- are affected by the SPARK mode in effect and the volatility of
4466 -- the context. Analyze all pragmas in a specific order.
4468 Analyze_If_Present (Pragma_SPARK_Mode);
4469 Analyze_If_Present (Pragma_Volatile_Function);
4470 Analyze_Pre_Post_Condition_In_Decl_Part (N);
4471 end if;
4472 end Analyze_Pre_Post_Condition;
4474 -----------------------------------------
4475 -- Analyze_Refined_Depends_Global_Post --
4476 -----------------------------------------
4478 procedure Analyze_Refined_Depends_Global_Post
4479 (Spec_Id : out Entity_Id;
4480 Body_Id : out Entity_Id;
4481 Legal : out Boolean)
4483 Body_Decl : Node_Id;
4484 Spec_Decl : Node_Id;
4486 begin
4487 -- Assume that the pragma is illegal
4489 Spec_Id := Empty;
4490 Body_Id := Empty;
4491 Legal := False;
4493 GNAT_Pragma;
4494 Check_Arg_Count (1);
4495 Check_No_Identifiers;
4497 -- Verify the placement of the pragma and check for duplicates. The
4498 -- pragma must apply to a subprogram body [stub].
4500 Body_Decl := Find_Related_Declaration_Or_Body (N, Do_Checks => True);
4502 -- Entry body
4504 if Nkind (Body_Decl) = N_Entry_Body then
4505 null;
4507 -- Subprogram body
4509 elsif Nkind (Body_Decl) = N_Subprogram_Body then
4510 null;
4512 -- Subprogram body stub
4514 elsif Nkind (Body_Decl) = N_Subprogram_Body_Stub then
4515 null;
4517 -- Task body
4519 elsif Nkind (Body_Decl) = N_Task_Body then
4520 null;
4522 else
4523 Pragma_Misplaced;
4524 return;
4525 end if;
4527 Body_Id := Defining_Entity (Body_Decl);
4528 Spec_Id := Unique_Defining_Entity (Body_Decl);
4530 -- The pragma must apply to the second declaration of a subprogram.
4531 -- In other words, the body [stub] cannot acts as a spec.
4533 if No (Spec_Id) then
4534 Error_Pragma ("pragma % cannot apply to a stand alone body");
4535 return;
4537 -- Catch the case where the subprogram body is a subunit and acts as
4538 -- the third declaration of the subprogram.
4540 elsif Nkind (Parent (Body_Decl)) = N_Subunit then
4541 Error_Pragma ("pragma % cannot apply to a subunit");
4542 return;
4543 end if;
4545 -- A refined pragma can only apply to the body [stub] of a subprogram
4546 -- declared in the visible part of a package. Retrieve the context of
4547 -- the subprogram declaration.
4549 Spec_Decl := Unit_Declaration_Node (Spec_Id);
4551 -- When dealing with protected entries or protected subprograms, use
4552 -- the enclosing protected type as the proper context.
4554 if Ekind_In (Spec_Id, E_Entry,
4555 E_Entry_Family,
4556 E_Function,
4557 E_Procedure)
4558 and then Ekind (Scope (Spec_Id)) = E_Protected_Type
4559 then
4560 Spec_Decl := Declaration_Node (Scope (Spec_Id));
4561 end if;
4563 if Nkind (Parent (Spec_Decl)) /= N_Package_Specification then
4564 Error_Pragma
4565 (Fix_Msg (Spec_Id, "pragma % must apply to the body of "
4566 & "subprogram declared in a package specification"));
4567 return;
4568 end if;
4570 -- If we get here, then the pragma is legal
4572 Legal := True;
4574 -- A pragma that applies to a Ghost entity becomes Ghost for the
4575 -- purposes of legality checks and removal of ignored Ghost code.
4577 Mark_Ghost_Pragma (N, Spec_Id);
4579 if Nam_In (Pname, Name_Refined_Depends, Name_Refined_Global) then
4580 Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
4581 end if;
4582 end Analyze_Refined_Depends_Global_Post;
4584 ----------------------------------
4585 -- Analyze_Unmodified_Or_Unused --
4586 ----------------------------------
4588 procedure Analyze_Unmodified_Or_Unused (Is_Unused : Boolean := False) is
4589 Arg : Node_Id;
4590 Arg_Expr : Node_Id;
4591 Arg_Id : Entity_Id;
4593 Ghost_Error_Posted : Boolean := False;
4594 -- Flag set when an error concerning the illegal mix of Ghost and
4595 -- non-Ghost variables is emitted.
4597 Ghost_Id : Entity_Id := Empty;
4598 -- The entity of the first Ghost variable encountered while
4599 -- processing the arguments of the pragma.
4601 begin
4602 GNAT_Pragma;
4603 Check_At_Least_N_Arguments (1);
4605 -- Loop through arguments
4607 Arg := Arg1;
4608 while Present (Arg) loop
4609 Check_No_Identifier (Arg);
4611 -- Note: the analyze call done by Check_Arg_Is_Local_Name will
4612 -- in fact generate reference, so that the entity will have a
4613 -- reference, which will inhibit any warnings about it not
4614 -- being referenced, and also properly show up in the ali file
4615 -- as a reference. But this reference is recorded before the
4616 -- Has_Pragma_Unreferenced flag is set, so that no warning is
4617 -- generated for this reference.
4619 Check_Arg_Is_Local_Name (Arg);
4620 Arg_Expr := Get_Pragma_Arg (Arg);
4622 if Is_Entity_Name (Arg_Expr) then
4623 Arg_Id := Entity (Arg_Expr);
4625 -- Skip processing the argument if already flagged
4627 if Is_Assignable (Arg_Id)
4628 and then not Has_Pragma_Unmodified (Arg_Id)
4629 and then not Has_Pragma_Unused (Arg_Id)
4630 then
4631 Set_Has_Pragma_Unmodified (Arg_Id);
4633 if Is_Unused then
4634 Set_Has_Pragma_Unused (Arg_Id);
4635 end if;
4637 -- A pragma that applies to a Ghost entity becomes Ghost for
4638 -- the purposes of legality checks and removal of ignored
4639 -- Ghost code.
4641 Mark_Ghost_Pragma (N, Arg_Id);
4643 -- Capture the entity of the first Ghost variable being
4644 -- processed for error detection purposes.
4646 if Is_Ghost_Entity (Arg_Id) then
4647 if No (Ghost_Id) then
4648 Ghost_Id := Arg_Id;
4649 end if;
4651 -- Otherwise the variable is non-Ghost. It is illegal to mix
4652 -- references to Ghost and non-Ghost entities
4653 -- (SPARK RM 6.9).
4655 elsif Present (Ghost_Id)
4656 and then not Ghost_Error_Posted
4657 then
4658 Ghost_Error_Posted := True;
4660 Error_Msg_Name_1 := Pname;
4661 Error_Msg_N
4662 ("pragma % cannot mention ghost and non-ghost "
4663 & "variables", N);
4665 Error_Msg_Sloc := Sloc (Ghost_Id);
4666 Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
4668 Error_Msg_Sloc := Sloc (Arg_Id);
4669 Error_Msg_NE ("\& # declared as non-ghost", N, Arg_Id);
4670 end if;
4672 -- Warn if already flagged as Unused or Unmodified
4674 elsif Has_Pragma_Unmodified (Arg_Id) then
4675 if Has_Pragma_Unused (Arg_Id) then
4676 Error_Msg_NE
4677 ("??pragma Unused already given for &!", Arg_Expr,
4678 Arg_Id);
4679 else
4680 Error_Msg_NE
4681 ("??pragma Unmodified already given for &!", Arg_Expr,
4682 Arg_Id);
4683 end if;
4685 -- Otherwise the pragma referenced an illegal entity
4687 else
4688 Error_Pragma_Arg
4689 ("pragma% can only be applied to a variable", Arg_Expr);
4690 end if;
4691 end if;
4693 Next (Arg);
4694 end loop;
4695 end Analyze_Unmodified_Or_Unused;
4697 -----------------------------------
4698 -- Analyze_Unreference_Or_Unused --
4699 -----------------------------------
4701 procedure Analyze_Unreferenced_Or_Unused
4702 (Is_Unused : Boolean := False)
4704 Arg : Node_Id;
4705 Arg_Expr : Node_Id;
4706 Arg_Id : Entity_Id;
4707 Citem : Node_Id;
4709 Ghost_Error_Posted : Boolean := False;
4710 -- Flag set when an error concerning the illegal mix of Ghost and
4711 -- non-Ghost names is emitted.
4713 Ghost_Id : Entity_Id := Empty;
4714 -- The entity of the first Ghost name encountered while processing
4715 -- the arguments of the pragma.
4717 begin
4718 GNAT_Pragma;
4719 Check_At_Least_N_Arguments (1);
4721 -- Check case of appearing within context clause
4723 if not Is_Unused and then Is_In_Context_Clause then
4725 -- The arguments must all be units mentioned in a with clause in
4726 -- the same context clause. Note that Par.Prag already checked
4727 -- that the arguments are either identifiers or selected
4728 -- components.
4730 Arg := Arg1;
4731 while Present (Arg) loop
4732 Citem := First (List_Containing (N));
4733 while Citem /= N loop
4734 Arg_Expr := Get_Pragma_Arg (Arg);
4736 if Nkind (Citem) = N_With_Clause
4737 and then Same_Name (Name (Citem), Arg_Expr)
4738 then
4739 Set_Has_Pragma_Unreferenced
4740 (Cunit_Entity
4741 (Get_Source_Unit
4742 (Library_Unit (Citem))));
4743 Set_Elab_Unit_Name (Arg_Expr, Name (Citem));
4744 exit;
4745 end if;
4747 Next (Citem);
4748 end loop;
4750 if Citem = N then
4751 Error_Pragma_Arg
4752 ("argument of pragma% is not withed unit", Arg);
4753 end if;
4755 Next (Arg);
4756 end loop;
4758 -- Case of not in list of context items
4760 else
4761 Arg := Arg1;
4762 while Present (Arg) loop
4763 Check_No_Identifier (Arg);
4765 -- Note: the analyze call done by Check_Arg_Is_Local_Name will
4766 -- in fact generate reference, so that the entity will have a
4767 -- reference, which will inhibit any warnings about it not
4768 -- being referenced, and also properly show up in the ali file
4769 -- as a reference. But this reference is recorded before the
4770 -- Has_Pragma_Unreferenced flag is set, so that no warning is
4771 -- generated for this reference.
4773 Check_Arg_Is_Local_Name (Arg);
4774 Arg_Expr := Get_Pragma_Arg (Arg);
4776 if Is_Entity_Name (Arg_Expr) then
4777 Arg_Id := Entity (Arg_Expr);
4779 -- Warn if already flagged as Unused or Unreferenced and
4780 -- skip processing the argument.
4782 if Has_Pragma_Unreferenced (Arg_Id) then
4783 if Has_Pragma_Unused (Arg_Id) then
4784 Error_Msg_NE
4785 ("??pragma Unused already given for &!", Arg_Expr,
4786 Arg_Id);
4787 else
4788 Error_Msg_NE
4789 ("??pragma Unreferenced already given for &!",
4790 Arg_Expr, Arg_Id);
4791 end if;
4793 -- Apply Unreferenced to the entity
4795 else
4796 -- If the entity is overloaded, the pragma applies to the
4797 -- most recent overloading, as documented. In this case,
4798 -- name resolution does not generate a reference, so it
4799 -- must be done here explicitly.
4801 if Is_Overloaded (Arg_Expr) then
4802 Generate_Reference (Arg_Id, N);
4803 end if;
4805 Set_Has_Pragma_Unreferenced (Arg_Id);
4807 if Is_Unused then
4808 Set_Has_Pragma_Unused (Arg_Id);
4809 end if;
4811 -- A pragma that applies to a Ghost entity becomes Ghost
4812 -- for the purposes of legality checks and removal of
4813 -- ignored Ghost code.
4815 Mark_Ghost_Pragma (N, Arg_Id);
4817 -- Capture the entity of the first Ghost name being
4818 -- processed for error detection purposes.
4820 if Is_Ghost_Entity (Arg_Id) then
4821 if No (Ghost_Id) then
4822 Ghost_Id := Arg_Id;
4823 end if;
4825 -- Otherwise the name is non-Ghost. It is illegal to mix
4826 -- references to Ghost and non-Ghost entities
4827 -- (SPARK RM 6.9).
4829 elsif Present (Ghost_Id)
4830 and then not Ghost_Error_Posted
4831 then
4832 Ghost_Error_Posted := True;
4834 Error_Msg_Name_1 := Pname;
4835 Error_Msg_N
4836 ("pragma % cannot mention ghost and non-ghost "
4837 & "names", N);
4839 Error_Msg_Sloc := Sloc (Ghost_Id);
4840 Error_Msg_NE
4841 ("\& # declared as ghost", N, Ghost_Id);
4843 Error_Msg_Sloc := Sloc (Arg_Id);
4844 Error_Msg_NE
4845 ("\& # declared as non-ghost", N, Arg_Id);
4846 end if;
4847 end if;
4848 end if;
4850 Next (Arg);
4851 end loop;
4852 end if;
4853 end Analyze_Unreferenced_Or_Unused;
4855 --------------------------
4856 -- Check_Ada_83_Warning --
4857 --------------------------
4859 procedure Check_Ada_83_Warning is
4860 begin
4861 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
4862 Error_Msg_N ("(Ada 83) pragma& is non-standard??", N);
4863 end if;
4864 end Check_Ada_83_Warning;
4866 ---------------------
4867 -- Check_Arg_Count --
4868 ---------------------
4870 procedure Check_Arg_Count (Required : Nat) is
4871 begin
4872 if Arg_Count /= Required then
4873 Error_Pragma ("wrong number of arguments for pragma%");
4874 end if;
4875 end Check_Arg_Count;
4877 --------------------------------
4878 -- Check_Arg_Is_External_Name --
4879 --------------------------------
4881 procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
4882 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
4884 begin
4885 if Nkind (Argx) = N_Identifier then
4886 return;
4888 else
4889 Analyze_And_Resolve (Argx, Standard_String);
4891 if Is_OK_Static_Expression (Argx) then
4892 return;
4894 elsif Etype (Argx) = Any_Type then
4895 raise Pragma_Exit;
4897 -- An interesting special case, if we have a string literal and
4898 -- we are in Ada 83 mode, then we allow it even though it will
4899 -- not be flagged as static. This allows expected Ada 83 mode
4900 -- use of external names which are string literals, even though
4901 -- technically these are not static in Ada 83.
4903 elsif Ada_Version = Ada_83
4904 and then Nkind (Argx) = N_String_Literal
4905 then
4906 return;
4908 -- Here we have a real error (non-static expression)
4910 else
4911 Error_Msg_Name_1 := Pname;
4912 Flag_Non_Static_Expr
4913 (Fix_Error ("argument for pragma% must be a identifier or "
4914 & "static string expression!"), Argx);
4916 raise Pragma_Exit;
4917 end if;
4918 end if;
4919 end Check_Arg_Is_External_Name;
4921 -----------------------------
4922 -- Check_Arg_Is_Identifier --
4923 -----------------------------
4925 procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
4926 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
4927 begin
4928 if Nkind (Argx) /= N_Identifier then
4929 Error_Pragma_Arg ("argument for pragma% must be identifier", Argx);
4930 end if;
4931 end Check_Arg_Is_Identifier;
4933 ----------------------------------
4934 -- Check_Arg_Is_Integer_Literal --
4935 ----------------------------------
4937 procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
4938 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
4939 begin
4940 if Nkind (Argx) /= N_Integer_Literal then
4941 Error_Pragma_Arg
4942 ("argument for pragma% must be integer literal", Argx);
4943 end if;
4944 end Check_Arg_Is_Integer_Literal;
4946 -------------------------------------------
4947 -- Check_Arg_Is_Library_Level_Local_Name --
4948 -------------------------------------------
4950 -- LOCAL_NAME ::=
4951 -- DIRECT_NAME
4952 -- | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
4953 -- | library_unit_NAME
4955 procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
4956 begin
4957 Check_Arg_Is_Local_Name (Arg);
4959 -- If it came from an aspect, we want to give the error just as if it
4960 -- came from source.
4962 if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
4963 and then (Comes_From_Source (N)
4964 or else Present (Corresponding_Aspect (Parent (Arg))))
4965 then
4966 Error_Pragma_Arg
4967 ("argument for pragma% must be library level entity", Arg);
4968 end if;
4969 end Check_Arg_Is_Library_Level_Local_Name;
4971 -----------------------------
4972 -- Check_Arg_Is_Local_Name --
4973 -----------------------------
4975 -- LOCAL_NAME ::=
4976 -- DIRECT_NAME
4977 -- | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
4978 -- | library_unit_NAME
4980 procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
4981 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
4983 begin
4984 -- If this pragma came from an aspect specification, we don't want to
4985 -- check for this error, because that would cause spurious errors, in
4986 -- case a type is frozen in a scope more nested than the type. The
4987 -- aspect itself of course can't be anywhere but on the declaration
4988 -- itself.
4990 if Nkind (Arg) = N_Pragma_Argument_Association then
4991 if From_Aspect_Specification (Parent (Arg)) then
4992 return;
4993 end if;
4995 -- Arg is the Expression of an N_Pragma_Argument_Association
4997 else
4998 if From_Aspect_Specification (Parent (Parent (Arg))) then
4999 return;
5000 end if;
5001 end if;
5003 Analyze (Argx);
5005 if Nkind (Argx) not in N_Direct_Name
5006 and then (Nkind (Argx) /= N_Attribute_Reference
5007 or else Present (Expressions (Argx))
5008 or else Nkind (Prefix (Argx)) /= N_Identifier)
5009 and then (not Is_Entity_Name (Argx)
5010 or else not Is_Compilation_Unit (Entity (Argx)))
5011 then
5012 Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
5013 end if;
5015 -- No further check required if not an entity name
5017 if not Is_Entity_Name (Argx) then
5018 null;
5020 else
5021 declare
5022 OK : Boolean;
5023 Ent : constant Entity_Id := Entity (Argx);
5024 Scop : constant Entity_Id := Scope (Ent);
5026 begin
5027 -- Case of a pragma applied to a compilation unit: pragma must
5028 -- occur immediately after the program unit in the compilation.
5030 if Is_Compilation_Unit (Ent) then
5031 declare
5032 Decl : constant Node_Id := Unit_Declaration_Node (Ent);
5034 begin
5035 -- Case of pragma placed immediately after spec
5037 if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
5038 OK := True;
5040 -- Case of pragma placed immediately after body
5042 elsif Nkind (Decl) = N_Subprogram_Declaration
5043 and then Present (Corresponding_Body (Decl))
5044 then
5045 OK := Parent (N) =
5046 Aux_Decls_Node
5047 (Parent (Unit_Declaration_Node
5048 (Corresponding_Body (Decl))));
5050 -- All other cases are illegal
5052 else
5053 OK := False;
5054 end if;
5055 end;
5057 -- Special restricted placement rule from 10.2.1(11.8/2)
5059 elsif Is_Generic_Formal (Ent)
5060 and then Prag_Id = Pragma_Preelaborable_Initialization
5061 then
5062 OK := List_Containing (N) =
5063 Generic_Formal_Declarations
5064 (Unit_Declaration_Node (Scop));
5066 -- If this is an aspect applied to a subprogram body, the
5067 -- pragma is inserted in its declarative part.
5069 elsif From_Aspect_Specification (N)
5070 and then Ent = Current_Scope
5071 and then
5072 Nkind (Unit_Declaration_Node (Ent)) = N_Subprogram_Body
5073 then
5074 OK := True;
5076 -- If the aspect is a predicate (possibly others ???) and the
5077 -- context is a record type, this is a discriminant expression
5078 -- within a type declaration, that freezes the predicated
5079 -- subtype.
5081 elsif From_Aspect_Specification (N)
5082 and then Prag_Id = Pragma_Predicate
5083 and then Ekind (Current_Scope) = E_Record_Type
5084 and then Scop = Scope (Current_Scope)
5085 then
5086 OK := True;
5088 -- Default case, just check that the pragma occurs in the scope
5089 -- of the entity denoted by the name.
5091 else
5092 OK := Current_Scope = Scop;
5093 end if;
5095 if not OK then
5096 Error_Pragma_Arg
5097 ("pragma% argument must be in same declarative part", Arg);
5098 end if;
5099 end;
5100 end if;
5101 end Check_Arg_Is_Local_Name;
5103 ---------------------------------
5104 -- Check_Arg_Is_Locking_Policy --
5105 ---------------------------------
5107 procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
5108 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5110 begin
5111 Check_Arg_Is_Identifier (Argx);
5113 if not Is_Locking_Policy_Name (Chars (Argx)) then
5114 Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
5115 end if;
5116 end Check_Arg_Is_Locking_Policy;
5118 -----------------------------------------------
5119 -- Check_Arg_Is_Partition_Elaboration_Policy --
5120 -----------------------------------------------
5122 procedure Check_Arg_Is_Partition_Elaboration_Policy (Arg : Node_Id) is
5123 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5125 begin
5126 Check_Arg_Is_Identifier (Argx);
5128 if not Is_Partition_Elaboration_Policy_Name (Chars (Argx)) then
5129 Error_Pragma_Arg
5130 ("& is not a valid partition elaboration policy name", Argx);
5131 end if;
5132 end Check_Arg_Is_Partition_Elaboration_Policy;
5134 -------------------------
5135 -- Check_Arg_Is_One_Of --
5136 -------------------------
5138 procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
5139 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5141 begin
5142 Check_Arg_Is_Identifier (Argx);
5144 if not Nam_In (Chars (Argx), N1, N2) then
5145 Error_Msg_Name_2 := N1;
5146 Error_Msg_Name_3 := N2;
5147 Error_Pragma_Arg ("argument for pragma% must be% or%", Argx);
5148 end if;
5149 end Check_Arg_Is_One_Of;
5151 procedure Check_Arg_Is_One_Of
5152 (Arg : Node_Id;
5153 N1, N2, N3 : Name_Id)
5155 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5157 begin
5158 Check_Arg_Is_Identifier (Argx);
5160 if not Nam_In (Chars (Argx), N1, N2, N3) then
5161 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
5162 end if;
5163 end Check_Arg_Is_One_Of;
5165 procedure Check_Arg_Is_One_Of
5166 (Arg : Node_Id;
5167 N1, N2, N3, N4 : Name_Id)
5169 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5171 begin
5172 Check_Arg_Is_Identifier (Argx);
5174 if not Nam_In (Chars (Argx), N1, N2, N3, N4) then
5175 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
5176 end if;
5177 end Check_Arg_Is_One_Of;
5179 procedure Check_Arg_Is_One_Of
5180 (Arg : Node_Id;
5181 N1, N2, N3, N4, N5 : Name_Id)
5183 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5185 begin
5186 Check_Arg_Is_Identifier (Argx);
5188 if not Nam_In (Chars (Argx), N1, N2, N3, N4, N5) then
5189 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
5190 end if;
5191 end Check_Arg_Is_One_Of;
5193 ---------------------------------
5194 -- Check_Arg_Is_Queuing_Policy --
5195 ---------------------------------
5197 procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
5198 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5200 begin
5201 Check_Arg_Is_Identifier (Argx);
5203 if not Is_Queuing_Policy_Name (Chars (Argx)) then
5204 Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
5205 end if;
5206 end Check_Arg_Is_Queuing_Policy;
5208 ---------------------------------------
5209 -- Check_Arg_Is_OK_Static_Expression --
5210 ---------------------------------------
5212 procedure Check_Arg_Is_OK_Static_Expression
5213 (Arg : Node_Id;
5214 Typ : Entity_Id := Empty)
5216 begin
5217 Check_Expr_Is_OK_Static_Expression (Get_Pragma_Arg (Arg), Typ);
5218 end Check_Arg_Is_OK_Static_Expression;
5220 ------------------------------------------
5221 -- Check_Arg_Is_Task_Dispatching_Policy --
5222 ------------------------------------------
5224 procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
5225 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5227 begin
5228 Check_Arg_Is_Identifier (Argx);
5230 if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
5231 Error_Pragma_Arg
5232 ("& is not an allowed task dispatching policy name", Argx);
5233 end if;
5234 end Check_Arg_Is_Task_Dispatching_Policy;
5236 ---------------------
5237 -- Check_Arg_Order --
5238 ---------------------
5240 procedure Check_Arg_Order (Names : Name_List) is
5241 Arg : Node_Id;
5243 Highest_So_Far : Natural := 0;
5244 -- Highest index in Names seen do far
5246 begin
5247 Arg := Arg1;
5248 for J in 1 .. Arg_Count loop
5249 if Chars (Arg) /= No_Name then
5250 for K in Names'Range loop
5251 if Chars (Arg) = Names (K) then
5252 if K < Highest_So_Far then
5253 Error_Msg_Name_1 := Pname;
5254 Error_Msg_N
5255 ("parameters out of order for pragma%", Arg);
5256 Error_Msg_Name_1 := Names (K);
5257 Error_Msg_Name_2 := Names (Highest_So_Far);
5258 Error_Msg_N ("\% must appear before %", Arg);
5259 raise Pragma_Exit;
5261 else
5262 Highest_So_Far := K;
5263 end if;
5264 end if;
5265 end loop;
5266 end if;
5268 Arg := Next (Arg);
5269 end loop;
5270 end Check_Arg_Order;
5272 --------------------------------
5273 -- Check_At_Least_N_Arguments --
5274 --------------------------------
5276 procedure Check_At_Least_N_Arguments (N : Nat) is
5277 begin
5278 if Arg_Count < N then
5279 Error_Pragma ("too few arguments for pragma%");
5280 end if;
5281 end Check_At_Least_N_Arguments;
5283 -------------------------------
5284 -- Check_At_Most_N_Arguments --
5285 -------------------------------
5287 procedure Check_At_Most_N_Arguments (N : Nat) is
5288 Arg : Node_Id;
5289 begin
5290 if Arg_Count > N then
5291 Arg := Arg1;
5292 for J in 1 .. N loop
5293 Next (Arg);
5294 Error_Pragma_Arg ("too many arguments for pragma%", Arg);
5295 end loop;
5296 end if;
5297 end Check_At_Most_N_Arguments;
5299 ---------------------
5300 -- Check_Component --
5301 ---------------------
5303 procedure Check_Component
5304 (Comp : Node_Id;
5305 UU_Typ : Entity_Id;
5306 In_Variant_Part : Boolean := False)
5308 Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
5309 Sindic : constant Node_Id :=
5310 Subtype_Indication (Component_Definition (Comp));
5311 Typ : constant Entity_Id := Etype (Comp_Id);
5313 begin
5314 -- Ada 2005 (AI-216): If a component subtype is subject to a per-
5315 -- object constraint, then the component type shall be an Unchecked_
5316 -- Union.
5318 if Nkind (Sindic) = N_Subtype_Indication
5319 and then Has_Per_Object_Constraint (Comp_Id)
5320 and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
5321 then
5322 Error_Msg_N
5323 ("component subtype subject to per-object constraint "
5324 & "must be an Unchecked_Union", Comp);
5326 -- Ada 2012 (AI05-0026): For an unchecked union type declared within
5327 -- the body of a generic unit, or within the body of any of its
5328 -- descendant library units, no part of the type of a component
5329 -- declared in a variant_part of the unchecked union type shall be of
5330 -- a formal private type or formal private extension declared within
5331 -- the formal part of the generic unit.
5333 elsif Ada_Version >= Ada_2012
5334 and then In_Generic_Body (UU_Typ)
5335 and then In_Variant_Part
5336 and then Is_Private_Type (Typ)
5337 and then Is_Generic_Type (Typ)
5338 then
5339 Error_Msg_N
5340 ("component of unchecked union cannot be of generic type", Comp);
5342 elsif Needs_Finalization (Typ) then
5343 Error_Msg_N
5344 ("component of unchecked union cannot be controlled", Comp);
5346 elsif Has_Task (Typ) then
5347 Error_Msg_N
5348 ("component of unchecked union cannot have tasks", Comp);
5349 end if;
5350 end Check_Component;
5352 ----------------------------
5353 -- Check_Duplicate_Pragma --
5354 ----------------------------
5356 procedure Check_Duplicate_Pragma (E : Entity_Id) is
5357 Id : Entity_Id := E;
5358 P : Node_Id;
5360 begin
5361 -- Nothing to do if this pragma comes from an aspect specification,
5362 -- since we could not be duplicating a pragma, and we dealt with the
5363 -- case of duplicated aspects in Analyze_Aspect_Specifications.
5365 if From_Aspect_Specification (N) then
5366 return;
5367 end if;
5369 -- Otherwise current pragma may duplicate previous pragma or a
5370 -- previously given aspect specification or attribute definition
5371 -- clause for the same pragma.
5373 P := Get_Rep_Item (E, Pragma_Name (N), Check_Parents => False);
5375 if Present (P) then
5377 -- If the entity is a type, then we have to make sure that the
5378 -- ostensible duplicate is not for a parent type from which this
5379 -- type is derived.
5381 if Is_Type (E) then
5382 if Nkind (P) = N_Pragma then
5383 declare
5384 Args : constant List_Id :=
5385 Pragma_Argument_Associations (P);
5386 begin
5387 if Present (Args)
5388 and then Is_Entity_Name (Expression (First (Args)))
5389 and then Is_Type (Entity (Expression (First (Args))))
5390 and then Entity (Expression (First (Args))) /= E
5391 then
5392 return;
5393 end if;
5394 end;
5396 elsif Nkind (P) = N_Aspect_Specification
5397 and then Is_Type (Entity (P))
5398 and then Entity (P) /= E
5399 then
5400 return;
5401 end if;
5402 end if;
5404 -- Here we have a definite duplicate
5406 Error_Msg_Name_1 := Pragma_Name (N);
5407 Error_Msg_Sloc := Sloc (P);
5409 -- For a single protected or a single task object, the error is
5410 -- issued on the original entity.
5412 if Ekind_In (Id, E_Task_Type, E_Protected_Type) then
5413 Id := Defining_Identifier (Original_Node (Parent (Id)));
5414 end if;
5416 if Nkind (P) = N_Aspect_Specification
5417 or else From_Aspect_Specification (P)
5418 then
5419 Error_Msg_NE ("aspect% for & previously given#", N, Id);
5420 else
5421 Error_Msg_NE ("pragma% for & duplicates pragma#", N, Id);
5422 end if;
5424 raise Pragma_Exit;
5425 end if;
5426 end Check_Duplicate_Pragma;
5428 ----------------------------------
5429 -- Check_Duplicated_Export_Name --
5430 ----------------------------------
5432 procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
5433 String_Val : constant String_Id := Strval (Nam);
5435 begin
5436 -- We are only interested in the export case, and in the case of
5437 -- generics, it is the instance, not the template, that is the
5438 -- problem (the template will generate a warning in any case).
5440 if not Inside_A_Generic
5441 and then (Prag_Id = Pragma_Export
5442 or else
5443 Prag_Id = Pragma_Export_Procedure
5444 or else
5445 Prag_Id = Pragma_Export_Valued_Procedure
5446 or else
5447 Prag_Id = Pragma_Export_Function)
5448 then
5449 for J in Externals.First .. Externals.Last loop
5450 if String_Equal (String_Val, Strval (Externals.Table (J))) then
5451 Error_Msg_Sloc := Sloc (Externals.Table (J));
5452 Error_Msg_N ("external name duplicates name given#", Nam);
5453 exit;
5454 end if;
5455 end loop;
5457 Externals.Append (Nam);
5458 end if;
5459 end Check_Duplicated_Export_Name;
5461 ----------------------------------------
5462 -- Check_Expr_Is_OK_Static_Expression --
5463 ----------------------------------------
5465 procedure Check_Expr_Is_OK_Static_Expression
5466 (Expr : Node_Id;
5467 Typ : Entity_Id := Empty)
5469 begin
5470 if Present (Typ) then
5471 Analyze_And_Resolve (Expr, Typ);
5472 else
5473 Analyze_And_Resolve (Expr);
5474 end if;
5476 -- An expression cannot be considered static if its resolution failed
5477 -- or if it's erroneous. Stop the analysis of the related pragma.
5479 if Etype (Expr) = Any_Type or else Error_Posted (Expr) then
5480 raise Pragma_Exit;
5482 elsif Is_OK_Static_Expression (Expr) then
5483 return;
5485 -- An interesting special case, if we have a string literal and we
5486 -- are in Ada 83 mode, then we allow it even though it will not be
5487 -- flagged as static. This allows the use of Ada 95 pragmas like
5488 -- Import in Ada 83 mode. They will of course be flagged with
5489 -- warnings as usual, but will not cause errors.
5491 elsif Ada_Version = Ada_83
5492 and then Nkind (Expr) = N_String_Literal
5493 then
5494 return;
5496 -- Finally, we have a real error
5498 else
5499 Error_Msg_Name_1 := Pname;
5500 Flag_Non_Static_Expr
5501 (Fix_Error ("argument for pragma% must be a static expression!"),
5502 Expr);
5503 raise Pragma_Exit;
5504 end if;
5505 end Check_Expr_Is_OK_Static_Expression;
5507 -------------------------
5508 -- Check_First_Subtype --
5509 -------------------------
5511 procedure Check_First_Subtype (Arg : Node_Id) is
5512 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5513 Ent : constant Entity_Id := Entity (Argx);
5515 begin
5516 if Is_First_Subtype (Ent) then
5517 null;
5519 elsif Is_Type (Ent) then
5520 Error_Pragma_Arg
5521 ("pragma% cannot apply to subtype", Argx);
5523 elsif Is_Object (Ent) then
5524 Error_Pragma_Arg
5525 ("pragma% cannot apply to object, requires a type", Argx);
5527 else
5528 Error_Pragma_Arg
5529 ("pragma% cannot apply to&, requires a type", Argx);
5530 end if;
5531 end Check_First_Subtype;
5533 ----------------------
5534 -- Check_Identifier --
5535 ----------------------
5537 procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
5538 begin
5539 if Present (Arg)
5540 and then Nkind (Arg) = N_Pragma_Argument_Association
5541 then
5542 if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
5543 Error_Msg_Name_1 := Pname;
5544 Error_Msg_Name_2 := Id;
5545 Error_Msg_N ("pragma% argument expects identifier%", Arg);
5546 raise Pragma_Exit;
5547 end if;
5548 end if;
5549 end Check_Identifier;
5551 --------------------------------
5552 -- Check_Identifier_Is_One_Of --
5553 --------------------------------
5555 procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
5556 begin
5557 if Present (Arg)
5558 and then Nkind (Arg) = N_Pragma_Argument_Association
5559 then
5560 if Chars (Arg) = No_Name then
5561 Error_Msg_Name_1 := Pname;
5562 Error_Msg_N ("pragma% argument expects an identifier", Arg);
5563 raise Pragma_Exit;
5565 elsif Chars (Arg) /= N1
5566 and then Chars (Arg) /= N2
5567 then
5568 Error_Msg_Name_1 := Pname;
5569 Error_Msg_N ("invalid identifier for pragma% argument", Arg);
5570 raise Pragma_Exit;
5571 end if;
5572 end if;
5573 end Check_Identifier_Is_One_Of;
5575 ---------------------------
5576 -- Check_In_Main_Program --
5577 ---------------------------
5579 procedure Check_In_Main_Program is
5580 P : constant Node_Id := Parent (N);
5582 begin
5583 -- Must be in subprogram body
5585 if Nkind (P) /= N_Subprogram_Body then
5586 Error_Pragma ("% pragma allowed only in subprogram");
5588 -- Otherwise warn if obviously not main program
5590 elsif Present (Parameter_Specifications (Specification (P)))
5591 or else not Is_Compilation_Unit (Defining_Entity (P))
5592 then
5593 Error_Msg_Name_1 := Pname;
5594 Error_Msg_N
5595 ("??pragma% is only effective in main program", N);
5596 end if;
5597 end Check_In_Main_Program;
5599 ---------------------------------------
5600 -- Check_Interrupt_Or_Attach_Handler --
5601 ---------------------------------------
5603 procedure Check_Interrupt_Or_Attach_Handler is
5604 Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
5605 Handler_Proc, Proc_Scope : Entity_Id;
5607 begin
5608 Analyze (Arg1_X);
5610 if Prag_Id = Pragma_Interrupt_Handler then
5611 Check_Restriction (No_Dynamic_Attachment, N);
5612 end if;
5614 Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
5615 Proc_Scope := Scope (Handler_Proc);
5617 if Ekind (Proc_Scope) /= E_Protected_Type then
5618 Error_Pragma_Arg
5619 ("argument of pragma% must be protected procedure", Arg1);
5620 end if;
5622 -- For pragma case (as opposed to access case), check placement.
5623 -- We don't need to do that for aspects, because we have the
5624 -- check that they aspect applies an appropriate procedure.
5626 if not From_Aspect_Specification (N)
5627 and then Parent (N) /= Protected_Definition (Parent (Proc_Scope))
5628 then
5629 Error_Pragma ("pragma% must be in protected definition");
5630 end if;
5632 if not Is_Library_Level_Entity (Proc_Scope) then
5633 Error_Pragma_Arg
5634 ("argument for pragma% must be library level entity", Arg1);
5635 end if;
5637 -- AI05-0033: A pragma cannot appear within a generic body, because
5638 -- instance can be in a nested scope. The check that protected type
5639 -- is itself a library-level declaration is done elsewhere.
5641 -- Note: we omit this check in Relaxed_RM_Semantics mode to properly
5642 -- handle code prior to AI-0033. Analysis tools typically are not
5643 -- interested in this pragma in any case, so no need to worry too
5644 -- much about its placement.
5646 if Inside_A_Generic then
5647 if Ekind (Scope (Current_Scope)) = E_Generic_Package
5648 and then In_Package_Body (Scope (Current_Scope))
5649 and then not Relaxed_RM_Semantics
5650 then
5651 Error_Pragma ("pragma% cannot be used inside a generic");
5652 end if;
5653 end if;
5654 end Check_Interrupt_Or_Attach_Handler;
5656 ---------------------------------
5657 -- Check_Loop_Pragma_Placement --
5658 ---------------------------------
5660 procedure Check_Loop_Pragma_Placement is
5661 procedure Check_Loop_Pragma_Grouping (Loop_Stmt : Node_Id);
5662 -- Verify whether the current pragma is properly grouped with other
5663 -- pragma Loop_Invariant and/or Loop_Variant. Node Loop_Stmt is the
5664 -- related loop where the pragma appears.
5666 function Is_Loop_Pragma (Stmt : Node_Id) return Boolean;
5667 -- Determine whether an arbitrary statement Stmt denotes pragma
5668 -- Loop_Invariant or Loop_Variant.
5670 procedure Placement_Error (Constr : Node_Id);
5671 pragma No_Return (Placement_Error);
5672 -- Node Constr denotes the last loop restricted construct before we
5673 -- encountered an illegal relation between enclosing constructs. Emit
5674 -- an error depending on what Constr was.
5676 --------------------------------
5677 -- Check_Loop_Pragma_Grouping --
5678 --------------------------------
5680 procedure Check_Loop_Pragma_Grouping (Loop_Stmt : Node_Id) is
5681 Stop_Search : exception;
5682 -- This exception is used to terminate the recursive descent of
5683 -- routine Check_Grouping.
5685 procedure Check_Grouping (L : List_Id);
5686 -- Find the first group of pragmas in list L and if successful,
5687 -- ensure that the current pragma is part of that group. The
5688 -- routine raises Stop_Search once such a check is performed to
5689 -- halt the recursive descent.
5691 procedure Grouping_Error (Prag : Node_Id);
5692 pragma No_Return (Grouping_Error);
5693 -- Emit an error concerning the current pragma indicating that it
5694 -- should be placed after pragma Prag.
5696 --------------------
5697 -- Check_Grouping --
5698 --------------------
5700 procedure Check_Grouping (L : List_Id) is
5701 HSS : Node_Id;
5702 Prag : Node_Id;
5703 Stmt : Node_Id;
5705 begin
5706 -- Inspect the list of declarations or statements looking for
5707 -- the first grouping of pragmas:
5709 -- loop
5710 -- pragma Loop_Invariant ...;
5711 -- pragma Loop_Variant ...;
5712 -- . . . -- (1)
5713 -- pragma Loop_Variant ...; -- current pragma
5715 -- If the current pragma is not in the grouping, then it must
5716 -- either appear in a different declarative or statement list
5717 -- or the construct at (1) is separating the pragma from the
5718 -- grouping.
5720 Stmt := First (L);
5721 while Present (Stmt) loop
5723 -- Pragmas Loop_Invariant and Loop_Variant may only appear
5724 -- inside a loop or a block housed inside a loop. Inspect
5725 -- the declarations and statements of the block as they may
5726 -- contain the first grouping.
5728 if Nkind (Stmt) = N_Block_Statement then
5729 HSS := Handled_Statement_Sequence (Stmt);
5731 Check_Grouping (Declarations (Stmt));
5733 if Present (HSS) then
5734 Check_Grouping (Statements (HSS));
5735 end if;
5737 -- First pragma of the first topmost grouping has been found
5739 elsif Is_Loop_Pragma (Stmt) then
5741 -- The group and the current pragma are not in the same
5742 -- declarative or statement list.
5744 if List_Containing (Stmt) /= List_Containing (N) then
5745 Grouping_Error (Stmt);
5747 -- Try to reach the current pragma from the first pragma
5748 -- of the grouping while skipping other members:
5750 -- pragma Loop_Invariant ...; -- first pragma
5751 -- pragma Loop_Variant ...; -- member
5752 -- . . .
5753 -- pragma Loop_Variant ...; -- current pragma
5755 else
5756 while Present (Stmt) loop
5758 -- The current pragma is either the first pragma
5759 -- of the group or is a member of the group. Stop
5760 -- the search as the placement is legal.
5762 if Stmt = N then
5763 raise Stop_Search;
5765 -- Skip group members, but keep track of the last
5766 -- pragma in the group.
5768 elsif Is_Loop_Pragma (Stmt) then
5769 Prag := Stmt;
5771 -- Skip declarations and statements generated by
5772 -- the compiler during expansion.
5774 elsif not Comes_From_Source (Stmt) then
5775 null;
5777 -- A non-pragma is separating the group from the
5778 -- current pragma, the placement is illegal.
5780 else
5781 Grouping_Error (Prag);
5782 end if;
5784 Next (Stmt);
5785 end loop;
5787 -- If the traversal did not reach the current pragma,
5788 -- then the list must be malformed.
5790 raise Program_Error;
5791 end if;
5792 end if;
5794 Next (Stmt);
5795 end loop;
5796 end Check_Grouping;
5798 --------------------
5799 -- Grouping_Error --
5800 --------------------
5802 procedure Grouping_Error (Prag : Node_Id) is
5803 begin
5804 Error_Msg_Sloc := Sloc (Prag);
5805 Error_Pragma ("pragma% must appear next to pragma#");
5806 end Grouping_Error;
5808 -- Start of processing for Check_Loop_Pragma_Grouping
5810 begin
5811 -- Inspect the statements of the loop or nested blocks housed
5812 -- within to determine whether the current pragma is part of the
5813 -- first topmost grouping of Loop_Invariant and Loop_Variant.
5815 Check_Grouping (Statements (Loop_Stmt));
5817 exception
5818 when Stop_Search => null;
5819 end Check_Loop_Pragma_Grouping;
5821 --------------------
5822 -- Is_Loop_Pragma --
5823 --------------------
5825 function Is_Loop_Pragma (Stmt : Node_Id) return Boolean is
5826 begin
5827 -- Inspect the original node as Loop_Invariant and Loop_Variant
5828 -- pragmas are rewritten to null when assertions are disabled.
5830 if Nkind (Original_Node (Stmt)) = N_Pragma then
5831 return
5832 Nam_In (Pragma_Name_Unmapped (Original_Node (Stmt)),
5833 Name_Loop_Invariant,
5834 Name_Loop_Variant);
5835 else
5836 return False;
5837 end if;
5838 end Is_Loop_Pragma;
5840 ---------------------
5841 -- Placement_Error --
5842 ---------------------
5844 procedure Placement_Error (Constr : Node_Id) is
5845 LA : constant String := " with Loop_Entry";
5847 begin
5848 if Prag_Id = Pragma_Assert then
5849 Error_Msg_String (1 .. LA'Length) := LA;
5850 Error_Msg_Strlen := LA'Length;
5851 else
5852 Error_Msg_Strlen := 0;
5853 end if;
5855 if Nkind (Constr) = N_Pragma then
5856 Error_Pragma
5857 ("pragma %~ must appear immediately within the statements "
5858 & "of a loop");
5859 else
5860 Error_Pragma_Arg
5861 ("block containing pragma %~ must appear immediately within "
5862 & "the statements of a loop", Constr);
5863 end if;
5864 end Placement_Error;
5866 -- Local declarations
5868 Prev : Node_Id;
5869 Stmt : Node_Id;
5871 -- Start of processing for Check_Loop_Pragma_Placement
5873 begin
5874 -- Check that pragma appears immediately within a loop statement,
5875 -- ignoring intervening block statements.
5877 Prev := N;
5878 Stmt := Parent (N);
5879 while Present (Stmt) loop
5881 -- The pragma or previous block must appear immediately within the
5882 -- current block's declarative or statement part.
5884 if Nkind (Stmt) = N_Block_Statement then
5885 if (No (Declarations (Stmt))
5886 or else List_Containing (Prev) /= Declarations (Stmt))
5887 and then
5888 List_Containing (Prev) /=
5889 Statements (Handled_Statement_Sequence (Stmt))
5890 then
5891 Placement_Error (Prev);
5892 return;
5894 -- Keep inspecting the parents because we are now within a
5895 -- chain of nested blocks.
5897 else
5898 Prev := Stmt;
5899 Stmt := Parent (Stmt);
5900 end if;
5902 -- The pragma or previous block must appear immediately within the
5903 -- statements of the loop.
5905 elsif Nkind (Stmt) = N_Loop_Statement then
5906 if List_Containing (Prev) /= Statements (Stmt) then
5907 Placement_Error (Prev);
5908 end if;
5910 -- Stop the traversal because we reached the innermost loop
5911 -- regardless of whether we encountered an error or not.
5913 exit;
5915 -- Ignore a handled statement sequence. Note that this node may
5916 -- be related to a subprogram body in which case we will emit an
5917 -- error on the next iteration of the search.
5919 elsif Nkind (Stmt) = N_Handled_Sequence_Of_Statements then
5920 Stmt := Parent (Stmt);
5922 -- Any other statement breaks the chain from the pragma to the
5923 -- loop.
5925 else
5926 Placement_Error (Prev);
5927 return;
5928 end if;
5929 end loop;
5931 -- Check that the current pragma Loop_Invariant or Loop_Variant is
5932 -- grouped together with other such pragmas.
5934 if Is_Loop_Pragma (N) then
5936 -- The previous check should have located the related loop
5938 pragma Assert (Nkind (Stmt) = N_Loop_Statement);
5939 Check_Loop_Pragma_Grouping (Stmt);
5940 end if;
5941 end Check_Loop_Pragma_Placement;
5943 -------------------------------------------
5944 -- Check_Is_In_Decl_Part_Or_Package_Spec --
5945 -------------------------------------------
5947 procedure Check_Is_In_Decl_Part_Or_Package_Spec is
5948 P : Node_Id;
5950 begin
5951 P := Parent (N);
5952 loop
5953 if No (P) then
5954 exit;
5956 elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
5957 exit;
5959 elsif Nkind_In (P, N_Package_Specification,
5960 N_Block_Statement)
5961 then
5962 return;
5964 -- Note: the following tests seem a little peculiar, because
5965 -- they test for bodies, but if we were in the statement part
5966 -- of the body, we would already have hit the handled statement
5967 -- sequence, so the only way we get here is by being in the
5968 -- declarative part of the body.
5970 elsif Nkind_In (P, N_Subprogram_Body,
5971 N_Package_Body,
5972 N_Task_Body,
5973 N_Entry_Body)
5974 then
5975 return;
5976 end if;
5978 P := Parent (P);
5979 end loop;
5981 Error_Pragma ("pragma% is not in declarative part or package spec");
5982 end Check_Is_In_Decl_Part_Or_Package_Spec;
5984 -------------------------
5985 -- Check_No_Identifier --
5986 -------------------------
5988 procedure Check_No_Identifier (Arg : Node_Id) is
5989 begin
5990 if Nkind (Arg) = N_Pragma_Argument_Association
5991 and then Chars (Arg) /= No_Name
5992 then
5993 Error_Pragma_Arg_Ident
5994 ("pragma% does not permit identifier& here", Arg);
5995 end if;
5996 end Check_No_Identifier;
5998 --------------------------
5999 -- Check_No_Identifiers --
6000 --------------------------
6002 procedure Check_No_Identifiers is
6003 Arg_Node : Node_Id;
6004 begin
6005 Arg_Node := Arg1;
6006 for J in 1 .. Arg_Count loop
6007 Check_No_Identifier (Arg_Node);
6008 Next (Arg_Node);
6009 end loop;
6010 end Check_No_Identifiers;
6012 ------------------------
6013 -- Check_No_Link_Name --
6014 ------------------------
6016 procedure Check_No_Link_Name is
6017 begin
6018 if Present (Arg3) and then Chars (Arg3) = Name_Link_Name then
6019 Arg4 := Arg3;
6020 end if;
6022 if Present (Arg4) then
6023 Error_Pragma_Arg
6024 ("Link_Name argument not allowed for Import Intrinsic", Arg4);
6025 end if;
6026 end Check_No_Link_Name;
6028 -------------------------------
6029 -- Check_Optional_Identifier --
6030 -------------------------------
6032 procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
6033 begin
6034 if Present (Arg)
6035 and then Nkind (Arg) = N_Pragma_Argument_Association
6036 and then Chars (Arg) /= No_Name
6037 then
6038 if Chars (Arg) /= Id then
6039 Error_Msg_Name_1 := Pname;
6040 Error_Msg_Name_2 := Id;
6041 Error_Msg_N ("pragma% argument expects identifier%", Arg);
6042 raise Pragma_Exit;
6043 end if;
6044 end if;
6045 end Check_Optional_Identifier;
6047 procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
6048 begin
6049 Check_Optional_Identifier (Arg, Name_Find (Id));
6050 end Check_Optional_Identifier;
6052 -------------------------------------
6053 -- Check_Static_Boolean_Expression --
6054 -------------------------------------
6056 procedure Check_Static_Boolean_Expression (Expr : Node_Id) is
6057 begin
6058 if Present (Expr) then
6059 Analyze_And_Resolve (Expr, Standard_Boolean);
6061 if not Is_OK_Static_Expression (Expr) then
6062 Error_Pragma_Arg
6063 ("expression of pragma % must be static", Expr);
6064 end if;
6065 end if;
6066 end Check_Static_Boolean_Expression;
6068 -----------------------------
6069 -- Check_Static_Constraint --
6070 -----------------------------
6072 -- Note: for convenience in writing this procedure, in addition to
6073 -- the officially (i.e. by spec) allowed argument which is always a
6074 -- constraint, it also allows ranges and discriminant associations.
6075 -- Above is not clear ???
6077 procedure Check_Static_Constraint (Constr : Node_Id) is
6079 procedure Require_Static (E : Node_Id);
6080 -- Require given expression to be static expression
6082 --------------------
6083 -- Require_Static --
6084 --------------------
6086 procedure Require_Static (E : Node_Id) is
6087 begin
6088 if not Is_OK_Static_Expression (E) then
6089 Flag_Non_Static_Expr
6090 ("non-static constraint not allowed in Unchecked_Union!", E);
6091 raise Pragma_Exit;
6092 end if;
6093 end Require_Static;
6095 -- Start of processing for Check_Static_Constraint
6097 begin
6098 case Nkind (Constr) is
6099 when N_Discriminant_Association =>
6100 Require_Static (Expression (Constr));
6102 when N_Range =>
6103 Require_Static (Low_Bound (Constr));
6104 Require_Static (High_Bound (Constr));
6106 when N_Attribute_Reference =>
6107 Require_Static (Type_Low_Bound (Etype (Prefix (Constr))));
6108 Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
6110 when N_Range_Constraint =>
6111 Check_Static_Constraint (Range_Expression (Constr));
6113 when N_Index_Or_Discriminant_Constraint =>
6114 declare
6115 IDC : Entity_Id;
6116 begin
6117 IDC := First (Constraints (Constr));
6118 while Present (IDC) loop
6119 Check_Static_Constraint (IDC);
6120 Next (IDC);
6121 end loop;
6122 end;
6124 when others =>
6125 null;
6126 end case;
6127 end Check_Static_Constraint;
6129 --------------------------------------
6130 -- Check_Valid_Configuration_Pragma --
6131 --------------------------------------
6133 -- A configuration pragma must appear in the context clause of a
6134 -- compilation unit, and only other pragmas may precede it. Note that
6135 -- the test also allows use in a configuration pragma file.
6137 procedure Check_Valid_Configuration_Pragma is
6138 begin
6139 if not Is_Configuration_Pragma then
6140 Error_Pragma ("incorrect placement for configuration pragma%");
6141 end if;
6142 end Check_Valid_Configuration_Pragma;
6144 -------------------------------------
6145 -- Check_Valid_Library_Unit_Pragma --
6146 -------------------------------------
6148 procedure Check_Valid_Library_Unit_Pragma is
6149 Plist : List_Id;
6150 Parent_Node : Node_Id;
6151 Unit_Name : Entity_Id;
6152 Unit_Kind : Node_Kind;
6153 Unit_Node : Node_Id;
6154 Sindex : Source_File_Index;
6156 begin
6157 if not Is_List_Member (N) then
6158 Pragma_Misplaced;
6160 else
6161 Plist := List_Containing (N);
6162 Parent_Node := Parent (Plist);
6164 if Parent_Node = Empty then
6165 Pragma_Misplaced;
6167 -- Case of pragma appearing after a compilation unit. In this case
6168 -- it must have an argument with the corresponding name and must
6169 -- be part of the following pragmas of its parent.
6171 elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
6172 if Plist /= Pragmas_After (Parent_Node) then
6173 Pragma_Misplaced;
6175 elsif Arg_Count = 0 then
6176 Error_Pragma
6177 ("argument required if outside compilation unit");
6179 else
6180 Check_No_Identifiers;
6181 Check_Arg_Count (1);
6182 Unit_Node := Unit (Parent (Parent_Node));
6183 Unit_Kind := Nkind (Unit_Node);
6185 Analyze (Get_Pragma_Arg (Arg1));
6187 if Unit_Kind = N_Generic_Subprogram_Declaration
6188 or else Unit_Kind = N_Subprogram_Declaration
6189 then
6190 Unit_Name := Defining_Entity (Unit_Node);
6192 elsif Unit_Kind in N_Generic_Instantiation then
6193 Unit_Name := Defining_Entity (Unit_Node);
6195 else
6196 Unit_Name := Cunit_Entity (Current_Sem_Unit);
6197 end if;
6199 if Chars (Unit_Name) /=
6200 Chars (Entity (Get_Pragma_Arg (Arg1)))
6201 then
6202 Error_Pragma_Arg
6203 ("pragma% argument is not current unit name", Arg1);
6204 end if;
6206 if Ekind (Unit_Name) = E_Package
6207 and then Present (Renamed_Entity (Unit_Name))
6208 then
6209 Error_Pragma ("pragma% not allowed for renamed package");
6210 end if;
6211 end if;
6213 -- Pragma appears other than after a compilation unit
6215 else
6216 -- Here we check for the generic instantiation case and also
6217 -- for the case of processing a generic formal package. We
6218 -- detect these cases by noting that the Sloc on the node
6219 -- does not belong to the current compilation unit.
6221 Sindex := Source_Index (Current_Sem_Unit);
6223 if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
6224 Rewrite (N, Make_Null_Statement (Loc));
6225 return;
6227 -- If before first declaration, the pragma applies to the
6228 -- enclosing unit, and the name if present must be this name.
6230 elsif Is_Before_First_Decl (N, Plist) then
6231 Unit_Node := Unit_Declaration_Node (Current_Scope);
6232 Unit_Kind := Nkind (Unit_Node);
6234 if Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
6235 Pragma_Misplaced;
6237 elsif Unit_Kind = N_Subprogram_Body
6238 and then not Acts_As_Spec (Unit_Node)
6239 then
6240 Pragma_Misplaced;
6242 elsif Nkind (Parent_Node) = N_Package_Body then
6243 Pragma_Misplaced;
6245 elsif Nkind (Parent_Node) = N_Package_Specification
6246 and then Plist = Private_Declarations (Parent_Node)
6247 then
6248 Pragma_Misplaced;
6250 elsif (Nkind (Parent_Node) = N_Generic_Package_Declaration
6251 or else Nkind (Parent_Node) =
6252 N_Generic_Subprogram_Declaration)
6253 and then Plist = Generic_Formal_Declarations (Parent_Node)
6254 then
6255 Pragma_Misplaced;
6257 elsif Arg_Count > 0 then
6258 Analyze (Get_Pragma_Arg (Arg1));
6260 if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
6261 Error_Pragma_Arg
6262 ("name in pragma% must be enclosing unit", Arg1);
6263 end if;
6265 -- It is legal to have no argument in this context
6267 else
6268 return;
6269 end if;
6271 -- Error if not before first declaration. This is because a
6272 -- library unit pragma argument must be the name of a library
6273 -- unit (RM 10.1.5(7)), but the only names permitted in this
6274 -- context are (RM 10.1.5(6)) names of subprogram declarations,
6275 -- generic subprogram declarations or generic instantiations.
6277 else
6278 Error_Pragma
6279 ("pragma% misplaced, must be before first declaration");
6280 end if;
6281 end if;
6282 end if;
6283 end Check_Valid_Library_Unit_Pragma;
6285 -------------------
6286 -- Check_Variant --
6287 -------------------
6289 procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
6290 Clist : constant Node_Id := Component_List (Variant);
6291 Comp : Node_Id;
6293 begin
6294 Comp := First (Component_Items (Clist));
6295 while Present (Comp) loop
6296 Check_Component (Comp, UU_Typ, In_Variant_Part => True);
6297 Next (Comp);
6298 end loop;
6299 end Check_Variant;
6301 ---------------------------
6302 -- Ensure_Aggregate_Form --
6303 ---------------------------
6305 procedure Ensure_Aggregate_Form (Arg : Node_Id) is
6306 CFSD : constant Boolean := Get_Comes_From_Source_Default;
6307 Expr : constant Node_Id := Expression (Arg);
6308 Loc : constant Source_Ptr := Sloc (Expr);
6309 Comps : List_Id := No_List;
6310 Exprs : List_Id := No_List;
6311 Nam : Name_Id := No_Name;
6312 Nam_Loc : Source_Ptr;
6314 begin
6315 -- The pragma argument is in positional form:
6317 -- pragma Depends (Nam => ...)
6318 -- ^
6319 -- Chars field
6321 -- Note that the Sloc of the Chars field is the Sloc of the pragma
6322 -- argument association.
6324 if Nkind (Arg) = N_Pragma_Argument_Association then
6325 Nam := Chars (Arg);
6326 Nam_Loc := Sloc (Arg);
6328 -- Remove the pragma argument name as this will be captured in the
6329 -- aggregate.
6331 Set_Chars (Arg, No_Name);
6332 end if;
6334 -- The argument is already in aggregate form, but the presence of a
6335 -- name causes this to be interpreted as named association which in
6336 -- turn must be converted into an aggregate.
6338 -- pragma Global (In_Out => (A, B, C))
6339 -- ^ ^
6340 -- name aggregate
6342 -- pragma Global ((In_Out => (A, B, C)))
6343 -- ^ ^
6344 -- aggregate aggregate
6346 if Nkind (Expr) = N_Aggregate then
6347 if Nam = No_Name then
6348 return;
6349 end if;
6351 -- Do not transform a null argument into an aggregate as N_Null has
6352 -- special meaning in formal verification pragmas.
6354 elsif Nkind (Expr) = N_Null then
6355 return;
6356 end if;
6358 -- Everything comes from source if the original comes from source
6360 Set_Comes_From_Source_Default (Comes_From_Source (Arg));
6362 -- Positional argument is transformed into an aggregate with an
6363 -- Expressions list.
6365 if Nam = No_Name then
6366 Exprs := New_List (Relocate_Node (Expr));
6368 -- An associative argument is transformed into an aggregate with
6369 -- Component_Associations.
6371 else
6372 Comps := New_List (
6373 Make_Component_Association (Loc,
6374 Choices => New_List (Make_Identifier (Nam_Loc, Nam)),
6375 Expression => Relocate_Node (Expr)));
6376 end if;
6378 Set_Expression (Arg,
6379 Make_Aggregate (Loc,
6380 Component_Associations => Comps,
6381 Expressions => Exprs));
6383 -- Restore Comes_From_Source default
6385 Set_Comes_From_Source_Default (CFSD);
6386 end Ensure_Aggregate_Form;
6388 ------------------
6389 -- Error_Pragma --
6390 ------------------
6392 procedure Error_Pragma (Msg : String) is
6393 begin
6394 Error_Msg_Name_1 := Pname;
6395 Error_Msg_N (Fix_Error (Msg), N);
6396 raise Pragma_Exit;
6397 end Error_Pragma;
6399 ----------------------
6400 -- Error_Pragma_Arg --
6401 ----------------------
6403 procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
6404 begin
6405 Error_Msg_Name_1 := Pname;
6406 Error_Msg_N (Fix_Error (Msg), Get_Pragma_Arg (Arg));
6407 raise Pragma_Exit;
6408 end Error_Pragma_Arg;
6410 procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
6411 begin
6412 Error_Msg_Name_1 := Pname;
6413 Error_Msg_N (Fix_Error (Msg1), Get_Pragma_Arg (Arg));
6414 Error_Pragma_Arg (Msg2, Arg);
6415 end Error_Pragma_Arg;
6417 ----------------------------
6418 -- Error_Pragma_Arg_Ident --
6419 ----------------------------
6421 procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
6422 begin
6423 Error_Msg_Name_1 := Pname;
6424 Error_Msg_N (Fix_Error (Msg), Arg);
6425 raise Pragma_Exit;
6426 end Error_Pragma_Arg_Ident;
6428 ----------------------
6429 -- Error_Pragma_Ref --
6430 ----------------------
6432 procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
6433 begin
6434 Error_Msg_Name_1 := Pname;
6435 Error_Msg_Sloc := Sloc (Ref);
6436 Error_Msg_NE (Fix_Error (Msg), N, Ref);
6437 raise Pragma_Exit;
6438 end Error_Pragma_Ref;
6440 ------------------------
6441 -- Find_Lib_Unit_Name --
6442 ------------------------
6444 function Find_Lib_Unit_Name return Entity_Id is
6445 begin
6446 -- Return inner compilation unit entity, for case of nested
6447 -- categorization pragmas. This happens in generic unit.
6449 if Nkind (Parent (N)) = N_Package_Specification
6450 and then Defining_Entity (Parent (N)) /= Current_Scope
6451 then
6452 return Defining_Entity (Parent (N));
6453 else
6454 return Current_Scope;
6455 end if;
6456 end Find_Lib_Unit_Name;
6458 ----------------------------
6459 -- Find_Program_Unit_Name --
6460 ----------------------------
6462 procedure Find_Program_Unit_Name (Id : Node_Id) is
6463 Unit_Name : Entity_Id;
6464 Unit_Kind : Node_Kind;
6465 P : constant Node_Id := Parent (N);
6467 begin
6468 if Nkind (P) = N_Compilation_Unit then
6469 Unit_Kind := Nkind (Unit (P));
6471 if Nkind_In (Unit_Kind, N_Subprogram_Declaration,
6472 N_Package_Declaration)
6473 or else Unit_Kind in N_Generic_Declaration
6474 then
6475 Unit_Name := Defining_Entity (Unit (P));
6477 if Chars (Id) = Chars (Unit_Name) then
6478 Set_Entity (Id, Unit_Name);
6479 Set_Etype (Id, Etype (Unit_Name));
6480 else
6481 Set_Etype (Id, Any_Type);
6482 Error_Pragma
6483 ("cannot find program unit referenced by pragma%");
6484 end if;
6486 else
6487 Set_Etype (Id, Any_Type);
6488 Error_Pragma ("pragma% inapplicable to this unit");
6489 end if;
6491 else
6492 Analyze (Id);
6493 end if;
6494 end Find_Program_Unit_Name;
6496 -----------------------------------------
6497 -- Find_Unique_Parameterless_Procedure --
6498 -----------------------------------------
6500 function Find_Unique_Parameterless_Procedure
6501 (Name : Entity_Id;
6502 Arg : Node_Id) return Entity_Id
6504 Proc : Entity_Id := Empty;
6506 begin
6507 -- The body of this procedure needs some comments ???
6509 if not Is_Entity_Name (Name) then
6510 Error_Pragma_Arg
6511 ("argument of pragma% must be entity name", Arg);
6513 elsif not Is_Overloaded (Name) then
6514 Proc := Entity (Name);
6516 if Ekind (Proc) /= E_Procedure
6517 or else Present (First_Formal (Proc))
6518 then
6519 Error_Pragma_Arg
6520 ("argument of pragma% must be parameterless procedure", Arg);
6521 end if;
6523 else
6524 declare
6525 Found : Boolean := False;
6526 It : Interp;
6527 Index : Interp_Index;
6529 begin
6530 Get_First_Interp (Name, Index, It);
6531 while Present (It.Nam) loop
6532 Proc := It.Nam;
6534 if Ekind (Proc) = E_Procedure
6535 and then No (First_Formal (Proc))
6536 then
6537 if not Found then
6538 Found := True;
6539 Set_Entity (Name, Proc);
6540 Set_Is_Overloaded (Name, False);
6541 else
6542 Error_Pragma_Arg
6543 ("ambiguous handler name for pragma% ", Arg);
6544 end if;
6545 end if;
6547 Get_Next_Interp (Index, It);
6548 end loop;
6550 if not Found then
6551 Error_Pragma_Arg
6552 ("argument of pragma% must be parameterless procedure",
6553 Arg);
6554 else
6555 Proc := Entity (Name);
6556 end if;
6557 end;
6558 end if;
6560 return Proc;
6561 end Find_Unique_Parameterless_Procedure;
6563 ---------------
6564 -- Fix_Error --
6565 ---------------
6567 function Fix_Error (Msg : String) return String is
6568 Res : String (Msg'Range) := Msg;
6569 Res_Last : Natural := Msg'Last;
6570 J : Natural;
6572 begin
6573 -- If we have a rewriting of another pragma, go to that pragma
6575 if Is_Rewrite_Substitution (N)
6576 and then Nkind (Original_Node (N)) = N_Pragma
6577 then
6578 Error_Msg_Name_1 := Pragma_Name (Original_Node (N));
6579 end if;
6581 -- Case where pragma comes from an aspect specification
6583 if From_Aspect_Specification (N) then
6585 -- Change appearence of "pragma" in message to "aspect"
6587 J := Res'First;
6588 while J <= Res_Last - 5 loop
6589 if Res (J .. J + 5) = "pragma" then
6590 Res (J .. J + 5) := "aspect";
6591 J := J + 6;
6593 else
6594 J := J + 1;
6595 end if;
6596 end loop;
6598 -- Change "argument of" at start of message to "entity for"
6600 if Res'Length > 11
6601 and then Res (Res'First .. Res'First + 10) = "argument of"
6602 then
6603 Res (Res'First .. Res'First + 9) := "entity for";
6604 Res (Res'First + 10 .. Res_Last - 1) :=
6605 Res (Res'First + 11 .. Res_Last);
6606 Res_Last := Res_Last - 1;
6607 end if;
6609 -- Change "argument" at start of message to "entity"
6611 if Res'Length > 8
6612 and then Res (Res'First .. Res'First + 7) = "argument"
6613 then
6614 Res (Res'First .. Res'First + 5) := "entity";
6615 Res (Res'First + 6 .. Res_Last - 2) :=
6616 Res (Res'First + 8 .. Res_Last);
6617 Res_Last := Res_Last - 2;
6618 end if;
6620 -- Get name from corresponding aspect
6622 Error_Msg_Name_1 := Original_Aspect_Pragma_Name (N);
6623 end if;
6625 -- Return possibly modified message
6627 return Res (Res'First .. Res_Last);
6628 end Fix_Error;
6630 -------------------------
6631 -- Gather_Associations --
6632 -------------------------
6634 procedure Gather_Associations
6635 (Names : Name_List;
6636 Args : out Args_List)
6638 Arg : Node_Id;
6640 begin
6641 -- Initialize all parameters to Empty
6643 for J in Args'Range loop
6644 Args (J) := Empty;
6645 end loop;
6647 -- That's all we have to do if there are no argument associations
6649 if No (Pragma_Argument_Associations (N)) then
6650 return;
6651 end if;
6653 -- Otherwise first deal with any positional parameters present
6655 Arg := First (Pragma_Argument_Associations (N));
6656 for Index in Args'Range loop
6657 exit when No (Arg) or else Chars (Arg) /= No_Name;
6658 Args (Index) := Get_Pragma_Arg (Arg);
6659 Next (Arg);
6660 end loop;
6662 -- Positional parameters all processed, if any left, then we
6663 -- have too many positional parameters.
6665 if Present (Arg) and then Chars (Arg) = No_Name then
6666 Error_Pragma_Arg
6667 ("too many positional associations for pragma%", Arg);
6668 end if;
6670 -- Process named parameters if any are present
6672 while Present (Arg) loop
6673 if Chars (Arg) = No_Name then
6674 Error_Pragma_Arg
6675 ("positional association cannot follow named association",
6676 Arg);
6678 else
6679 for Index in Names'Range loop
6680 if Names (Index) = Chars (Arg) then
6681 if Present (Args (Index)) then
6682 Error_Pragma_Arg
6683 ("duplicate argument association for pragma%", Arg);
6684 else
6685 Args (Index) := Get_Pragma_Arg (Arg);
6686 exit;
6687 end if;
6688 end if;
6690 if Index = Names'Last then
6691 Error_Msg_Name_1 := Pname;
6692 Error_Msg_N ("pragma% does not allow & argument", Arg);
6694 -- Check for possible misspelling
6696 for Index1 in Names'Range loop
6697 if Is_Bad_Spelling_Of
6698 (Chars (Arg), Names (Index1))
6699 then
6700 Error_Msg_Name_1 := Names (Index1);
6701 Error_Msg_N -- CODEFIX
6702 ("\possible misspelling of%", Arg);
6703 exit;
6704 end if;
6705 end loop;
6707 raise Pragma_Exit;
6708 end if;
6709 end loop;
6710 end if;
6712 Next (Arg);
6713 end loop;
6714 end Gather_Associations;
6716 -----------------
6717 -- GNAT_Pragma --
6718 -----------------
6720 procedure GNAT_Pragma is
6721 begin
6722 -- We need to check the No_Implementation_Pragmas restriction for
6723 -- the case of a pragma from source. Note that the case of aspects
6724 -- generating corresponding pragmas marks these pragmas as not being
6725 -- from source, so this test also catches that case.
6727 if Comes_From_Source (N) then
6728 Check_Restriction (No_Implementation_Pragmas, N);
6729 end if;
6730 end GNAT_Pragma;
6732 --------------------------
6733 -- Is_Before_First_Decl --
6734 --------------------------
6736 function Is_Before_First_Decl
6737 (Pragma_Node : Node_Id;
6738 Decls : List_Id) return Boolean
6740 Item : Node_Id := First (Decls);
6742 begin
6743 -- Only other pragmas can come before this pragma
6745 loop
6746 if No (Item) or else Nkind (Item) /= N_Pragma then
6747 return False;
6749 elsif Item = Pragma_Node then
6750 return True;
6751 end if;
6753 Next (Item);
6754 end loop;
6755 end Is_Before_First_Decl;
6757 -----------------------------
6758 -- Is_Configuration_Pragma --
6759 -----------------------------
6761 -- A configuration pragma must appear in the context clause of a
6762 -- compilation unit, and only other pragmas may precede it. Note that
6763 -- the test below also permits use in a configuration pragma file.
6765 function Is_Configuration_Pragma return Boolean is
6766 Lis : constant List_Id := List_Containing (N);
6767 Par : constant Node_Id := Parent (N);
6768 Prg : Node_Id;
6770 begin
6771 -- If no parent, then we are in the configuration pragma file,
6772 -- so the placement is definitely appropriate.
6774 if No (Par) then
6775 return True;
6777 -- Otherwise we must be in the context clause of a compilation unit
6778 -- and the only thing allowed before us in the context list is more
6779 -- configuration pragmas.
6781 elsif Nkind (Par) = N_Compilation_Unit
6782 and then Context_Items (Par) = Lis
6783 then
6784 Prg := First (Lis);
6786 loop
6787 if Prg = N then
6788 return True;
6789 elsif Nkind (Prg) /= N_Pragma then
6790 return False;
6791 end if;
6793 Next (Prg);
6794 end loop;
6796 else
6797 return False;
6798 end if;
6799 end Is_Configuration_Pragma;
6801 --------------------------
6802 -- Is_In_Context_Clause --
6803 --------------------------
6805 function Is_In_Context_Clause return Boolean is
6806 Plist : List_Id;
6807 Parent_Node : Node_Id;
6809 begin
6810 if not Is_List_Member (N) then
6811 return False;
6813 else
6814 Plist := List_Containing (N);
6815 Parent_Node := Parent (Plist);
6817 if Parent_Node = Empty
6818 or else Nkind (Parent_Node) /= N_Compilation_Unit
6819 or else Context_Items (Parent_Node) /= Plist
6820 then
6821 return False;
6822 end if;
6823 end if;
6825 return True;
6826 end Is_In_Context_Clause;
6828 ---------------------------------
6829 -- Is_Static_String_Expression --
6830 ---------------------------------
6832 function Is_Static_String_Expression (Arg : Node_Id) return Boolean is
6833 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6834 Lit : constant Boolean := Nkind (Argx) = N_String_Literal;
6836 begin
6837 Analyze_And_Resolve (Argx);
6839 -- Special case Ada 83, where the expression will never be static,
6840 -- but we will return true if we had a string literal to start with.
6842 if Ada_Version = Ada_83 then
6843 return Lit;
6845 -- Normal case, true only if we end up with a string literal that
6846 -- is marked as being the result of evaluating a static expression.
6848 else
6849 return Is_OK_Static_Expression (Argx)
6850 and then Nkind (Argx) = N_String_Literal;
6851 end if;
6853 end Is_Static_String_Expression;
6855 ----------------------
6856 -- Pragma_Misplaced --
6857 ----------------------
6859 procedure Pragma_Misplaced is
6860 begin
6861 Error_Pragma ("incorrect placement of pragma%");
6862 end Pragma_Misplaced;
6864 ------------------------------------------------
6865 -- Process_Atomic_Independent_Shared_Volatile --
6866 ------------------------------------------------
6868 procedure Process_Atomic_Independent_Shared_Volatile is
6869 procedure Set_Atomic_VFA (E : Entity_Id);
6870 -- Set given type as Is_Atomic or Is_Volatile_Full_Access. Also, if
6871 -- no explicit alignment was given, set alignment to unknown, since
6872 -- back end knows what the alignment requirements are for atomic and
6873 -- full access arrays. Note: this is necessary for derived types.
6875 --------------------
6876 -- Set_Atomic_VFA --
6877 --------------------
6879 procedure Set_Atomic_VFA (E : Entity_Id) is
6880 begin
6881 if Prag_Id = Pragma_Volatile_Full_Access then
6882 Set_Is_Volatile_Full_Access (E);
6883 else
6884 Set_Is_Atomic (E);
6885 end if;
6887 if not Has_Alignment_Clause (E) then
6888 Set_Alignment (E, Uint_0);
6889 end if;
6890 end Set_Atomic_VFA;
6892 -- Local variables
6894 Decl : Node_Id;
6895 E : Entity_Id;
6896 E_Arg : Node_Id;
6898 -- Start of processing for Process_Atomic_Independent_Shared_Volatile
6900 begin
6901 Check_Ada_83_Warning;
6902 Check_No_Identifiers;
6903 Check_Arg_Count (1);
6904 Check_Arg_Is_Local_Name (Arg1);
6905 E_Arg := Get_Pragma_Arg (Arg1);
6907 if Etype (E_Arg) = Any_Type then
6908 return;
6909 end if;
6911 E := Entity (E_Arg);
6913 -- A pragma that applies to a Ghost entity becomes Ghost for the
6914 -- purposes of legality checks and removal of ignored Ghost code.
6916 Mark_Ghost_Pragma (N, E);
6918 -- Check duplicate before we chain ourselves
6920 Check_Duplicate_Pragma (E);
6922 -- Check Atomic and VFA used together
6924 if (Is_Atomic (E) and then Prag_Id = Pragma_Volatile_Full_Access)
6925 or else (Is_Volatile_Full_Access (E)
6926 and then (Prag_Id = Pragma_Atomic
6927 or else
6928 Prag_Id = Pragma_Shared))
6929 then
6930 Error_Pragma
6931 ("cannot have Volatile_Full_Access and Atomic for same entity");
6932 end if;
6934 -- Check for applying VFA to an entity which has aliased component
6936 if Prag_Id = Pragma_Volatile_Full_Access then
6937 declare
6938 Comp : Entity_Id;
6939 Aliased_Comp : Boolean := False;
6940 -- Set True if aliased component present
6942 begin
6943 if Is_Array_Type (Etype (E)) then
6944 Aliased_Comp := Has_Aliased_Components (Etype (E));
6946 -- Record case, too bad Has_Aliased_Components is not also
6947 -- set for records, should it be ???
6949 elsif Is_Record_Type (Etype (E)) then
6950 Comp := First_Component_Or_Discriminant (Etype (E));
6951 while Present (Comp) loop
6952 if Is_Aliased (Comp)
6953 or else Is_Aliased (Etype (Comp))
6954 then
6955 Aliased_Comp := True;
6956 exit;
6957 end if;
6959 Next_Component_Or_Discriminant (Comp);
6960 end loop;
6961 end if;
6963 if Aliased_Comp then
6964 Error_Pragma
6965 ("cannot apply Volatile_Full_Access (aliased component "
6966 & "present)");
6967 end if;
6968 end;
6969 end if;
6971 -- Now check appropriateness of the entity
6973 Decl := Declaration_Node (E);
6975 if Is_Type (E) then
6976 if Rep_Item_Too_Early (E, N)
6977 or else
6978 Rep_Item_Too_Late (E, N)
6979 then
6980 return;
6981 else
6982 Check_First_Subtype (Arg1);
6983 end if;
6985 -- Attribute belongs on the base type. If the view of the type is
6986 -- currently private, it also belongs on the underlying type.
6988 if Prag_Id = Pragma_Atomic
6989 or else
6990 Prag_Id = Pragma_Shared
6991 or else
6992 Prag_Id = Pragma_Volatile_Full_Access
6993 then
6994 Set_Atomic_VFA (E);
6995 Set_Atomic_VFA (Base_Type (E));
6996 Set_Atomic_VFA (Underlying_Type (E));
6997 end if;
6999 -- Atomic/Shared/Volatile_Full_Access imply Independent
7001 if Prag_Id /= Pragma_Volatile then
7002 Set_Is_Independent (E);
7003 Set_Is_Independent (Base_Type (E));
7004 Set_Is_Independent (Underlying_Type (E));
7006 if Prag_Id = Pragma_Independent then
7007 Record_Independence_Check (N, Base_Type (E));
7008 end if;
7009 end if;
7011 -- Atomic/Shared/Volatile_Full_Access imply Volatile
7013 if Prag_Id /= Pragma_Independent then
7014 Set_Is_Volatile (E);
7015 Set_Is_Volatile (Base_Type (E));
7016 Set_Is_Volatile (Underlying_Type (E));
7018 Set_Treat_As_Volatile (E);
7019 Set_Treat_As_Volatile (Underlying_Type (E));
7020 end if;
7022 elsif Nkind (Decl) = N_Object_Declaration
7023 or else (Nkind (Decl) = N_Component_Declaration
7024 and then Original_Record_Component (E) = E)
7025 then
7026 if Rep_Item_Too_Late (E, N) then
7027 return;
7028 end if;
7030 if Prag_Id = Pragma_Atomic
7031 or else
7032 Prag_Id = Pragma_Shared
7033 or else
7034 Prag_Id = Pragma_Volatile_Full_Access
7035 then
7036 if Prag_Id = Pragma_Volatile_Full_Access then
7037 Set_Is_Volatile_Full_Access (E);
7038 else
7039 Set_Is_Atomic (E);
7040 end if;
7042 -- If the object declaration has an explicit initialization, a
7043 -- temporary may have to be created to hold the expression, to
7044 -- ensure that access to the object remain atomic.
7046 if Nkind (Parent (E)) = N_Object_Declaration
7047 and then Present (Expression (Parent (E)))
7048 then
7049 Set_Has_Delayed_Freeze (E);
7050 end if;
7051 end if;
7053 -- Atomic/Shared/Volatile_Full_Access imply Independent
7055 if Prag_Id /= Pragma_Volatile then
7056 Set_Is_Independent (E);
7058 if Prag_Id = Pragma_Independent then
7059 Record_Independence_Check (N, E);
7060 end if;
7061 end if;
7063 -- Atomic/Shared/Volatile_Full_Access imply Volatile
7065 if Prag_Id /= Pragma_Independent then
7066 Set_Is_Volatile (E);
7067 Set_Treat_As_Volatile (E);
7068 end if;
7070 else
7071 Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
7072 end if;
7074 -- The following check is only relevant when SPARK_Mode is on as
7075 -- this is not a standard Ada legality rule. Pragma Volatile can
7076 -- only apply to a full type declaration or an object declaration
7077 -- (SPARK RM 7.1.3(2)). Original_Node is necessary to account for
7078 -- untagged derived types that are rewritten as subtypes of their
7079 -- respective root types.
7081 if SPARK_Mode = On
7082 and then Prag_Id = Pragma_Volatile
7083 and then
7084 not Nkind_In (Original_Node (Decl), N_Full_Type_Declaration,
7085 N_Object_Declaration)
7086 then
7087 Error_Pragma_Arg
7088 ("argument of pragma % must denote a full type or object "
7089 & "declaration", Arg1);
7090 end if;
7091 end Process_Atomic_Independent_Shared_Volatile;
7093 -------------------------------------------
7094 -- Process_Compile_Time_Warning_Or_Error --
7095 -------------------------------------------
7097 procedure Process_Compile_Time_Warning_Or_Error is
7098 Validation_Needed : Boolean := False;
7100 function Check_Node (N : Node_Id) return Traverse_Result;
7101 -- Tree visitor that checks if N is an attribute reference that can
7102 -- be statically computed by the back end. Validation_Needed is set
7103 -- to True if found.
7105 ----------------
7106 -- Check_Node --
7107 ----------------
7109 function Check_Node (N : Node_Id) return Traverse_Result is
7110 begin
7111 if Nkind (N) = N_Attribute_Reference
7112 and then Is_Entity_Name (Prefix (N))
7113 then
7114 declare
7115 Attr_Id : constant Attribute_Id :=
7116 Get_Attribute_Id (Attribute_Name (N));
7117 begin
7118 if Attr_Id = Attribute_Alignment
7119 or else Attr_Id = Attribute_Size
7120 then
7121 Validation_Needed := True;
7122 end if;
7123 end;
7124 end if;
7126 return OK;
7127 end Check_Node;
7129 procedure Check_Expression is new Traverse_Proc (Check_Node);
7131 -- Local variables
7133 Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
7135 -- Start of processing for Process_Compile_Time_Warning_Or_Error
7137 begin
7138 Check_Arg_Count (2);
7139 Check_No_Identifiers;
7140 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
7141 Analyze_And_Resolve (Arg1x, Standard_Boolean);
7143 if Compile_Time_Known_Value (Arg1x) then
7144 Process_Compile_Time_Warning_Or_Error (N, Sloc (Arg1));
7146 -- Register the expression for its validation after the back end has
7147 -- been called if it has occurrences of attributes Size or Alignment
7148 -- (because they may be statically computed by the back end and hence
7149 -- the whole expression needs to be reevaluated).
7151 else
7152 Check_Expression (Arg1x);
7154 if Validation_Needed then
7155 Sem_Ch13.Validate_Compile_Time_Warning_Error (N);
7156 end if;
7157 end if;
7158 end Process_Compile_Time_Warning_Or_Error;
7160 ------------------------
7161 -- Process_Convention --
7162 ------------------------
7164 procedure Process_Convention
7165 (C : out Convention_Id;
7166 Ent : out Entity_Id)
7168 Cname : Name_Id;
7170 procedure Diagnose_Multiple_Pragmas (S : Entity_Id);
7171 -- Called if we have more than one Export/Import/Convention pragma.
7172 -- This is generally illegal, but we have a special case of allowing
7173 -- Import and Interface to coexist if they specify the convention in
7174 -- a consistent manner. We are allowed to do this, since Interface is
7175 -- an implementation defined pragma, and we choose to do it since we
7176 -- know Rational allows this combination. S is the entity id of the
7177 -- subprogram in question. This procedure also sets the special flag
7178 -- Import_Interface_Present in both pragmas in the case where we do
7179 -- have matching Import and Interface pragmas.
7181 procedure Set_Convention_From_Pragma (E : Entity_Id);
7182 -- Set convention in entity E, and also flag that the entity has a
7183 -- convention pragma. If entity is for a private or incomplete type,
7184 -- also set convention and flag on underlying type. This procedure
7185 -- also deals with the special case of C_Pass_By_Copy convention,
7186 -- and error checks for inappropriate convention specification.
7188 -------------------------------
7189 -- Diagnose_Multiple_Pragmas --
7190 -------------------------------
7192 procedure Diagnose_Multiple_Pragmas (S : Entity_Id) is
7193 Pdec : constant Node_Id := Declaration_Node (S);
7194 Decl : Node_Id;
7195 Err : Boolean;
7197 function Same_Convention (Decl : Node_Id) return Boolean;
7198 -- Decl is a pragma node. This function returns True if this
7199 -- pragma has a first argument that is an identifier with a
7200 -- Chars field corresponding to the Convention_Id C.
7202 function Same_Name (Decl : Node_Id) return Boolean;
7203 -- Decl is a pragma node. This function returns True if this
7204 -- pragma has a second argument that is an identifier with a
7205 -- Chars field that matches the Chars of the current subprogram.
7207 ---------------------
7208 -- Same_Convention --
7209 ---------------------
7211 function Same_Convention (Decl : Node_Id) return Boolean is
7212 Arg1 : constant Node_Id :=
7213 First (Pragma_Argument_Associations (Decl));
7215 begin
7216 if Present (Arg1) then
7217 declare
7218 Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
7219 begin
7220 if Nkind (Arg) = N_Identifier
7221 and then Is_Convention_Name (Chars (Arg))
7222 and then Get_Convention_Id (Chars (Arg)) = C
7223 then
7224 return True;
7225 end if;
7226 end;
7227 end if;
7229 return False;
7230 end Same_Convention;
7232 ---------------
7233 -- Same_Name --
7234 ---------------
7236 function Same_Name (Decl : Node_Id) return Boolean is
7237 Arg1 : constant Node_Id :=
7238 First (Pragma_Argument_Associations (Decl));
7239 Arg2 : Node_Id;
7241 begin
7242 if No (Arg1) then
7243 return False;
7244 end if;
7246 Arg2 := Next (Arg1);
7248 if No (Arg2) then
7249 return False;
7250 end if;
7252 declare
7253 Arg : constant Node_Id := Get_Pragma_Arg (Arg2);
7254 begin
7255 if Nkind (Arg) = N_Identifier
7256 and then Chars (Arg) = Chars (S)
7257 then
7258 return True;
7259 end if;
7260 end;
7262 return False;
7263 end Same_Name;
7265 -- Start of processing for Diagnose_Multiple_Pragmas
7267 begin
7268 Err := True;
7270 -- Definitely give message if we have Convention/Export here
7272 if Prag_Id = Pragma_Convention or else Prag_Id = Pragma_Export then
7273 null;
7275 -- If we have an Import or Export, scan back from pragma to
7276 -- find any previous pragma applying to the same procedure.
7277 -- The scan will be terminated by the start of the list, or
7278 -- hitting the subprogram declaration. This won't allow one
7279 -- pragma to appear in the public part and one in the private
7280 -- part, but that seems very unlikely in practice.
7282 else
7283 Decl := Prev (N);
7284 while Present (Decl) and then Decl /= Pdec loop
7286 -- Look for pragma with same name as us
7288 if Nkind (Decl) = N_Pragma
7289 and then Same_Name (Decl)
7290 then
7291 -- Give error if same as our pragma or Export/Convention
7293 if Nam_In (Pragma_Name_Unmapped (Decl),
7294 Name_Export,
7295 Name_Convention,
7296 Pragma_Name_Unmapped (N))
7297 then
7298 exit;
7300 -- Case of Import/Interface or the other way round
7302 elsif Nam_In (Pragma_Name_Unmapped (Decl),
7303 Name_Interface, Name_Import)
7304 then
7305 -- Here we know that we have Import and Interface. It
7306 -- doesn't matter which way round they are. See if
7307 -- they specify the same convention. If so, all OK,
7308 -- and set special flags to stop other messages
7310 if Same_Convention (Decl) then
7311 Set_Import_Interface_Present (N);
7312 Set_Import_Interface_Present (Decl);
7313 Err := False;
7315 -- If different conventions, special message
7317 else
7318 Error_Msg_Sloc := Sloc (Decl);
7319 Error_Pragma_Arg
7320 ("convention differs from that given#", Arg1);
7321 return;
7322 end if;
7323 end if;
7324 end if;
7326 Next (Decl);
7327 end loop;
7328 end if;
7330 -- Give message if needed if we fall through those tests
7331 -- except on Relaxed_RM_Semantics where we let go: either this
7332 -- is a case accepted/ignored by other Ada compilers (e.g.
7333 -- a mix of Convention and Import), or another error will be
7334 -- generated later (e.g. using both Import and Export).
7336 if Err and not Relaxed_RM_Semantics then
7337 Error_Pragma_Arg
7338 ("at most one Convention/Export/Import pragma is allowed",
7339 Arg2);
7340 end if;
7341 end Diagnose_Multiple_Pragmas;
7343 --------------------------------
7344 -- Set_Convention_From_Pragma --
7345 --------------------------------
7347 procedure Set_Convention_From_Pragma (E : Entity_Id) is
7348 begin
7349 -- Ada 2005 (AI-430): Check invalid attempt to change convention
7350 -- for an overridden dispatching operation. Technically this is
7351 -- an amendment and should only be done in Ada 2005 mode. However,
7352 -- this is clearly a mistake, since the problem that is addressed
7353 -- by this AI is that there is a clear gap in the RM.
7355 if Is_Dispatching_Operation (E)
7356 and then Present (Overridden_Operation (E))
7357 and then C /= Convention (Overridden_Operation (E))
7358 then
7359 Error_Pragma_Arg
7360 ("cannot change convention for overridden dispatching "
7361 & "operation", Arg1);
7362 end if;
7364 -- Special checks for Convention_Stdcall
7366 if C = Convention_Stdcall then
7368 -- A dispatching call is not allowed. A dispatching subprogram
7369 -- cannot be used to interface to the Win32 API, so in fact
7370 -- this check does not impose any effective restriction.
7372 if Is_Dispatching_Operation (E) then
7373 Error_Msg_Sloc := Sloc (E);
7375 -- Note: make this unconditional so that if there is more
7376 -- than one call to which the pragma applies, we get a
7377 -- message for each call. Also don't use Error_Pragma,
7378 -- so that we get multiple messages.
7380 Error_Msg_N
7381 ("dispatching subprogram# cannot use Stdcall convention!",
7382 Arg1);
7384 -- Several allowed cases
7386 elsif Is_Subprogram_Or_Generic_Subprogram (E)
7388 -- A variable is OK
7390 or else Ekind (E) = E_Variable
7392 -- A component as well. The entity does not have its Ekind
7393 -- set until the enclosing record declaration is fully
7394 -- analyzed.
7396 or else Nkind (Parent (E)) = N_Component_Declaration
7398 -- An access to subprogram is also allowed
7400 or else
7401 (Is_Access_Type (E)
7402 and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
7404 -- Allow internal call to set convention of subprogram type
7406 or else Ekind (E) = E_Subprogram_Type
7407 then
7408 null;
7410 else
7411 Error_Pragma_Arg
7412 ("second argument of pragma% must be subprogram (type)",
7413 Arg2);
7414 end if;
7415 end if;
7417 -- Set the convention
7419 Set_Convention (E, C);
7420 Set_Has_Convention_Pragma (E);
7422 -- For the case of a record base type, also set the convention of
7423 -- any anonymous access types declared in the record which do not
7424 -- currently have a specified convention.
7426 if Is_Record_Type (E) and then Is_Base_Type (E) then
7427 declare
7428 Comp : Node_Id;
7430 begin
7431 Comp := First_Component (E);
7432 while Present (Comp) loop
7433 if Present (Etype (Comp))
7434 and then Ekind_In (Etype (Comp),
7435 E_Anonymous_Access_Type,
7436 E_Anonymous_Access_Subprogram_Type)
7437 and then not Has_Convention_Pragma (Comp)
7438 then
7439 Set_Convention (Comp, C);
7440 end if;
7442 Next_Component (Comp);
7443 end loop;
7444 end;
7445 end if;
7447 -- Deal with incomplete/private type case, where underlying type
7448 -- is available, so set convention of that underlying type.
7450 if Is_Incomplete_Or_Private_Type (E)
7451 and then Present (Underlying_Type (E))
7452 then
7453 Set_Convention (Underlying_Type (E), C);
7454 Set_Has_Convention_Pragma (Underlying_Type (E), True);
7455 end if;
7457 -- A class-wide type should inherit the convention of the specific
7458 -- root type (although this isn't specified clearly by the RM).
7460 if Is_Type (E) and then Present (Class_Wide_Type (E)) then
7461 Set_Convention (Class_Wide_Type (E), C);
7462 end if;
7464 -- If the entity is a record type, then check for special case of
7465 -- C_Pass_By_Copy, which is treated the same as C except that the
7466 -- special record flag is set. This convention is only permitted
7467 -- on record types (see AI95-00131).
7469 if Cname = Name_C_Pass_By_Copy then
7470 if Is_Record_Type (E) then
7471 Set_C_Pass_By_Copy (Base_Type (E));
7472 elsif Is_Incomplete_Or_Private_Type (E)
7473 and then Is_Record_Type (Underlying_Type (E))
7474 then
7475 Set_C_Pass_By_Copy (Base_Type (Underlying_Type (E)));
7476 else
7477 Error_Pragma_Arg
7478 ("C_Pass_By_Copy convention allowed only for record type",
7479 Arg2);
7480 end if;
7481 end if;
7483 -- If the entity is a derived boolean type, check for the special
7484 -- case of convention C, C++, or Fortran, where we consider any
7485 -- nonzero value to represent true.
7487 if Is_Discrete_Type (E)
7488 and then Root_Type (Etype (E)) = Standard_Boolean
7489 and then
7490 (C = Convention_C
7491 or else
7492 C = Convention_CPP
7493 or else
7494 C = Convention_Fortran)
7495 then
7496 Set_Nonzero_Is_True (Base_Type (E));
7497 end if;
7498 end Set_Convention_From_Pragma;
7500 -- Local variables
7502 Comp_Unit : Unit_Number_Type;
7503 E : Entity_Id;
7504 E1 : Entity_Id;
7505 Id : Node_Id;
7507 -- Start of processing for Process_Convention
7509 begin
7510 Check_At_Least_N_Arguments (2);
7511 Check_Optional_Identifier (Arg1, Name_Convention);
7512 Check_Arg_Is_Identifier (Arg1);
7513 Cname := Chars (Get_Pragma_Arg (Arg1));
7515 -- C_Pass_By_Copy is treated as a synonym for convention C (this is
7516 -- tested again below to set the critical flag).
7518 if Cname = Name_C_Pass_By_Copy then
7519 C := Convention_C;
7521 -- Otherwise we must have something in the standard convention list
7523 elsif Is_Convention_Name (Cname) then
7524 C := Get_Convention_Id (Chars (Get_Pragma_Arg (Arg1)));
7526 -- Otherwise warn on unrecognized convention
7528 else
7529 if Warn_On_Export_Import then
7530 Error_Msg_N
7531 ("??unrecognized convention name, C assumed",
7532 Get_Pragma_Arg (Arg1));
7533 end if;
7535 C := Convention_C;
7536 end if;
7538 Check_Optional_Identifier (Arg2, Name_Entity);
7539 Check_Arg_Is_Local_Name (Arg2);
7541 Id := Get_Pragma_Arg (Arg2);
7542 Analyze (Id);
7544 if not Is_Entity_Name (Id) then
7545 Error_Pragma_Arg ("entity name required", Arg2);
7546 end if;
7548 E := Entity (Id);
7550 -- Set entity to return
7552 Ent := E;
7554 -- Ada_Pass_By_Copy special checking
7556 if C = Convention_Ada_Pass_By_Copy then
7557 if not Is_First_Subtype (E) then
7558 Error_Pragma_Arg
7559 ("convention `Ada_Pass_By_Copy` only allowed for types",
7560 Arg2);
7561 end if;
7563 if Is_By_Reference_Type (E) then
7564 Error_Pragma_Arg
7565 ("convention `Ada_Pass_By_Copy` not allowed for by-reference "
7566 & "type", Arg1);
7567 end if;
7569 -- Ada_Pass_By_Reference special checking
7571 elsif C = Convention_Ada_Pass_By_Reference then
7572 if not Is_First_Subtype (E) then
7573 Error_Pragma_Arg
7574 ("convention `Ada_Pass_By_Reference` only allowed for types",
7575 Arg2);
7576 end if;
7578 if Is_By_Copy_Type (E) then
7579 Error_Pragma_Arg
7580 ("convention `Ada_Pass_By_Reference` not allowed for by-copy "
7581 & "type", Arg1);
7582 end if;
7583 end if;
7585 -- Go to renamed subprogram if present, since convention applies to
7586 -- the actual renamed entity, not to the renaming entity. If the
7587 -- subprogram is inherited, go to parent subprogram.
7589 if Is_Subprogram (E)
7590 and then Present (Alias (E))
7591 then
7592 if Nkind (Parent (Declaration_Node (E))) =
7593 N_Subprogram_Renaming_Declaration
7594 then
7595 if Scope (E) /= Scope (Alias (E)) then
7596 Error_Pragma_Ref
7597 ("cannot apply pragma% to non-local entity&#", E);
7598 end if;
7600 E := Alias (E);
7602 elsif Nkind_In (Parent (E), N_Full_Type_Declaration,
7603 N_Private_Extension_Declaration)
7604 and then Scope (E) = Scope (Alias (E))
7605 then
7606 E := Alias (E);
7608 -- Return the parent subprogram the entity was inherited from
7610 Ent := E;
7611 end if;
7612 end if;
7614 -- Check that we are not applying this to a specless body. Relax this
7615 -- check if Relaxed_RM_Semantics to accommodate other Ada compilers.
7617 if Is_Subprogram (E)
7618 and then Nkind (Parent (Declaration_Node (E))) = N_Subprogram_Body
7619 and then not Relaxed_RM_Semantics
7620 then
7621 Error_Pragma
7622 ("pragma% requires separate spec and must come before body");
7623 end if;
7625 -- Check that we are not applying this to a named constant
7627 if Ekind_In (E, E_Named_Integer, E_Named_Real) then
7628 Error_Msg_Name_1 := Pname;
7629 Error_Msg_N
7630 ("cannot apply pragma% to named constant!",
7631 Get_Pragma_Arg (Arg2));
7632 Error_Pragma_Arg
7633 ("\supply appropriate type for&!", Arg2);
7634 end if;
7636 if Ekind (E) = E_Enumeration_Literal then
7637 Error_Pragma ("enumeration literal not allowed for pragma%");
7638 end if;
7640 -- Check for rep item appearing too early or too late
7642 if Etype (E) = Any_Type
7643 or else Rep_Item_Too_Early (E, N)
7644 then
7645 raise Pragma_Exit;
7647 elsif Present (Underlying_Type (E)) then
7648 E := Underlying_Type (E);
7649 end if;
7651 if Rep_Item_Too_Late (E, N) then
7652 raise Pragma_Exit;
7653 end if;
7655 if Has_Convention_Pragma (E) then
7656 Diagnose_Multiple_Pragmas (E);
7658 elsif Convention (E) = Convention_Protected
7659 or else Ekind (Scope (E)) = E_Protected_Type
7660 then
7661 Error_Pragma_Arg
7662 ("a protected operation cannot be given a different convention",
7663 Arg2);
7664 end if;
7666 -- For Intrinsic, a subprogram is required
7668 if C = Convention_Intrinsic
7669 and then not Is_Subprogram_Or_Generic_Subprogram (E)
7670 then
7671 -- Accept Intrinsic Export on types if Relaxed_RM_Semantics
7673 if not (Is_Type (E) and then Relaxed_RM_Semantics) then
7674 Error_Pragma_Arg
7675 ("second argument of pragma% must be a subprogram", Arg2);
7676 end if;
7677 end if;
7679 -- Deal with non-subprogram cases
7681 if not Is_Subprogram_Or_Generic_Subprogram (E) then
7682 Set_Convention_From_Pragma (E);
7684 if Is_Type (E) then
7686 -- The pragma must apply to a first subtype, but it can also
7687 -- apply to a generic type in a generic formal part, in which
7688 -- case it will also appear in the corresponding instance.
7690 if Is_Generic_Type (E) or else In_Instance then
7691 null;
7692 else
7693 Check_First_Subtype (Arg2);
7694 end if;
7696 Set_Convention_From_Pragma (Base_Type (E));
7698 -- For access subprograms, we must set the convention on the
7699 -- internally generated directly designated type as well.
7701 if Ekind (E) = E_Access_Subprogram_Type then
7702 Set_Convention_From_Pragma (Directly_Designated_Type (E));
7703 end if;
7704 end if;
7706 -- For the subprogram case, set proper convention for all homonyms
7707 -- in same scope and the same declarative part, i.e. the same
7708 -- compilation unit.
7710 else
7711 Comp_Unit := Get_Source_Unit (E);
7712 Set_Convention_From_Pragma (E);
7714 -- Treat a pragma Import as an implicit body, and pragma import
7715 -- as implicit reference (for navigation in GPS).
7717 if Prag_Id = Pragma_Import then
7718 Generate_Reference (E, Id, 'b');
7720 -- For exported entities we restrict the generation of references
7721 -- to entities exported to foreign languages since entities
7722 -- exported to Ada do not provide further information to GPS and
7723 -- add undesired references to the output of the gnatxref tool.
7725 elsif Prag_Id = Pragma_Export
7726 and then Convention (E) /= Convention_Ada
7727 then
7728 Generate_Reference (E, Id, 'i');
7729 end if;
7731 -- If the pragma comes from an aspect, it only applies to the
7732 -- given entity, not its homonyms.
7734 if From_Aspect_Specification (N) then
7735 if C = Convention_Intrinsic
7736 and then Nkind (Ent) = N_Defining_Operator_Symbol
7737 then
7738 if Is_Fixed_Point_Type (Etype (Ent))
7739 or else Is_Fixed_Point_Type (Etype (First_Entity (Ent)))
7740 or else Is_Fixed_Point_Type (Etype (Last_Entity (Ent)))
7741 then
7742 Error_Msg_N
7743 ("no intrinsic operator available for this fixed-point "
7744 & "operation", N);
7745 Error_Msg_N
7746 ("\use expression functions with the desired "
7747 & "conversions made explicit", N);
7748 end if;
7749 end if;
7751 return;
7752 end if;
7754 -- Otherwise Loop through the homonyms of the pragma argument's
7755 -- entity, an apply convention to those in the current scope.
7757 E1 := Ent;
7759 loop
7760 E1 := Homonym (E1);
7761 exit when No (E1) or else Scope (E1) /= Current_Scope;
7763 -- Ignore entry for which convention is already set
7765 if Has_Convention_Pragma (E1) then
7766 goto Continue;
7767 end if;
7769 if Is_Subprogram (E1)
7770 and then Nkind (Parent (Declaration_Node (E1))) =
7771 N_Subprogram_Body
7772 and then not Relaxed_RM_Semantics
7773 then
7774 Set_Has_Completion (E); -- to prevent cascaded error
7775 Error_Pragma_Ref
7776 ("pragma% requires separate spec and must come before "
7777 & "body#", E1);
7778 end if;
7780 -- Do not set the pragma on inherited operations or on formal
7781 -- subprograms.
7783 if Comes_From_Source (E1)
7784 and then Comp_Unit = Get_Source_Unit (E1)
7785 and then not Is_Formal_Subprogram (E1)
7786 and then Nkind (Original_Node (Parent (E1))) /=
7787 N_Full_Type_Declaration
7788 then
7789 if Present (Alias (E1))
7790 and then Scope (E1) /= Scope (Alias (E1))
7791 then
7792 Error_Pragma_Ref
7793 ("cannot apply pragma% to non-local entity& declared#",
7794 E1);
7795 end if;
7797 Set_Convention_From_Pragma (E1);
7799 if Prag_Id = Pragma_Import then
7800 Generate_Reference (E1, Id, 'b');
7801 end if;
7802 end if;
7804 <<Continue>>
7805 null;
7806 end loop;
7807 end if;
7808 end Process_Convention;
7810 ----------------------------------------
7811 -- Process_Disable_Enable_Atomic_Sync --
7812 ----------------------------------------
7814 procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id) is
7815 begin
7816 Check_No_Identifiers;
7817 Check_At_Most_N_Arguments (1);
7819 -- Modeled internally as
7820 -- pragma Suppress/Unsuppress (Atomic_Synchronization [,Entity])
7822 Rewrite (N,
7823 Make_Pragma (Loc,
7824 Chars => Nam,
7825 Pragma_Argument_Associations => New_List (
7826 Make_Pragma_Argument_Association (Loc,
7827 Expression =>
7828 Make_Identifier (Loc, Name_Atomic_Synchronization)))));
7830 if Present (Arg1) then
7831 Append_To (Pragma_Argument_Associations (N), New_Copy (Arg1));
7832 end if;
7834 Analyze (N);
7835 end Process_Disable_Enable_Atomic_Sync;
7837 -------------------------------------------------
7838 -- Process_Extended_Import_Export_Internal_Arg --
7839 -------------------------------------------------
7841 procedure Process_Extended_Import_Export_Internal_Arg
7842 (Arg_Internal : Node_Id := Empty)
7844 begin
7845 if No (Arg_Internal) then
7846 Error_Pragma ("Internal parameter required for pragma%");
7847 end if;
7849 if Nkind (Arg_Internal) = N_Identifier then
7850 null;
7852 elsif Nkind (Arg_Internal) = N_Operator_Symbol
7853 and then (Prag_Id = Pragma_Import_Function
7854 or else
7855 Prag_Id = Pragma_Export_Function)
7856 then
7857 null;
7859 else
7860 Error_Pragma_Arg
7861 ("wrong form for Internal parameter for pragma%", Arg_Internal);
7862 end if;
7864 Check_Arg_Is_Local_Name (Arg_Internal);
7865 end Process_Extended_Import_Export_Internal_Arg;
7867 --------------------------------------------------
7868 -- Process_Extended_Import_Export_Object_Pragma --
7869 --------------------------------------------------
7871 procedure Process_Extended_Import_Export_Object_Pragma
7872 (Arg_Internal : Node_Id;
7873 Arg_External : Node_Id;
7874 Arg_Size : Node_Id)
7876 Def_Id : Entity_Id;
7878 begin
7879 Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
7880 Def_Id := Entity (Arg_Internal);
7882 if not Ekind_In (Def_Id, E_Constant, E_Variable) then
7883 Error_Pragma_Arg
7884 ("pragma% must designate an object", Arg_Internal);
7885 end if;
7887 if Has_Rep_Pragma (Def_Id, Name_Common_Object)
7888 or else
7889 Has_Rep_Pragma (Def_Id, Name_Psect_Object)
7890 then
7891 Error_Pragma_Arg
7892 ("previous Common/Psect_Object applies, pragma % not permitted",
7893 Arg_Internal);
7894 end if;
7896 if Rep_Item_Too_Late (Def_Id, N) then
7897 raise Pragma_Exit;
7898 end if;
7900 Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
7902 if Present (Arg_Size) then
7903 Check_Arg_Is_External_Name (Arg_Size);
7904 end if;
7906 -- Export_Object case
7908 if Prag_Id = Pragma_Export_Object then
7909 if not Is_Library_Level_Entity (Def_Id) then
7910 Error_Pragma_Arg
7911 ("argument for pragma% must be library level entity",
7912 Arg_Internal);
7913 end if;
7915 if Ekind (Current_Scope) = E_Generic_Package then
7916 Error_Pragma ("pragma& cannot appear in a generic unit");
7917 end if;
7919 if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
7920 Error_Pragma_Arg
7921 ("exported object must have compile time known size",
7922 Arg_Internal);
7923 end if;
7925 if Warn_On_Export_Import and then Is_Exported (Def_Id) then
7926 Error_Msg_N ("??duplicate Export_Object pragma", N);
7927 else
7928 Set_Exported (Def_Id, Arg_Internal);
7929 end if;
7931 -- Import_Object case
7933 else
7934 if Is_Concurrent_Type (Etype (Def_Id)) then
7935 Error_Pragma_Arg
7936 ("cannot use pragma% for task/protected object",
7937 Arg_Internal);
7938 end if;
7940 if Ekind (Def_Id) = E_Constant then
7941 Error_Pragma_Arg
7942 ("cannot import a constant", Arg_Internal);
7943 end if;
7945 if Warn_On_Export_Import
7946 and then Has_Discriminants (Etype (Def_Id))
7947 then
7948 Error_Msg_N
7949 ("imported value must be initialized??", Arg_Internal);
7950 end if;
7952 if Warn_On_Export_Import
7953 and then Is_Access_Type (Etype (Def_Id))
7954 then
7955 Error_Pragma_Arg
7956 ("cannot import object of an access type??", Arg_Internal);
7957 end if;
7959 if Warn_On_Export_Import
7960 and then Is_Imported (Def_Id)
7961 then
7962 Error_Msg_N ("??duplicate Import_Object pragma", N);
7964 -- Check for explicit initialization present. Note that an
7965 -- initialization generated by the code generator, e.g. for an
7966 -- access type, does not count here.
7968 elsif Present (Expression (Parent (Def_Id)))
7969 and then
7970 Comes_From_Source
7971 (Original_Node (Expression (Parent (Def_Id))))
7972 then
7973 Error_Msg_Sloc := Sloc (Def_Id);
7974 Error_Pragma_Arg
7975 ("imported entities cannot be initialized (RM B.1(24))",
7976 "\no initialization allowed for & declared#", Arg1);
7977 else
7978 Set_Imported (Def_Id);
7979 Note_Possible_Modification (Arg_Internal, Sure => False);
7980 end if;
7981 end if;
7982 end Process_Extended_Import_Export_Object_Pragma;
7984 ------------------------------------------------------
7985 -- Process_Extended_Import_Export_Subprogram_Pragma --
7986 ------------------------------------------------------
7988 procedure Process_Extended_Import_Export_Subprogram_Pragma
7989 (Arg_Internal : Node_Id;
7990 Arg_External : Node_Id;
7991 Arg_Parameter_Types : Node_Id;
7992 Arg_Result_Type : Node_Id := Empty;
7993 Arg_Mechanism : Node_Id;
7994 Arg_Result_Mechanism : Node_Id := Empty)
7996 Ent : Entity_Id;
7997 Def_Id : Entity_Id;
7998 Hom_Id : Entity_Id;
7999 Formal : Entity_Id;
8000 Ambiguous : Boolean;
8001 Match : Boolean;
8003 function Same_Base_Type
8004 (Ptype : Node_Id;
8005 Formal : Entity_Id) return Boolean;
8006 -- Determines if Ptype references the type of Formal. Note that only
8007 -- the base types need to match according to the spec. Ptype here is
8008 -- the argument from the pragma, which is either a type name, or an
8009 -- access attribute.
8011 --------------------
8012 -- Same_Base_Type --
8013 --------------------
8015 function Same_Base_Type
8016 (Ptype : Node_Id;
8017 Formal : Entity_Id) return Boolean
8019 Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
8020 Pref : Node_Id;
8022 begin
8023 -- Case where pragma argument is typ'Access
8025 if Nkind (Ptype) = N_Attribute_Reference
8026 and then Attribute_Name (Ptype) = Name_Access
8027 then
8028 Pref := Prefix (Ptype);
8029 Find_Type (Pref);
8031 if not Is_Entity_Name (Pref)
8032 or else Entity (Pref) = Any_Type
8033 then
8034 raise Pragma_Exit;
8035 end if;
8037 -- We have a match if the corresponding argument is of an
8038 -- anonymous access type, and its designated type matches the
8039 -- type of the prefix of the access attribute
8041 return Ekind (Ftyp) = E_Anonymous_Access_Type
8042 and then Base_Type (Entity (Pref)) =
8043 Base_Type (Etype (Designated_Type (Ftyp)));
8045 -- Case where pragma argument is a type name
8047 else
8048 Find_Type (Ptype);
8050 if not Is_Entity_Name (Ptype)
8051 or else Entity (Ptype) = Any_Type
8052 then
8053 raise Pragma_Exit;
8054 end if;
8056 -- We have a match if the corresponding argument is of the type
8057 -- given in the pragma (comparing base types)
8059 return Base_Type (Entity (Ptype)) = Ftyp;
8060 end if;
8061 end Same_Base_Type;
8063 -- Start of processing for
8064 -- Process_Extended_Import_Export_Subprogram_Pragma
8066 begin
8067 Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
8068 Ent := Empty;
8069 Ambiguous := False;
8071 -- Loop through homonyms (overloadings) of the entity
8073 Hom_Id := Entity (Arg_Internal);
8074 while Present (Hom_Id) loop
8075 Def_Id := Get_Base_Subprogram (Hom_Id);
8077 -- We need a subprogram in the current scope
8079 if not Is_Subprogram (Def_Id)
8080 or else Scope (Def_Id) /= Current_Scope
8081 then
8082 null;
8084 else
8085 Match := True;
8087 -- Pragma cannot apply to subprogram body
8089 if Is_Subprogram (Def_Id)
8090 and then Nkind (Parent (Declaration_Node (Def_Id))) =
8091 N_Subprogram_Body
8092 then
8093 Error_Pragma
8094 ("pragma% requires separate spec and must come before "
8095 & "body");
8096 end if;
8098 -- Test result type if given, note that the result type
8099 -- parameter can only be present for the function cases.
8101 if Present (Arg_Result_Type)
8102 and then not Same_Base_Type (Arg_Result_Type, Def_Id)
8103 then
8104 Match := False;
8106 elsif Etype (Def_Id) /= Standard_Void_Type
8107 and then Nam_In (Pname, Name_Export_Procedure,
8108 Name_Import_Procedure)
8109 then
8110 Match := False;
8112 -- Test parameter types if given. Note that this parameter has
8113 -- not been analyzed (and must not be, since it is semantic
8114 -- nonsense), so we get it as the parser left it.
8116 elsif Present (Arg_Parameter_Types) then
8117 Check_Matching_Types : declare
8118 Formal : Entity_Id;
8119 Ptype : Node_Id;
8121 begin
8122 Formal := First_Formal (Def_Id);
8124 if Nkind (Arg_Parameter_Types) = N_Null then
8125 if Present (Formal) then
8126 Match := False;
8127 end if;
8129 -- A list of one type, e.g. (List) is parsed as a
8130 -- parenthesized expression.
8132 elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
8133 and then Paren_Count (Arg_Parameter_Types) = 1
8134 then
8135 if No (Formal)
8136 or else Present (Next_Formal (Formal))
8137 then
8138 Match := False;
8139 else
8140 Match :=
8141 Same_Base_Type (Arg_Parameter_Types, Formal);
8142 end if;
8144 -- A list of more than one type is parsed as a aggregate
8146 elsif Nkind (Arg_Parameter_Types) = N_Aggregate
8147 and then Paren_Count (Arg_Parameter_Types) = 0
8148 then
8149 Ptype := First (Expressions (Arg_Parameter_Types));
8150 while Present (Ptype) or else Present (Formal) loop
8151 if No (Ptype)
8152 or else No (Formal)
8153 or else not Same_Base_Type (Ptype, Formal)
8154 then
8155 Match := False;
8156 exit;
8157 else
8158 Next_Formal (Formal);
8159 Next (Ptype);
8160 end if;
8161 end loop;
8163 -- Anything else is of the wrong form
8165 else
8166 Error_Pragma_Arg
8167 ("wrong form for Parameter_Types parameter",
8168 Arg_Parameter_Types);
8169 end if;
8170 end Check_Matching_Types;
8171 end if;
8173 -- Match is now False if the entry we found did not match
8174 -- either a supplied Parameter_Types or Result_Types argument
8176 if Match then
8177 if No (Ent) then
8178 Ent := Def_Id;
8180 -- Ambiguous case, the flag Ambiguous shows if we already
8181 -- detected this and output the initial messages.
8183 else
8184 if not Ambiguous then
8185 Ambiguous := True;
8186 Error_Msg_Name_1 := Pname;
8187 Error_Msg_N
8188 ("pragma% does not uniquely identify subprogram!",
8190 Error_Msg_Sloc := Sloc (Ent);
8191 Error_Msg_N ("matching subprogram #!", N);
8192 Ent := Empty;
8193 end if;
8195 Error_Msg_Sloc := Sloc (Def_Id);
8196 Error_Msg_N ("matching subprogram #!", N);
8197 end if;
8198 end if;
8199 end if;
8201 Hom_Id := Homonym (Hom_Id);
8202 end loop;
8204 -- See if we found an entry
8206 if No (Ent) then
8207 if not Ambiguous then
8208 if Is_Generic_Subprogram (Entity (Arg_Internal)) then
8209 Error_Pragma
8210 ("pragma% cannot be given for generic subprogram");
8211 else
8212 Error_Pragma
8213 ("pragma% does not identify local subprogram");
8214 end if;
8215 end if;
8217 return;
8218 end if;
8220 -- Import pragmas must be for imported entities
8222 if Prag_Id = Pragma_Import_Function
8223 or else
8224 Prag_Id = Pragma_Import_Procedure
8225 or else
8226 Prag_Id = Pragma_Import_Valued_Procedure
8227 then
8228 if not Is_Imported (Ent) then
8229 Error_Pragma
8230 ("pragma Import or Interface must precede pragma%");
8231 end if;
8233 -- Here we have the Export case which can set the entity as exported
8235 -- But does not do so if the specified external name is null, since
8236 -- that is taken as a signal in DEC Ada 83 (with which we want to be
8237 -- compatible) to request no external name.
8239 elsif Nkind (Arg_External) = N_String_Literal
8240 and then String_Length (Strval (Arg_External)) = 0
8241 then
8242 null;
8244 -- In all other cases, set entity as exported
8246 else
8247 Set_Exported (Ent, Arg_Internal);
8248 end if;
8250 -- Special processing for Valued_Procedure cases
8252 if Prag_Id = Pragma_Import_Valued_Procedure
8253 or else
8254 Prag_Id = Pragma_Export_Valued_Procedure
8255 then
8256 Formal := First_Formal (Ent);
8258 if No (Formal) then
8259 Error_Pragma ("at least one parameter required for pragma%");
8261 elsif Ekind (Formal) /= E_Out_Parameter then
8262 Error_Pragma ("first parameter must have mode out for pragma%");
8264 else
8265 Set_Is_Valued_Procedure (Ent);
8266 end if;
8267 end if;
8269 Set_Extended_Import_Export_External_Name (Ent, Arg_External);
8271 -- Process Result_Mechanism argument if present. We have already
8272 -- checked that this is only allowed for the function case.
8274 if Present (Arg_Result_Mechanism) then
8275 Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
8276 end if;
8278 -- Process Mechanism parameter if present. Note that this parameter
8279 -- is not analyzed, and must not be analyzed since it is semantic
8280 -- nonsense, so we get it in exactly as the parser left it.
8282 if Present (Arg_Mechanism) then
8283 declare
8284 Formal : Entity_Id;
8285 Massoc : Node_Id;
8286 Mname : Node_Id;
8287 Choice : Node_Id;
8289 begin
8290 -- A single mechanism association without a formal parameter
8291 -- name is parsed as a parenthesized expression. All other
8292 -- cases are parsed as aggregates, so we rewrite the single
8293 -- parameter case as an aggregate for consistency.
8295 if Nkind (Arg_Mechanism) /= N_Aggregate
8296 and then Paren_Count (Arg_Mechanism) = 1
8297 then
8298 Rewrite (Arg_Mechanism,
8299 Make_Aggregate (Sloc (Arg_Mechanism),
8300 Expressions => New_List (
8301 Relocate_Node (Arg_Mechanism))));
8302 end if;
8304 -- Case of only mechanism name given, applies to all formals
8306 if Nkind (Arg_Mechanism) /= N_Aggregate then
8307 Formal := First_Formal (Ent);
8308 while Present (Formal) loop
8309 Set_Mechanism_Value (Formal, Arg_Mechanism);
8310 Next_Formal (Formal);
8311 end loop;
8313 -- Case of list of mechanism associations given
8315 else
8316 if Null_Record_Present (Arg_Mechanism) then
8317 Error_Pragma_Arg
8318 ("inappropriate form for Mechanism parameter",
8319 Arg_Mechanism);
8320 end if;
8322 -- Deal with positional ones first
8324 Formal := First_Formal (Ent);
8326 if Present (Expressions (Arg_Mechanism)) then
8327 Mname := First (Expressions (Arg_Mechanism));
8328 while Present (Mname) loop
8329 if No (Formal) then
8330 Error_Pragma_Arg
8331 ("too many mechanism associations", Mname);
8332 end if;
8334 Set_Mechanism_Value (Formal, Mname);
8335 Next_Formal (Formal);
8336 Next (Mname);
8337 end loop;
8338 end if;
8340 -- Deal with named entries
8342 if Present (Component_Associations (Arg_Mechanism)) then
8343 Massoc := First (Component_Associations (Arg_Mechanism));
8344 while Present (Massoc) loop
8345 Choice := First (Choices (Massoc));
8347 if Nkind (Choice) /= N_Identifier
8348 or else Present (Next (Choice))
8349 then
8350 Error_Pragma_Arg
8351 ("incorrect form for mechanism association",
8352 Massoc);
8353 end if;
8355 Formal := First_Formal (Ent);
8356 loop
8357 if No (Formal) then
8358 Error_Pragma_Arg
8359 ("parameter name & not present", Choice);
8360 end if;
8362 if Chars (Choice) = Chars (Formal) then
8363 Set_Mechanism_Value
8364 (Formal, Expression (Massoc));
8366 -- Set entity on identifier (needed by ASIS)
8368 Set_Entity (Choice, Formal);
8370 exit;
8371 end if;
8373 Next_Formal (Formal);
8374 end loop;
8376 Next (Massoc);
8377 end loop;
8378 end if;
8379 end if;
8380 end;
8381 end if;
8382 end Process_Extended_Import_Export_Subprogram_Pragma;
8384 --------------------------
8385 -- Process_Generic_List --
8386 --------------------------
8388 procedure Process_Generic_List is
8389 Arg : Node_Id;
8390 Exp : Node_Id;
8392 begin
8393 Check_No_Identifiers;
8394 Check_At_Least_N_Arguments (1);
8396 -- Check all arguments are names of generic units or instances
8398 Arg := Arg1;
8399 while Present (Arg) loop
8400 Exp := Get_Pragma_Arg (Arg);
8401 Analyze (Exp);
8403 if not Is_Entity_Name (Exp)
8404 or else
8405 (not Is_Generic_Instance (Entity (Exp))
8406 and then
8407 not Is_Generic_Unit (Entity (Exp)))
8408 then
8409 Error_Pragma_Arg
8410 ("pragma% argument must be name of generic unit/instance",
8411 Arg);
8412 end if;
8414 Next (Arg);
8415 end loop;
8416 end Process_Generic_List;
8418 ------------------------------------
8419 -- Process_Import_Predefined_Type --
8420 ------------------------------------
8422 procedure Process_Import_Predefined_Type is
8423 Loc : constant Source_Ptr := Sloc (N);
8424 Elmt : Elmt_Id;
8425 Ftyp : Node_Id := Empty;
8426 Decl : Node_Id;
8427 Def : Node_Id;
8428 Nam : Name_Id;
8430 begin
8431 Nam := String_To_Name (Strval (Expression (Arg3)));
8433 Elmt := First_Elmt (Predefined_Float_Types);
8434 while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
8435 Next_Elmt (Elmt);
8436 end loop;
8438 Ftyp := Node (Elmt);
8440 if Present (Ftyp) then
8442 -- Don't build a derived type declaration, because predefined C
8443 -- types have no declaration anywhere, so cannot really be named.
8444 -- Instead build a full type declaration, starting with an
8445 -- appropriate type definition is built
8447 if Is_Floating_Point_Type (Ftyp) then
8448 Def := Make_Floating_Point_Definition (Loc,
8449 Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
8450 Make_Real_Range_Specification (Loc,
8451 Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
8452 Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
8454 -- Should never have a predefined type we cannot handle
8456 else
8457 raise Program_Error;
8458 end if;
8460 -- Build and insert a Full_Type_Declaration, which will be
8461 -- analyzed as soon as this list entry has been analyzed.
8463 Decl := Make_Full_Type_Declaration (Loc,
8464 Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
8465 Type_Definition => Def);
8467 Insert_After (N, Decl);
8468 Mark_Rewrite_Insertion (Decl);
8470 else
8471 Error_Pragma_Arg ("no matching type found for pragma%",
8472 Arg2);
8473 end if;
8474 end Process_Import_Predefined_Type;
8476 ---------------------------------
8477 -- Process_Import_Or_Interface --
8478 ---------------------------------
8480 procedure Process_Import_Or_Interface is
8481 C : Convention_Id;
8482 Def_Id : Entity_Id;
8483 Hom_Id : Entity_Id;
8485 begin
8486 -- In Relaxed_RM_Semantics, support old Ada 83 style:
8487 -- pragma Import (Entity, "external name");
8489 if Relaxed_RM_Semantics
8490 and then Arg_Count = 2
8491 and then Prag_Id = Pragma_Import
8492 and then Nkind (Expression (Arg2)) = N_String_Literal
8493 then
8494 C := Convention_C;
8495 Def_Id := Get_Pragma_Arg (Arg1);
8496 Analyze (Def_Id);
8498 if not Is_Entity_Name (Def_Id) then
8499 Error_Pragma_Arg ("entity name required", Arg1);
8500 end if;
8502 Def_Id := Entity (Def_Id);
8503 Kill_Size_Check_Code (Def_Id);
8504 Note_Possible_Modification (Get_Pragma_Arg (Arg1), Sure => False);
8506 else
8507 Process_Convention (C, Def_Id);
8509 -- A pragma that applies to a Ghost entity becomes Ghost for the
8510 -- purposes of legality checks and removal of ignored Ghost code.
8512 Mark_Ghost_Pragma (N, Def_Id);
8513 Kill_Size_Check_Code (Def_Id);
8514 Note_Possible_Modification (Get_Pragma_Arg (Arg2), Sure => False);
8515 end if;
8517 -- Various error checks
8519 if Ekind_In (Def_Id, E_Variable, E_Constant) then
8521 -- We do not permit Import to apply to a renaming declaration
8523 if Present (Renamed_Object (Def_Id)) then
8524 Error_Pragma_Arg
8525 ("pragma% not allowed for object renaming", Arg2);
8527 -- User initialization is not allowed for imported object, but
8528 -- the object declaration may contain a default initialization,
8529 -- that will be discarded. Note that an explicit initialization
8530 -- only counts if it comes from source, otherwise it is simply
8531 -- the code generator making an implicit initialization explicit.
8533 elsif Present (Expression (Parent (Def_Id)))
8534 and then Comes_From_Source
8535 (Original_Node (Expression (Parent (Def_Id))))
8536 then
8537 -- Set imported flag to prevent cascaded errors
8539 Set_Is_Imported (Def_Id);
8541 Error_Msg_Sloc := Sloc (Def_Id);
8542 Error_Pragma_Arg
8543 ("no initialization allowed for declaration of& #",
8544 "\imported entities cannot be initialized (RM B.1(24))",
8545 Arg2);
8547 else
8548 -- If the pragma comes from an aspect specification the
8549 -- Is_Imported flag has already been set.
8551 if not From_Aspect_Specification (N) then
8552 Set_Imported (Def_Id);
8553 end if;
8555 Process_Interface_Name (Def_Id, Arg3, Arg4, N);
8557 -- Note that we do not set Is_Public here. That's because we
8558 -- only want to set it if there is no address clause, and we
8559 -- don't know that yet, so we delay that processing till
8560 -- freeze time.
8562 -- pragma Import completes deferred constants
8564 if Ekind (Def_Id) = E_Constant then
8565 Set_Has_Completion (Def_Id);
8566 end if;
8568 -- It is not possible to import a constant of an unconstrained
8569 -- array type (e.g. string) because there is no simple way to
8570 -- write a meaningful subtype for it.
8572 if Is_Array_Type (Etype (Def_Id))
8573 and then not Is_Constrained (Etype (Def_Id))
8574 then
8575 Error_Msg_NE
8576 ("imported constant& must have a constrained subtype",
8577 N, Def_Id);
8578 end if;
8579 end if;
8581 elsif Is_Subprogram_Or_Generic_Subprogram (Def_Id) then
8583 -- If the name is overloaded, pragma applies to all of the denoted
8584 -- entities in the same declarative part, unless the pragma comes
8585 -- from an aspect specification or was generated by the compiler
8586 -- (such as for pragma Provide_Shift_Operators).
8588 Hom_Id := Def_Id;
8589 while Present (Hom_Id) loop
8591 Def_Id := Get_Base_Subprogram (Hom_Id);
8593 -- Ignore inherited subprograms because the pragma will apply
8594 -- to the parent operation, which is the one called.
8596 if Is_Overloadable (Def_Id)
8597 and then Present (Alias (Def_Id))
8598 then
8599 null;
8601 -- If it is not a subprogram, it must be in an outer scope and
8602 -- pragma does not apply.
8604 elsif not Is_Subprogram_Or_Generic_Subprogram (Def_Id) then
8605 null;
8607 -- The pragma does not apply to primitives of interfaces
8609 elsif Is_Dispatching_Operation (Def_Id)
8610 and then Present (Find_Dispatching_Type (Def_Id))
8611 and then Is_Interface (Find_Dispatching_Type (Def_Id))
8612 then
8613 null;
8615 -- Verify that the homonym is in the same declarative part (not
8616 -- just the same scope). If the pragma comes from an aspect
8617 -- specification we know that it is part of the declaration.
8619 elsif Parent (Unit_Declaration_Node (Def_Id)) /= Parent (N)
8620 and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
8621 and then not From_Aspect_Specification (N)
8622 then
8623 exit;
8625 else
8626 -- If the pragma comes from an aspect specification the
8627 -- Is_Imported flag has already been set.
8629 if not From_Aspect_Specification (N) then
8630 Set_Imported (Def_Id);
8631 end if;
8633 -- Reject an Import applied to an abstract subprogram
8635 if Is_Subprogram (Def_Id)
8636 and then Is_Abstract_Subprogram (Def_Id)
8637 then
8638 Error_Msg_Sloc := Sloc (Def_Id);
8639 Error_Msg_NE
8640 ("cannot import abstract subprogram& declared#",
8641 Arg2, Def_Id);
8642 end if;
8644 -- Special processing for Convention_Intrinsic
8646 if C = Convention_Intrinsic then
8648 -- Link_Name argument not allowed for intrinsic
8650 Check_No_Link_Name;
8652 Set_Is_Intrinsic_Subprogram (Def_Id);
8654 -- If no external name is present, then check that this
8655 -- is a valid intrinsic subprogram. If an external name
8656 -- is present, then this is handled by the back end.
8658 if No (Arg3) then
8659 Check_Intrinsic_Subprogram
8660 (Def_Id, Get_Pragma_Arg (Arg2));
8661 end if;
8662 end if;
8664 -- Verify that the subprogram does not have a completion
8665 -- through a renaming declaration. For other completions the
8666 -- pragma appears as a too late representation.
8668 declare
8669 Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
8671 begin
8672 if Present (Decl)
8673 and then Nkind (Decl) = N_Subprogram_Declaration
8674 and then Present (Corresponding_Body (Decl))
8675 and then Nkind (Unit_Declaration_Node
8676 (Corresponding_Body (Decl))) =
8677 N_Subprogram_Renaming_Declaration
8678 then
8679 Error_Msg_Sloc := Sloc (Def_Id);
8680 Error_Msg_NE
8681 ("cannot import&, renaming already provided for "
8682 & "declaration #", N, Def_Id);
8683 end if;
8684 end;
8686 -- If the pragma comes from an aspect specification, there
8687 -- must be an Import aspect specified as well. In the rare
8688 -- case where Import is set to False, the suprogram needs to
8689 -- have a local completion.
8691 declare
8692 Imp_Aspect : constant Node_Id :=
8693 Find_Aspect (Def_Id, Aspect_Import);
8694 Expr : Node_Id;
8696 begin
8697 if Present (Imp_Aspect)
8698 and then Present (Expression (Imp_Aspect))
8699 then
8700 Expr := Expression (Imp_Aspect);
8701 Analyze_And_Resolve (Expr, Standard_Boolean);
8703 if Is_Entity_Name (Expr)
8704 and then Entity (Expr) = Standard_True
8705 then
8706 Set_Has_Completion (Def_Id);
8707 end if;
8709 -- If there is no expression, the default is True, as for
8710 -- all boolean aspects. Same for the older pragma.
8712 else
8713 Set_Has_Completion (Def_Id);
8714 end if;
8715 end;
8717 Process_Interface_Name (Def_Id, Arg3, Arg4, N);
8718 end if;
8720 if Is_Compilation_Unit (Hom_Id) then
8722 -- Its possible homonyms are not affected by the pragma.
8723 -- Such homonyms might be present in the context of other
8724 -- units being compiled.
8726 exit;
8728 elsif From_Aspect_Specification (N) then
8729 exit;
8731 -- If the pragma was created by the compiler, then we don't
8732 -- want it to apply to other homonyms. This kind of case can
8733 -- occur when using pragma Provide_Shift_Operators, which
8734 -- generates implicit shift and rotate operators with Import
8735 -- pragmas that might apply to earlier explicit or implicit
8736 -- declarations marked with Import (for example, coming from
8737 -- an earlier pragma Provide_Shift_Operators for another type),
8738 -- and we don't generally want other homonyms being treated
8739 -- as imported or the pragma flagged as an illegal duplicate.
8741 elsif not Comes_From_Source (N) then
8742 exit;
8744 else
8745 Hom_Id := Homonym (Hom_Id);
8746 end if;
8747 end loop;
8749 -- Import a CPP class
8751 elsif C = Convention_CPP
8752 and then (Is_Record_Type (Def_Id)
8753 or else Ekind (Def_Id) = E_Incomplete_Type)
8754 then
8755 if Ekind (Def_Id) = E_Incomplete_Type then
8756 if Present (Full_View (Def_Id)) then
8757 Def_Id := Full_View (Def_Id);
8759 else
8760 Error_Msg_N
8761 ("cannot import 'C'P'P type before full declaration seen",
8762 Get_Pragma_Arg (Arg2));
8764 -- Although we have reported the error we decorate it as
8765 -- CPP_Class to avoid reporting spurious errors
8767 Set_Is_CPP_Class (Def_Id);
8768 return;
8769 end if;
8770 end if;
8772 -- Types treated as CPP classes must be declared limited (note:
8773 -- this used to be a warning but there is no real benefit to it
8774 -- since we did effectively intend to treat the type as limited
8775 -- anyway).
8777 if not Is_Limited_Type (Def_Id) then
8778 Error_Msg_N
8779 ("imported 'C'P'P type must be limited",
8780 Get_Pragma_Arg (Arg2));
8781 end if;
8783 if Etype (Def_Id) /= Def_Id
8784 and then not Is_CPP_Class (Root_Type (Def_Id))
8785 then
8786 Error_Msg_N ("root type must be a 'C'P'P type", Arg1);
8787 end if;
8789 Set_Is_CPP_Class (Def_Id);
8791 -- Imported CPP types must not have discriminants (because C++
8792 -- classes do not have discriminants).
8794 if Has_Discriminants (Def_Id) then
8795 Error_Msg_N
8796 ("imported 'C'P'P type cannot have discriminants",
8797 First (Discriminant_Specifications
8798 (Declaration_Node (Def_Id))));
8799 end if;
8801 -- Check that components of imported CPP types do not have default
8802 -- expressions. For private types this check is performed when the
8803 -- full view is analyzed (see Process_Full_View).
8805 if not Is_Private_Type (Def_Id) then
8806 Check_CPP_Type_Has_No_Defaults (Def_Id);
8807 end if;
8809 -- Import a CPP exception
8811 elsif C = Convention_CPP
8812 and then Ekind (Def_Id) = E_Exception
8813 then
8814 if No (Arg3) then
8815 Error_Pragma_Arg
8816 ("'External_'Name arguments is required for 'Cpp exception",
8817 Arg3);
8818 else
8819 -- As only a string is allowed, Check_Arg_Is_External_Name
8820 -- isn't called.
8822 Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
8823 end if;
8825 if Present (Arg4) then
8826 Error_Pragma_Arg
8827 ("Link_Name argument not allowed for imported Cpp exception",
8828 Arg4);
8829 end if;
8831 -- Do not call Set_Interface_Name as the name of the exception
8832 -- shouldn't be modified (and in particular it shouldn't be
8833 -- the External_Name). For exceptions, the External_Name is the
8834 -- name of the RTTI structure.
8836 -- ??? Emit an error if pragma Import/Export_Exception is present
8838 elsif Nkind (Parent (Def_Id)) = N_Incomplete_Type_Declaration then
8839 Check_No_Link_Name;
8840 Check_Arg_Count (3);
8841 Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
8843 Process_Import_Predefined_Type;
8845 else
8846 Error_Pragma_Arg
8847 ("second argument of pragma% must be object, subprogram "
8848 & "or incomplete type",
8849 Arg2);
8850 end if;
8852 -- If this pragma applies to a compilation unit, then the unit, which
8853 -- is a subprogram, does not require (or allow) a body. We also do
8854 -- not need to elaborate imported procedures.
8856 if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
8857 declare
8858 Cunit : constant Node_Id := Parent (Parent (N));
8859 begin
8860 Set_Body_Required (Cunit, False);
8861 end;
8862 end if;
8863 end Process_Import_Or_Interface;
8865 --------------------
8866 -- Process_Inline --
8867 --------------------
8869 procedure Process_Inline (Status : Inline_Status) is
8870 Applies : Boolean;
8871 Assoc : Node_Id;
8872 Decl : Node_Id;
8873 Subp : Entity_Id;
8874 Subp_Id : Node_Id;
8876 Ghost_Error_Posted : Boolean := False;
8877 -- Flag set when an error concerning the illegal mix of Ghost and
8878 -- non-Ghost subprograms is emitted.
8880 Ghost_Id : Entity_Id := Empty;
8881 -- The entity of the first Ghost subprogram encountered while
8882 -- processing the arguments of the pragma.
8884 procedure Make_Inline (Subp : Entity_Id);
8885 -- Subp is the defining unit name of the subprogram declaration. If
8886 -- the pragma is valid, call Set_Inline_Flags on Subp, as well as on
8887 -- the corresponding body, if there is one present.
8889 procedure Set_Inline_Flags (Subp : Entity_Id);
8890 -- Set Has_Pragma_{No_Inline,Inline,Inline_Always} flag on Subp.
8891 -- Also set or clear Is_Inlined flag on Subp depending on Status.
8893 function Inlining_Not_Possible (Subp : Entity_Id) return Boolean;
8894 -- Returns True if it can be determined at this stage that inlining
8895 -- is not possible, for example if the body is available and contains
8896 -- exception handlers, we prevent inlining, since otherwise we can
8897 -- get undefined symbols at link time. This function also emits a
8898 -- warning if the pragma appears too late.
8900 -- ??? is business with link symbols still valid, or does it relate
8901 -- to front end ZCX which is being phased out ???
8903 ---------------------------
8904 -- Inlining_Not_Possible --
8905 ---------------------------
8907 function Inlining_Not_Possible (Subp : Entity_Id) return Boolean is
8908 Decl : constant Node_Id := Unit_Declaration_Node (Subp);
8909 Stats : Node_Id;
8911 begin
8912 if Nkind (Decl) = N_Subprogram_Body then
8913 Stats := Handled_Statement_Sequence (Decl);
8914 return Present (Exception_Handlers (Stats))
8915 or else Present (At_End_Proc (Stats));
8917 elsif Nkind (Decl) = N_Subprogram_Declaration
8918 and then Present (Corresponding_Body (Decl))
8919 then
8920 if Analyzed (Corresponding_Body (Decl)) then
8921 Error_Msg_N ("pragma appears too late, ignored??", N);
8922 return True;
8924 -- If the subprogram is a renaming as body, the body is just a
8925 -- call to the renamed subprogram, and inlining is trivially
8926 -- possible.
8928 elsif
8929 Nkind (Unit_Declaration_Node (Corresponding_Body (Decl))) =
8930 N_Subprogram_Renaming_Declaration
8931 then
8932 return False;
8934 else
8935 Stats :=
8936 Handled_Statement_Sequence
8937 (Unit_Declaration_Node (Corresponding_Body (Decl)));
8939 return
8940 Present (Exception_Handlers (Stats))
8941 or else Present (At_End_Proc (Stats));
8942 end if;
8944 else
8945 -- If body is not available, assume the best, the check is
8946 -- performed again when compiling enclosing package bodies.
8948 return False;
8949 end if;
8950 end Inlining_Not_Possible;
8952 -----------------
8953 -- Make_Inline --
8954 -----------------
8956 procedure Make_Inline (Subp : Entity_Id) is
8957 Kind : constant Entity_Kind := Ekind (Subp);
8958 Inner_Subp : Entity_Id := Subp;
8960 begin
8961 -- Ignore if bad type, avoid cascaded error
8963 if Etype (Subp) = Any_Type then
8964 Applies := True;
8965 return;
8967 -- If inlining is not possible, for now do not treat as an error
8969 elsif Status /= Suppressed
8970 and then Front_End_Inlining
8971 and then Inlining_Not_Possible (Subp)
8972 then
8973 Applies := True;
8974 return;
8976 -- Here we have a candidate for inlining, but we must exclude
8977 -- derived operations. Otherwise we would end up trying to inline
8978 -- a phantom declaration, and the result would be to drag in a
8979 -- body which has no direct inlining associated with it. That
8980 -- would not only be inefficient but would also result in the
8981 -- backend doing cross-unit inlining in cases where it was
8982 -- definitely inappropriate to do so.
8984 -- However, a simple Comes_From_Source test is insufficient, since
8985 -- we do want to allow inlining of generic instances which also do
8986 -- not come from source. We also need to recognize specs generated
8987 -- by the front-end for bodies that carry the pragma. Finally,
8988 -- predefined operators do not come from source but are not
8989 -- inlineable either.
8991 elsif Is_Generic_Instance (Subp)
8992 or else Nkind (Parent (Parent (Subp))) = N_Subprogram_Declaration
8993 then
8994 null;
8996 elsif not Comes_From_Source (Subp)
8997 and then Scope (Subp) /= Standard_Standard
8998 then
8999 Applies := True;
9000 return;
9001 end if;
9003 -- The referenced entity must either be the enclosing entity, or
9004 -- an entity declared within the current open scope.
9006 if Present (Scope (Subp))
9007 and then Scope (Subp) /= Current_Scope
9008 and then Subp /= Current_Scope
9009 then
9010 Error_Pragma_Arg
9011 ("argument of% must be entity in current scope", Assoc);
9012 return;
9013 end if;
9015 -- Processing for procedure, operator or function. If subprogram
9016 -- is aliased (as for an instance) indicate that the renamed
9017 -- entity (if declared in the same unit) is inlined.
9018 -- If this is the anonymous subprogram created for a subprogram
9019 -- instance, the inlining applies to it directly. Otherwise we
9020 -- retrieve it as the alias of the visible subprogram instance.
9022 if Is_Subprogram (Subp) then
9023 if Is_Wrapper_Package (Scope (Subp)) then
9024 Inner_Subp := Subp;
9025 else
9026 Inner_Subp := Ultimate_Alias (Inner_Subp);
9027 end if;
9029 if In_Same_Source_Unit (Subp, Inner_Subp) then
9030 Set_Inline_Flags (Inner_Subp);
9032 Decl := Parent (Parent (Inner_Subp));
9034 if Nkind (Decl) = N_Subprogram_Declaration
9035 and then Present (Corresponding_Body (Decl))
9036 then
9037 Set_Inline_Flags (Corresponding_Body (Decl));
9039 elsif Is_Generic_Instance (Subp)
9040 and then Comes_From_Source (Subp)
9041 then
9042 -- Indicate that the body needs to be created for
9043 -- inlining subsequent calls. The instantiation node
9044 -- follows the declaration of the wrapper package
9045 -- created for it. The subprogram that requires the
9046 -- body is the anonymous one in the wrapper package.
9048 if Scope (Subp) /= Standard_Standard
9049 and then
9050 Need_Subprogram_Instance_Body
9051 (Next (Unit_Declaration_Node
9052 (Scope (Alias (Subp)))), Subp)
9053 then
9054 null;
9055 end if;
9057 -- Inline is a program unit pragma (RM 10.1.5) and cannot
9058 -- appear in a formal part to apply to a formal subprogram.
9059 -- Do not apply check within an instance or a formal package
9060 -- the test will have been applied to the original generic.
9062 elsif Nkind (Decl) in N_Formal_Subprogram_Declaration
9063 and then List_Containing (Decl) = List_Containing (N)
9064 and then not In_Instance
9065 then
9066 Error_Msg_N
9067 ("Inline cannot apply to a formal subprogram", N);
9069 -- If Subp is a renaming, it is the renamed entity that
9070 -- will appear in any call, and be inlined. However, for
9071 -- ASIS uses it is convenient to indicate that the renaming
9072 -- itself is an inlined subprogram, so that some gnatcheck
9073 -- rules can be applied in the absence of expansion.
9075 elsif Nkind (Decl) = N_Subprogram_Renaming_Declaration then
9076 Set_Inline_Flags (Subp);
9077 end if;
9078 end if;
9080 Applies := True;
9082 -- For a generic subprogram set flag as well, for use at the point
9083 -- of instantiation, to determine whether the body should be
9084 -- generated.
9086 elsif Is_Generic_Subprogram (Subp) then
9087 Set_Inline_Flags (Subp);
9088 Applies := True;
9090 -- Literals are by definition inlined
9092 elsif Kind = E_Enumeration_Literal then
9093 null;
9095 -- Anything else is an error
9097 else
9098 Error_Pragma_Arg
9099 ("expect subprogram name for pragma%", Assoc);
9100 end if;
9101 end Make_Inline;
9103 ----------------------
9104 -- Set_Inline_Flags --
9105 ----------------------
9107 procedure Set_Inline_Flags (Subp : Entity_Id) is
9108 begin
9109 -- First set the Has_Pragma_XXX flags and issue the appropriate
9110 -- errors and warnings for suspicious combinations.
9112 if Prag_Id = Pragma_No_Inline then
9113 if Has_Pragma_Inline_Always (Subp) then
9114 Error_Msg_N
9115 ("Inline_Always and No_Inline are mutually exclusive", N);
9116 elsif Has_Pragma_Inline (Subp) then
9117 Error_Msg_NE
9118 ("Inline and No_Inline both specified for& ??",
9119 N, Entity (Subp_Id));
9120 end if;
9122 Set_Has_Pragma_No_Inline (Subp);
9123 else
9124 if Prag_Id = Pragma_Inline_Always then
9125 if Has_Pragma_No_Inline (Subp) then
9126 Error_Msg_N
9127 ("Inline_Always and No_Inline are mutually exclusive",
9129 end if;
9131 Set_Has_Pragma_Inline_Always (Subp);
9132 else
9133 if Has_Pragma_No_Inline (Subp) then
9134 Error_Msg_NE
9135 ("Inline and No_Inline both specified for& ??",
9136 N, Entity (Subp_Id));
9137 end if;
9138 end if;
9140 Set_Has_Pragma_Inline (Subp);
9141 end if;
9143 -- Then adjust the Is_Inlined flag. It can never be set if the
9144 -- subprogram is subject to pragma No_Inline.
9146 case Status is
9147 when Suppressed =>
9148 Set_Is_Inlined (Subp, False);
9150 when Disabled =>
9151 null;
9153 when Enabled =>
9154 if not Has_Pragma_No_Inline (Subp) then
9155 Set_Is_Inlined (Subp, True);
9156 end if;
9157 end case;
9159 -- A pragma that applies to a Ghost entity becomes Ghost for the
9160 -- purposes of legality checks and removal of ignored Ghost code.
9162 Mark_Ghost_Pragma (N, Subp);
9164 -- Capture the entity of the first Ghost subprogram being
9165 -- processed for error detection purposes.
9167 if Is_Ghost_Entity (Subp) then
9168 if No (Ghost_Id) then
9169 Ghost_Id := Subp;
9170 end if;
9172 -- Otherwise the subprogram is non-Ghost. It is illegal to mix
9173 -- references to Ghost and non-Ghost entities (SPARK RM 6.9).
9175 elsif Present (Ghost_Id) and then not Ghost_Error_Posted then
9176 Ghost_Error_Posted := True;
9178 Error_Msg_Name_1 := Pname;
9179 Error_Msg_N
9180 ("pragma % cannot mention ghost and non-ghost subprograms",
9183 Error_Msg_Sloc := Sloc (Ghost_Id);
9184 Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
9186 Error_Msg_Sloc := Sloc (Subp);
9187 Error_Msg_NE ("\& # declared as non-ghost", N, Subp);
9188 end if;
9189 end Set_Inline_Flags;
9191 -- Start of processing for Process_Inline
9193 begin
9194 Check_No_Identifiers;
9195 Check_At_Least_N_Arguments (1);
9197 if Status = Enabled then
9198 Inline_Processing_Required := True;
9199 end if;
9201 Assoc := Arg1;
9202 while Present (Assoc) loop
9203 Subp_Id := Get_Pragma_Arg (Assoc);
9204 Analyze (Subp_Id);
9205 Applies := False;
9207 if Is_Entity_Name (Subp_Id) then
9208 Subp := Entity (Subp_Id);
9210 if Subp = Any_Id then
9212 -- If previous error, avoid cascaded errors
9214 Check_Error_Detected;
9215 Applies := True;
9217 else
9218 Make_Inline (Subp);
9220 -- For the pragma case, climb homonym chain. This is
9221 -- what implements allowing the pragma in the renaming
9222 -- case, with the result applying to the ancestors, and
9223 -- also allows Inline to apply to all previous homonyms.
9225 if not From_Aspect_Specification (N) then
9226 while Present (Homonym (Subp))
9227 and then Scope (Homonym (Subp)) = Current_Scope
9228 loop
9229 Make_Inline (Homonym (Subp));
9230 Subp := Homonym (Subp);
9231 end loop;
9232 end if;
9233 end if;
9234 end if;
9236 if not Applies then
9237 Error_Pragma_Arg ("inappropriate argument for pragma%", Assoc);
9238 end if;
9240 Next (Assoc);
9241 end loop;
9243 -- If the context is a package declaration, the pragma indicates
9244 -- that inlining will require the presence of the corresponding
9245 -- body. (this may be further refined).
9247 if not In_Instance
9248 and then Nkind (Unit (Cunit (Current_Sem_Unit))) =
9249 N_Package_Declaration
9250 then
9251 Set_Body_Needed_For_Inlining (Cunit_Entity (Current_Sem_Unit));
9252 end if;
9253 end Process_Inline;
9255 ----------------------------
9256 -- Process_Interface_Name --
9257 ----------------------------
9259 procedure Process_Interface_Name
9260 (Subprogram_Def : Entity_Id;
9261 Ext_Arg : Node_Id;
9262 Link_Arg : Node_Id;
9263 Prag : Node_Id)
9265 Ext_Nam : Node_Id;
9266 Link_Nam : Node_Id;
9267 String_Val : String_Id;
9269 procedure Check_Form_Of_Interface_Name (SN : Node_Id);
9270 -- SN is a string literal node for an interface name. This routine
9271 -- performs some minimal checks that the name is reasonable. In
9272 -- particular that no spaces or other obviously incorrect characters
9273 -- appear. This is only a warning, since any characters are allowed.
9275 ----------------------------------
9276 -- Check_Form_Of_Interface_Name --
9277 ----------------------------------
9279 procedure Check_Form_Of_Interface_Name (SN : Node_Id) is
9280 S : constant String_Id := Strval (Expr_Value_S (SN));
9281 SL : constant Nat := String_Length (S);
9282 C : Char_Code;
9284 begin
9285 if SL = 0 then
9286 Error_Msg_N ("interface name cannot be null string", SN);
9287 end if;
9289 for J in 1 .. SL loop
9290 C := Get_String_Char (S, J);
9292 -- Look for dubious character and issue unconditional warning.
9293 -- Definitely dubious if not in character range.
9295 if not In_Character_Range (C)
9297 -- Commas, spaces and (back)slashes are dubious
9299 or else Get_Character (C) = ','
9300 or else Get_Character (C) = '\'
9301 or else Get_Character (C) = ' '
9302 or else Get_Character (C) = '/'
9303 then
9304 Error_Msg
9305 ("??interface name contains illegal character",
9306 Sloc (SN) + Source_Ptr (J));
9307 end if;
9308 end loop;
9309 end Check_Form_Of_Interface_Name;
9311 -- Start of processing for Process_Interface_Name
9313 begin
9314 -- If we are looking at a pragma that comes from an aspect then it
9315 -- needs to have its corresponding aspect argument expressions
9316 -- analyzed in addition to the generated pragma so that aspects
9317 -- within generic units get properly resolved.
9319 if Present (Prag) and then From_Aspect_Specification (Prag) then
9320 declare
9321 Asp : constant Node_Id := Corresponding_Aspect (Prag);
9322 Dummy_1 : Node_Id;
9323 Dummy_2 : Node_Id;
9324 Dummy_3 : Node_Id;
9325 EN : Node_Id;
9326 LN : Node_Id;
9328 begin
9329 -- Obtain all interfacing aspects used to construct the pragma
9331 Get_Interfacing_Aspects
9332 (Asp, Dummy_1, EN, Dummy_2, Dummy_3, LN);
9334 -- Analyze the expression of aspect External_Name
9336 if Present (EN) then
9337 Analyze (Expression (EN));
9338 end if;
9340 -- Analyze the expressio of aspect Link_Name
9342 if Present (LN) then
9343 Analyze (Expression (LN));
9344 end if;
9345 end;
9346 end if;
9348 if No (Link_Arg) then
9349 if No (Ext_Arg) then
9350 return;
9352 elsif Chars (Ext_Arg) = Name_Link_Name then
9353 Ext_Nam := Empty;
9354 Link_Nam := Expression (Ext_Arg);
9356 else
9357 Check_Optional_Identifier (Ext_Arg, Name_External_Name);
9358 Ext_Nam := Expression (Ext_Arg);
9359 Link_Nam := Empty;
9360 end if;
9362 else
9363 Check_Optional_Identifier (Ext_Arg, Name_External_Name);
9364 Check_Optional_Identifier (Link_Arg, Name_Link_Name);
9365 Ext_Nam := Expression (Ext_Arg);
9366 Link_Nam := Expression (Link_Arg);
9367 end if;
9369 -- Check expressions for external name and link name are static
9371 if Present (Ext_Nam) then
9372 Check_Arg_Is_OK_Static_Expression (Ext_Nam, Standard_String);
9373 Check_Form_Of_Interface_Name (Ext_Nam);
9375 -- Verify that external name is not the name of a local entity,
9376 -- which would hide the imported one and could lead to run-time
9377 -- surprises. The problem can only arise for entities declared in
9378 -- a package body (otherwise the external name is fully qualified
9379 -- and will not conflict).
9381 declare
9382 Nam : Name_Id;
9383 E : Entity_Id;
9384 Par : Node_Id;
9386 begin
9387 if Prag_Id = Pragma_Import then
9388 Nam := String_To_Name (Strval (Expr_Value_S (Ext_Nam)));
9389 E := Entity_Id (Get_Name_Table_Int (Nam));
9391 if Nam /= Chars (Subprogram_Def)
9392 and then Present (E)
9393 and then not Is_Overloadable (E)
9394 and then Is_Immediately_Visible (E)
9395 and then not Is_Imported (E)
9396 and then Ekind (Scope (E)) = E_Package
9397 then
9398 Par := Parent (E);
9399 while Present (Par) loop
9400 if Nkind (Par) = N_Package_Body then
9401 Error_Msg_Sloc := Sloc (E);
9402 Error_Msg_NE
9403 ("imported entity is hidden by & declared#",
9404 Ext_Arg, E);
9405 exit;
9406 end if;
9408 Par := Parent (Par);
9409 end loop;
9410 end if;
9411 end if;
9412 end;
9413 end if;
9415 if Present (Link_Nam) then
9416 Check_Arg_Is_OK_Static_Expression (Link_Nam, Standard_String);
9417 Check_Form_Of_Interface_Name (Link_Nam);
9418 end if;
9420 -- If there is no link name, just set the external name
9422 if No (Link_Nam) then
9423 Link_Nam := Adjust_External_Name_Case (Expr_Value_S (Ext_Nam));
9425 -- For the Link_Name case, the given literal is preceded by an
9426 -- asterisk, which indicates to GCC that the given name should be
9427 -- taken literally, and in particular that no prepending of
9428 -- underlines should occur, even in systems where this is the
9429 -- normal default.
9431 else
9432 Start_String;
9433 Store_String_Char (Get_Char_Code ('*'));
9434 String_Val := Strval (Expr_Value_S (Link_Nam));
9435 Store_String_Chars (String_Val);
9436 Link_Nam :=
9437 Make_String_Literal (Sloc (Link_Nam),
9438 Strval => End_String);
9439 end if;
9441 -- Set the interface name. If the entity is a generic instance, use
9442 -- its alias, which is the callable entity.
9444 if Is_Generic_Instance (Subprogram_Def) then
9445 Set_Encoded_Interface_Name
9446 (Alias (Get_Base_Subprogram (Subprogram_Def)), Link_Nam);
9447 else
9448 Set_Encoded_Interface_Name
9449 (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
9450 end if;
9452 Check_Duplicated_Export_Name (Link_Nam);
9453 end Process_Interface_Name;
9455 -----------------------------------------
9456 -- Process_Interrupt_Or_Attach_Handler --
9457 -----------------------------------------
9459 procedure Process_Interrupt_Or_Attach_Handler is
9460 Handler : constant Entity_Id := Entity (Get_Pragma_Arg (Arg1));
9461 Prot_Typ : constant Entity_Id := Scope (Handler);
9463 begin
9464 -- A pragma that applies to a Ghost entity becomes Ghost for the
9465 -- purposes of legality checks and removal of ignored Ghost code.
9467 Mark_Ghost_Pragma (N, Handler);
9468 Set_Is_Interrupt_Handler (Handler);
9470 pragma Assert (Ekind (Prot_Typ) = E_Protected_Type);
9472 Record_Rep_Item (Prot_Typ, N);
9474 -- Chain the pragma on the contract for completeness
9476 Add_Contract_Item (N, Handler);
9477 end Process_Interrupt_Or_Attach_Handler;
9479 --------------------------------------------------
9480 -- Process_Restrictions_Or_Restriction_Warnings --
9481 --------------------------------------------------
9483 -- Note: some of the simple identifier cases were handled in par-prag,
9484 -- but it is harmless (and more straightforward) to simply handle all
9485 -- cases here, even if it means we repeat a bit of work in some cases.
9487 procedure Process_Restrictions_Or_Restriction_Warnings
9488 (Warn : Boolean)
9490 Arg : Node_Id;
9491 R_Id : Restriction_Id;
9492 Id : Name_Id;
9493 Expr : Node_Id;
9494 Val : Uint;
9496 begin
9497 -- Ignore all Restrictions pragmas in CodePeer mode
9499 if CodePeer_Mode then
9500 return;
9501 end if;
9503 Check_Ada_83_Warning;
9504 Check_At_Least_N_Arguments (1);
9505 Check_Valid_Configuration_Pragma;
9507 Arg := Arg1;
9508 while Present (Arg) loop
9509 Id := Chars (Arg);
9510 Expr := Get_Pragma_Arg (Arg);
9512 -- Case of no restriction identifier present
9514 if Id = No_Name then
9515 if Nkind (Expr) /= N_Identifier then
9516 Error_Pragma_Arg
9517 ("invalid form for restriction", Arg);
9518 end if;
9520 R_Id :=
9521 Get_Restriction_Id
9522 (Process_Restriction_Synonyms (Expr));
9524 if R_Id not in All_Boolean_Restrictions then
9525 Error_Msg_Name_1 := Pname;
9526 Error_Msg_N
9527 ("invalid restriction identifier&", Get_Pragma_Arg (Arg));
9529 -- Check for possible misspelling
9531 for J in Restriction_Id loop
9532 declare
9533 Rnm : constant String := Restriction_Id'Image (J);
9535 begin
9536 Name_Buffer (1 .. Rnm'Length) := Rnm;
9537 Name_Len := Rnm'Length;
9538 Set_Casing (All_Lower_Case);
9540 if Is_Bad_Spelling_Of (Chars (Expr), Name_Enter) then
9541 Set_Casing
9542 (Identifier_Casing
9543 (Source_Index (Current_Sem_Unit)));
9544 Error_Msg_String (1 .. Rnm'Length) :=
9545 Name_Buffer (1 .. Name_Len);
9546 Error_Msg_Strlen := Rnm'Length;
9547 Error_Msg_N -- CODEFIX
9548 ("\possible misspelling of ""~""",
9549 Get_Pragma_Arg (Arg));
9550 exit;
9551 end if;
9552 end;
9553 end loop;
9555 raise Pragma_Exit;
9556 end if;
9558 if Implementation_Restriction (R_Id) then
9559 Check_Restriction (No_Implementation_Restrictions, Arg);
9560 end if;
9562 -- Special processing for No_Elaboration_Code restriction
9564 if R_Id = No_Elaboration_Code then
9566 -- Restriction is only recognized within a configuration
9567 -- pragma file, or within a unit of the main extended
9568 -- program. Note: the test for Main_Unit is needed to
9569 -- properly include the case of configuration pragma files.
9571 if not (Current_Sem_Unit = Main_Unit
9572 or else In_Extended_Main_Source_Unit (N))
9573 then
9574 return;
9576 -- Don't allow in a subunit unless already specified in
9577 -- body or spec.
9579 elsif Nkind (Parent (N)) = N_Compilation_Unit
9580 and then Nkind (Unit (Parent (N))) = N_Subunit
9581 and then not Restriction_Active (No_Elaboration_Code)
9582 then
9583 Error_Msg_N
9584 ("invalid specification of ""No_Elaboration_Code""",
9586 Error_Msg_N
9587 ("\restriction cannot be specified in a subunit", N);
9588 Error_Msg_N
9589 ("\unless also specified in body or spec", N);
9590 return;
9592 -- If we accept a No_Elaboration_Code restriction, then it
9593 -- needs to be added to the configuration restriction set so
9594 -- that we get proper application to other units in the main
9595 -- extended source as required.
9597 else
9598 Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
9599 end if;
9600 end if;
9602 -- If this is a warning, then set the warning unless we already
9603 -- have a real restriction active (we never want a warning to
9604 -- override a real restriction).
9606 if Warn then
9607 if not Restriction_Active (R_Id) then
9608 Set_Restriction (R_Id, N);
9609 Restriction_Warnings (R_Id) := True;
9610 end if;
9612 -- If real restriction case, then set it and make sure that the
9613 -- restriction warning flag is off, since a real restriction
9614 -- always overrides a warning.
9616 else
9617 Set_Restriction (R_Id, N);
9618 Restriction_Warnings (R_Id) := False;
9619 end if;
9621 -- Check for obsolescent restrictions in Ada 2005 mode
9623 if not Warn
9624 and then Ada_Version >= Ada_2005
9625 and then (R_Id = No_Asynchronous_Control
9626 or else
9627 R_Id = No_Unchecked_Deallocation
9628 or else
9629 R_Id = No_Unchecked_Conversion)
9630 then
9631 Check_Restriction (No_Obsolescent_Features, N);
9632 end if;
9634 -- A very special case that must be processed here: pragma
9635 -- Restrictions (No_Exceptions) turns off all run-time
9636 -- checking. This is a bit dubious in terms of the formal
9637 -- language definition, but it is what is intended by RM
9638 -- H.4(12). Restriction_Warnings never affects generated code
9639 -- so this is done only in the real restriction case.
9641 -- Atomic_Synchronization is not a real check, so it is not
9642 -- affected by this processing).
9644 -- Ignore the effect of pragma Restrictions (No_Exceptions) on
9645 -- run-time checks in CodePeer and GNATprove modes: we want to
9646 -- generate checks for analysis purposes, as set respectively
9647 -- by -gnatC and -gnatd.F
9649 if not Warn
9650 and then not (CodePeer_Mode or GNATprove_Mode)
9651 and then R_Id = No_Exceptions
9652 then
9653 for J in Scope_Suppress.Suppress'Range loop
9654 if J /= Atomic_Synchronization then
9655 Scope_Suppress.Suppress (J) := True;
9656 end if;
9657 end loop;
9658 end if;
9660 -- Case of No_Dependence => unit-name. Note that the parser
9661 -- already made the necessary entry in the No_Dependence table.
9663 elsif Id = Name_No_Dependence then
9664 if not OK_No_Dependence_Unit_Name (Expr) then
9665 raise Pragma_Exit;
9666 end if;
9668 -- Case of No_Specification_Of_Aspect => aspect-identifier
9670 elsif Id = Name_No_Specification_Of_Aspect then
9671 declare
9672 A_Id : Aspect_Id;
9674 begin
9675 if Nkind (Expr) /= N_Identifier then
9676 A_Id := No_Aspect;
9677 else
9678 A_Id := Get_Aspect_Id (Chars (Expr));
9679 end if;
9681 if A_Id = No_Aspect then
9682 Error_Pragma_Arg ("invalid restriction name", Arg);
9683 else
9684 Set_Restriction_No_Specification_Of_Aspect (Expr, Warn);
9685 end if;
9686 end;
9688 -- Case of No_Use_Of_Attribute => attribute-identifier
9690 elsif Id = Name_No_Use_Of_Attribute then
9691 if Nkind (Expr) /= N_Identifier
9692 or else not Is_Attribute_Name (Chars (Expr))
9693 then
9694 Error_Msg_N ("unknown attribute name??", Expr);
9696 else
9697 Set_Restriction_No_Use_Of_Attribute (Expr, Warn);
9698 end if;
9700 -- Case of No_Use_Of_Entity => fully-qualified-name
9702 elsif Id = Name_No_Use_Of_Entity then
9704 -- Restriction is only recognized within a configuration
9705 -- pragma file, or within a unit of the main extended
9706 -- program. Note: the test for Main_Unit is needed to
9707 -- properly include the case of configuration pragma files.
9709 if Current_Sem_Unit = Main_Unit
9710 or else In_Extended_Main_Source_Unit (N)
9711 then
9712 if not OK_No_Dependence_Unit_Name (Expr) then
9713 Error_Msg_N ("wrong form for entity name", Expr);
9714 else
9715 Set_Restriction_No_Use_Of_Entity
9716 (Expr, Warn, No_Profile);
9717 end if;
9718 end if;
9720 -- Case of No_Use_Of_Pragma => pragma-identifier
9722 elsif Id = Name_No_Use_Of_Pragma then
9723 if Nkind (Expr) /= N_Identifier
9724 or else not Is_Pragma_Name (Chars (Expr))
9725 then
9726 Error_Msg_N ("unknown pragma name??", Expr);
9727 else
9728 Set_Restriction_No_Use_Of_Pragma (Expr, Warn);
9729 end if;
9731 -- All other cases of restriction identifier present
9733 else
9734 R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
9735 Analyze_And_Resolve (Expr, Any_Integer);
9737 if R_Id not in All_Parameter_Restrictions then
9738 Error_Pragma_Arg
9739 ("invalid restriction parameter identifier", Arg);
9741 elsif not Is_OK_Static_Expression (Expr) then
9742 Flag_Non_Static_Expr
9743 ("value must be static expression!", Expr);
9744 raise Pragma_Exit;
9746 elsif not Is_Integer_Type (Etype (Expr))
9747 or else Expr_Value (Expr) < 0
9748 then
9749 Error_Pragma_Arg
9750 ("value must be non-negative integer", Arg);
9751 end if;
9753 -- Restriction pragma is active
9755 Val := Expr_Value (Expr);
9757 if not UI_Is_In_Int_Range (Val) then
9758 Error_Pragma_Arg
9759 ("pragma ignored, value too large??", Arg);
9760 end if;
9762 -- Warning case. If the real restriction is active, then we
9763 -- ignore the request, since warning never overrides a real
9764 -- restriction. Otherwise we set the proper warning. Note that
9765 -- this circuit sets the warning again if it is already set,
9766 -- which is what we want, since the constant may have changed.
9768 if Warn then
9769 if not Restriction_Active (R_Id) then
9770 Set_Restriction
9771 (R_Id, N, Integer (UI_To_Int (Val)));
9772 Restriction_Warnings (R_Id) := True;
9773 end if;
9775 -- Real restriction case, set restriction and make sure warning
9776 -- flag is off since real restriction always overrides warning.
9778 else
9779 Set_Restriction (R_Id, N, Integer (UI_To_Int (Val)));
9780 Restriction_Warnings (R_Id) := False;
9781 end if;
9782 end if;
9784 Next (Arg);
9785 end loop;
9786 end Process_Restrictions_Or_Restriction_Warnings;
9788 ---------------------------------
9789 -- Process_Suppress_Unsuppress --
9790 ---------------------------------
9792 -- Note: this procedure makes entries in the check suppress data
9793 -- structures managed by Sem. See spec of package Sem for full
9794 -- details on how we handle recording of check suppression.
9796 procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
9797 C : Check_Id;
9798 E : Entity_Id;
9799 E_Id : Node_Id;
9801 In_Package_Spec : constant Boolean :=
9802 Is_Package_Or_Generic_Package (Current_Scope)
9803 and then not In_Package_Body (Current_Scope);
9805 procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
9806 -- Used to suppress a single check on the given entity
9808 --------------------------------
9809 -- Suppress_Unsuppress_Echeck --
9810 --------------------------------
9812 procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
9813 begin
9814 -- Check for error of trying to set atomic synchronization for
9815 -- a non-atomic variable.
9817 if C = Atomic_Synchronization
9818 and then not (Is_Atomic (E) or else Has_Atomic_Components (E))
9819 then
9820 Error_Msg_N
9821 ("pragma & requires atomic type or variable",
9822 Pragma_Identifier (Original_Node (N)));
9823 end if;
9825 Set_Checks_May_Be_Suppressed (E);
9827 if In_Package_Spec then
9828 Push_Global_Suppress_Stack_Entry
9829 (Entity => E,
9830 Check => C,
9831 Suppress => Suppress_Case);
9832 else
9833 Push_Local_Suppress_Stack_Entry
9834 (Entity => E,
9835 Check => C,
9836 Suppress => Suppress_Case);
9837 end if;
9839 -- If this is a first subtype, and the base type is distinct,
9840 -- then also set the suppress flags on the base type.
9842 if Is_First_Subtype (E) and then Etype (E) /= E then
9843 Suppress_Unsuppress_Echeck (Etype (E), C);
9844 end if;
9845 end Suppress_Unsuppress_Echeck;
9847 -- Start of processing for Process_Suppress_Unsuppress
9849 begin
9850 -- Ignore pragma Suppress/Unsuppress in CodePeer and GNATprove modes
9851 -- on user code: we want to generate checks for analysis purposes, as
9852 -- set respectively by -gnatC and -gnatd.F
9854 if Comes_From_Source (N)
9855 and then (CodePeer_Mode or GNATprove_Mode)
9856 then
9857 return;
9858 end if;
9860 -- Suppress/Unsuppress can appear as a configuration pragma, or in a
9861 -- declarative part or a package spec (RM 11.5(5)).
9863 if not Is_Configuration_Pragma then
9864 Check_Is_In_Decl_Part_Or_Package_Spec;
9865 end if;
9867 Check_At_Least_N_Arguments (1);
9868 Check_At_Most_N_Arguments (2);
9869 Check_No_Identifier (Arg1);
9870 Check_Arg_Is_Identifier (Arg1);
9872 C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
9874 if C = No_Check_Id then
9875 Error_Pragma_Arg
9876 ("argument of pragma% is not valid check name", Arg1);
9877 end if;
9879 -- Warn that suppress of Elaboration_Check has no effect in SPARK
9881 if C = Elaboration_Check and then SPARK_Mode = On then
9882 Error_Pragma_Arg
9883 ("Suppress of Elaboration_Check ignored in SPARK??",
9884 "\elaboration checking rules are statically enforced "
9885 & "(SPARK RM 7.7)", Arg1);
9886 end if;
9888 -- One-argument case
9890 if Arg_Count = 1 then
9892 -- Make an entry in the local scope suppress table. This is the
9893 -- table that directly shows the current value of the scope
9894 -- suppress check for any check id value.
9896 if C = All_Checks then
9898 -- For All_Checks, we set all specific predefined checks with
9899 -- the exception of Elaboration_Check, which is handled
9900 -- specially because of not wanting All_Checks to have the
9901 -- effect of deactivating static elaboration order processing.
9902 -- Atomic_Synchronization is also not affected, since this is
9903 -- not a real check.
9905 for J in Scope_Suppress.Suppress'Range loop
9906 if J /= Elaboration_Check
9907 and then
9908 J /= Atomic_Synchronization
9909 then
9910 Scope_Suppress.Suppress (J) := Suppress_Case;
9911 end if;
9912 end loop;
9914 -- If not All_Checks, and predefined check, then set appropriate
9915 -- scope entry. Note that we will set Elaboration_Check if this
9916 -- is explicitly specified. Atomic_Synchronization is allowed
9917 -- only if internally generated and entity is atomic.
9919 elsif C in Predefined_Check_Id
9920 and then (not Comes_From_Source (N)
9921 or else C /= Atomic_Synchronization)
9922 then
9923 Scope_Suppress.Suppress (C) := Suppress_Case;
9924 end if;
9926 -- Also make an entry in the Local_Entity_Suppress table
9928 Push_Local_Suppress_Stack_Entry
9929 (Entity => Empty,
9930 Check => C,
9931 Suppress => Suppress_Case);
9933 -- Case of two arguments present, where the check is suppressed for
9934 -- a specified entity (given as the second argument of the pragma)
9936 else
9937 -- This is obsolescent in Ada 2005 mode
9939 if Ada_Version >= Ada_2005 then
9940 Check_Restriction (No_Obsolescent_Features, Arg2);
9941 end if;
9943 Check_Optional_Identifier (Arg2, Name_On);
9944 E_Id := Get_Pragma_Arg (Arg2);
9945 Analyze (E_Id);
9947 if not Is_Entity_Name (E_Id) then
9948 Error_Pragma_Arg
9949 ("second argument of pragma% must be entity name", Arg2);
9950 end if;
9952 E := Entity (E_Id);
9954 if E = Any_Id then
9955 return;
9956 end if;
9958 -- A pragma that applies to a Ghost entity becomes Ghost for the
9959 -- purposes of legality checks and removal of ignored Ghost code.
9961 Mark_Ghost_Pragma (N, E);
9963 -- Enforce RM 11.5(7) which requires that for a pragma that
9964 -- appears within a package spec, the named entity must be
9965 -- within the package spec. We allow the package name itself
9966 -- to be mentioned since that makes sense, although it is not
9967 -- strictly allowed by 11.5(7).
9969 if In_Package_Spec
9970 and then E /= Current_Scope
9971 and then Scope (E) /= Current_Scope
9972 then
9973 Error_Pragma_Arg
9974 ("entity in pragma% is not in package spec (RM 11.5(7))",
9975 Arg2);
9976 end if;
9978 -- Loop through homonyms. As noted below, in the case of a package
9979 -- spec, only homonyms within the package spec are considered.
9981 loop
9982 Suppress_Unsuppress_Echeck (E, C);
9984 if Is_Generic_Instance (E)
9985 and then Is_Subprogram (E)
9986 and then Present (Alias (E))
9987 then
9988 Suppress_Unsuppress_Echeck (Alias (E), C);
9989 end if;
9991 -- Move to next homonym if not aspect spec case
9993 exit when From_Aspect_Specification (N);
9994 E := Homonym (E);
9995 exit when No (E);
9997 -- If we are within a package specification, the pragma only
9998 -- applies to homonyms in the same scope.
10000 exit when In_Package_Spec
10001 and then Scope (E) /= Current_Scope;
10002 end loop;
10003 end if;
10004 end Process_Suppress_Unsuppress;
10006 -------------------------------
10007 -- Record_Independence_Check --
10008 -------------------------------
10010 procedure Record_Independence_Check (N : Node_Id; E : Entity_Id) is
10011 begin
10012 -- For GCC back ends the validation is done a priori
10014 if not AAMP_On_Target then
10015 return;
10016 end if;
10018 Independence_Checks.Append ((N, E));
10019 end Record_Independence_Check;
10021 ------------------
10022 -- Set_Exported --
10023 ------------------
10025 procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
10026 begin
10027 if Is_Imported (E) then
10028 Error_Pragma_Arg
10029 ("cannot export entity& that was previously imported", Arg);
10031 elsif Present (Address_Clause (E))
10032 and then not Relaxed_RM_Semantics
10033 then
10034 Error_Pragma_Arg
10035 ("cannot export entity& that has an address clause", Arg);
10036 end if;
10038 Set_Is_Exported (E);
10040 -- Generate a reference for entity explicitly, because the
10041 -- identifier may be overloaded and name resolution will not
10042 -- generate one.
10044 Generate_Reference (E, Arg);
10046 -- Deal with exporting non-library level entity
10048 if not Is_Library_Level_Entity (E) then
10050 -- Not allowed at all for subprograms
10052 if Is_Subprogram (E) then
10053 Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
10055 -- Otherwise set public and statically allocated
10057 else
10058 Set_Is_Public (E);
10059 Set_Is_Statically_Allocated (E);
10061 -- Warn if the corresponding W flag is set
10063 if Warn_On_Export_Import
10065 -- Only do this for something that was in the source. Not
10066 -- clear if this can be False now (there used for sure to be
10067 -- cases on some systems where it was False), but anyway the
10068 -- test is harmless if not needed, so it is retained.
10070 and then Comes_From_Source (Arg)
10071 then
10072 Error_Msg_NE
10073 ("?x?& has been made static as a result of Export",
10074 Arg, E);
10075 Error_Msg_N
10076 ("\?x?this usage is non-standard and non-portable",
10077 Arg);
10078 end if;
10079 end if;
10080 end if;
10082 if Warn_On_Export_Import and then Is_Type (E) then
10083 Error_Msg_NE ("exporting a type has no effect?x?", Arg, E);
10084 end if;
10086 if Warn_On_Export_Import and Inside_A_Generic then
10087 Error_Msg_NE
10088 ("all instances of& will have the same external name?x?",
10089 Arg, E);
10090 end if;
10091 end Set_Exported;
10093 ----------------------------------------------
10094 -- Set_Extended_Import_Export_External_Name --
10095 ----------------------------------------------
10097 procedure Set_Extended_Import_Export_External_Name
10098 (Internal_Ent : Entity_Id;
10099 Arg_External : Node_Id)
10101 Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
10102 New_Name : Node_Id;
10104 begin
10105 if No (Arg_External) then
10106 return;
10107 end if;
10109 Check_Arg_Is_External_Name (Arg_External);
10111 if Nkind (Arg_External) = N_String_Literal then
10112 if String_Length (Strval (Arg_External)) = 0 then
10113 return;
10114 else
10115 New_Name := Adjust_External_Name_Case (Arg_External);
10116 end if;
10118 elsif Nkind (Arg_External) = N_Identifier then
10119 New_Name := Get_Default_External_Name (Arg_External);
10121 -- Check_Arg_Is_External_Name should let through only identifiers and
10122 -- string literals or static string expressions (which are folded to
10123 -- string literals).
10125 else
10126 raise Program_Error;
10127 end if;
10129 -- If we already have an external name set (by a prior normal Import
10130 -- or Export pragma), then the external names must match
10132 if Present (Interface_Name (Internal_Ent)) then
10134 -- Ignore mismatching names in CodePeer mode, to support some
10135 -- old compilers which would export the same procedure under
10136 -- different names, e.g:
10137 -- procedure P;
10138 -- pragma Export_Procedure (P, "a");
10139 -- pragma Export_Procedure (P, "b");
10141 if CodePeer_Mode then
10142 return;
10143 end if;
10145 Check_Matching_Internal_Names : declare
10146 S1 : constant String_Id := Strval (Old_Name);
10147 S2 : constant String_Id := Strval (New_Name);
10149 procedure Mismatch;
10150 pragma No_Return (Mismatch);
10151 -- Called if names do not match
10153 --------------
10154 -- Mismatch --
10155 --------------
10157 procedure Mismatch is
10158 begin
10159 Error_Msg_Sloc := Sloc (Old_Name);
10160 Error_Pragma_Arg
10161 ("external name does not match that given #",
10162 Arg_External);
10163 end Mismatch;
10165 -- Start of processing for Check_Matching_Internal_Names
10167 begin
10168 if String_Length (S1) /= String_Length (S2) then
10169 Mismatch;
10171 else
10172 for J in 1 .. String_Length (S1) loop
10173 if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
10174 Mismatch;
10175 end if;
10176 end loop;
10177 end if;
10178 end Check_Matching_Internal_Names;
10180 -- Otherwise set the given name
10182 else
10183 Set_Encoded_Interface_Name (Internal_Ent, New_Name);
10184 Check_Duplicated_Export_Name (New_Name);
10185 end if;
10186 end Set_Extended_Import_Export_External_Name;
10188 ------------------
10189 -- Set_Imported --
10190 ------------------
10192 procedure Set_Imported (E : Entity_Id) is
10193 begin
10194 -- Error message if already imported or exported
10196 if Is_Exported (E) or else Is_Imported (E) then
10198 -- Error if being set Exported twice
10200 if Is_Exported (E) then
10201 Error_Msg_NE ("entity& was previously exported", N, E);
10203 -- Ignore error in CodePeer mode where we treat all imported
10204 -- subprograms as unknown.
10206 elsif CodePeer_Mode then
10207 goto OK;
10209 -- OK if Import/Interface case
10211 elsif Import_Interface_Present (N) then
10212 goto OK;
10214 -- Error if being set Imported twice
10216 else
10217 Error_Msg_NE ("entity& was previously imported", N, E);
10218 end if;
10220 Error_Msg_Name_1 := Pname;
10221 Error_Msg_N
10222 ("\(pragma% applies to all previous entities)", N);
10224 Error_Msg_Sloc := Sloc (E);
10225 Error_Msg_NE ("\import not allowed for& declared#", N, E);
10227 -- Here if not previously imported or exported, OK to import
10229 else
10230 Set_Is_Imported (E);
10232 -- For subprogram, set Import_Pragma field
10234 if Is_Subprogram (E) then
10235 Set_Import_Pragma (E, N);
10236 end if;
10238 -- If the entity is an object that is not at the library level,
10239 -- then it is statically allocated. We do not worry about objects
10240 -- with address clauses in this context since they are not really
10241 -- imported in the linker sense.
10243 if Is_Object (E)
10244 and then not Is_Library_Level_Entity (E)
10245 and then No (Address_Clause (E))
10246 then
10247 Set_Is_Statically_Allocated (E);
10248 end if;
10249 end if;
10251 <<OK>> null;
10252 end Set_Imported;
10254 -------------------------
10255 -- Set_Mechanism_Value --
10256 -------------------------
10258 -- Note: the mechanism name has not been analyzed (and cannot indeed be
10259 -- analyzed, since it is semantic nonsense), so we get it in the exact
10260 -- form created by the parser.
10262 procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
10263 procedure Bad_Mechanism;
10264 pragma No_Return (Bad_Mechanism);
10265 -- Signal bad mechanism name
10267 -------------------------
10268 -- Bad_Mechanism_Value --
10269 -------------------------
10271 procedure Bad_Mechanism is
10272 begin
10273 Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
10274 end Bad_Mechanism;
10276 -- Start of processing for Set_Mechanism_Value
10278 begin
10279 if Mechanism (Ent) /= Default_Mechanism then
10280 Error_Msg_NE
10281 ("mechanism for & has already been set", Mech_Name, Ent);
10282 end if;
10284 -- MECHANISM_NAME ::= value | reference
10286 if Nkind (Mech_Name) = N_Identifier then
10287 if Chars (Mech_Name) = Name_Value then
10288 Set_Mechanism (Ent, By_Copy);
10289 return;
10291 elsif Chars (Mech_Name) = Name_Reference then
10292 Set_Mechanism (Ent, By_Reference);
10293 return;
10295 elsif Chars (Mech_Name) = Name_Copy then
10296 Error_Pragma_Arg
10297 ("bad mechanism name, Value assumed", Mech_Name);
10299 else
10300 Bad_Mechanism;
10301 end if;
10303 else
10304 Bad_Mechanism;
10305 end if;
10306 end Set_Mechanism_Value;
10308 --------------------------
10309 -- Set_Rational_Profile --
10310 --------------------------
10312 -- The Rational profile includes Implicit_Packing, Use_Vads_Size, and
10313 -- extension to the semantics of renaming declarations.
10315 procedure Set_Rational_Profile is
10316 begin
10317 Implicit_Packing := True;
10318 Overriding_Renamings := True;
10319 Use_VADS_Size := True;
10320 end Set_Rational_Profile;
10322 ---------------------------
10323 -- Set_Ravenscar_Profile --
10324 ---------------------------
10326 -- The tasks to be done here are
10328 -- Set required policies
10330 -- pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
10331 -- (For Ravenscar and GNAT_Extended_Ravenscar profiles)
10332 -- pragma Task_Dispatching_Policy (EDF_Across_Priorities)
10333 -- (For GNAT_Ravenscar_EDF profile)
10334 -- pragma Locking_Policy (Ceiling_Locking)
10336 -- Set Detect_Blocking mode
10338 -- Set required restrictions (see System.Rident for detailed list)
10340 -- Set the No_Dependence rules
10341 -- No_Dependence => Ada.Asynchronous_Task_Control
10342 -- No_Dependence => Ada.Calendar
10343 -- No_Dependence => Ada.Execution_Time.Group_Budget
10344 -- No_Dependence => Ada.Execution_Time.Timers
10345 -- No_Dependence => Ada.Task_Attributes
10346 -- No_Dependence => System.Multiprocessors.Dispatching_Domains
10348 procedure Set_Ravenscar_Profile (Profile : Profile_Name; N : Node_Id) is
10349 procedure Set_Error_Msg_To_Profile_Name;
10350 -- Set Error_Msg_String and Error_Msg_Strlen to the name of the
10351 -- profile.
10353 -----------------------------------
10354 -- Set_Error_Msg_To_Profile_Name --
10355 -----------------------------------
10357 procedure Set_Error_Msg_To_Profile_Name is
10358 Prof_Nam : constant Node_Id :=
10359 Get_Pragma_Arg
10360 (First (Pragma_Argument_Associations (N)));
10362 begin
10363 Get_Name_String (Chars (Prof_Nam));
10364 Adjust_Name_Case (Global_Name_Buffer, Sloc (Prof_Nam));
10365 Error_Msg_Strlen := Name_Len;
10366 Error_Msg_String (1 .. Name_Len) := Name_Buffer (1 .. Name_Len);
10367 end Set_Error_Msg_To_Profile_Name;
10369 -- Local variables
10371 Nod : Node_Id;
10372 Pref : Node_Id;
10373 Pref_Id : Node_Id;
10374 Sel_Id : Node_Id;
10376 Profile_Dispatching_Policy : Character;
10378 -- Start of processing for Set_Ravenscar_Profile
10380 begin
10381 -- pragma Task_Dispatching_Policy (EDF_Across_Priorities)
10383 if Profile = GNAT_Ravenscar_EDF then
10384 Profile_Dispatching_Policy := 'E';
10386 -- pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
10388 else
10389 Profile_Dispatching_Policy := 'F';
10390 end if;
10392 if Task_Dispatching_Policy /= ' '
10393 and then Task_Dispatching_Policy /= Profile_Dispatching_Policy
10394 then
10395 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
10396 Set_Error_Msg_To_Profile_Name;
10397 Error_Pragma ("Profile (~) incompatible with policy#");
10399 -- Set the FIFO_Within_Priorities policy, but always preserve
10400 -- System_Location since we like the error message with the run time
10401 -- name.
10403 else
10404 Task_Dispatching_Policy := Profile_Dispatching_Policy;
10406 if Task_Dispatching_Policy_Sloc /= System_Location then
10407 Task_Dispatching_Policy_Sloc := Loc;
10408 end if;
10409 end if;
10411 -- pragma Locking_Policy (Ceiling_Locking)
10413 if Locking_Policy /= ' '
10414 and then Locking_Policy /= 'C'
10415 then
10416 Error_Msg_Sloc := Locking_Policy_Sloc;
10417 Set_Error_Msg_To_Profile_Name;
10418 Error_Pragma ("Profile (~) incompatible with policy#");
10420 -- Set the Ceiling_Locking policy, but preserve System_Location since
10421 -- we like the error message with the run time name.
10423 else
10424 Locking_Policy := 'C';
10426 if Locking_Policy_Sloc /= System_Location then
10427 Locking_Policy_Sloc := Loc;
10428 end if;
10429 end if;
10431 -- pragma Detect_Blocking
10433 Detect_Blocking := True;
10435 -- Set the corresponding restrictions
10437 Set_Profile_Restrictions
10438 (Profile, N, Warn => Treat_Restrictions_As_Warnings);
10440 -- Set the No_Dependence restrictions
10442 -- The following No_Dependence restrictions:
10443 -- No_Dependence => Ada.Asynchronous_Task_Control
10444 -- No_Dependence => Ada.Calendar
10445 -- No_Dependence => Ada.Task_Attributes
10446 -- are already set by previous call to Set_Profile_Restrictions.
10448 -- Set the following restrictions which were added to Ada 2005:
10449 -- No_Dependence => Ada.Execution_Time.Group_Budget
10450 -- No_Dependence => Ada.Execution_Time.Timers
10452 if Ada_Version >= Ada_2005 then
10453 Pref_Id := Make_Identifier (Loc, Name_Find ("ada"));
10454 Sel_Id := Make_Identifier (Loc, Name_Find ("execution_time"));
10456 Pref :=
10457 Make_Selected_Component
10458 (Sloc => Loc,
10459 Prefix => Pref_Id,
10460 Selector_Name => Sel_Id);
10462 Sel_Id := Make_Identifier (Loc, Name_Find ("group_budgets"));
10464 Nod :=
10465 Make_Selected_Component
10466 (Sloc => Loc,
10467 Prefix => Pref,
10468 Selector_Name => Sel_Id);
10470 Set_Restriction_No_Dependence
10471 (Unit => Nod,
10472 Warn => Treat_Restrictions_As_Warnings,
10473 Profile => Ravenscar);
10475 Sel_Id := Make_Identifier (Loc, Name_Find ("timers"));
10477 Nod :=
10478 Make_Selected_Component
10479 (Sloc => Loc,
10480 Prefix => Pref,
10481 Selector_Name => Sel_Id);
10483 Set_Restriction_No_Dependence
10484 (Unit => Nod,
10485 Warn => Treat_Restrictions_As_Warnings,
10486 Profile => Ravenscar);
10487 end if;
10489 -- Set the following restriction which was added to Ada 2012 (see
10490 -- AI-0171):
10491 -- No_Dependence => System.Multiprocessors.Dispatching_Domains
10493 if Ada_Version >= Ada_2012 then
10494 Pref_Id := Make_Identifier (Loc, Name_Find ("system"));
10495 Sel_Id := Make_Identifier (Loc, Name_Find ("multiprocessors"));
10497 Pref :=
10498 Make_Selected_Component
10499 (Sloc => Loc,
10500 Prefix => Pref_Id,
10501 Selector_Name => Sel_Id);
10503 Sel_Id := Make_Identifier (Loc, Name_Find ("dispatching_domains"));
10505 Nod :=
10506 Make_Selected_Component
10507 (Sloc => Loc,
10508 Prefix => Pref,
10509 Selector_Name => Sel_Id);
10511 Set_Restriction_No_Dependence
10512 (Unit => Nod,
10513 Warn => Treat_Restrictions_As_Warnings,
10514 Profile => Ravenscar);
10515 end if;
10516 end Set_Ravenscar_Profile;
10518 -- Start of processing for Analyze_Pragma
10520 begin
10521 -- The following code is a defense against recursion. Not clear that
10522 -- this can happen legitimately, but perhaps some error situations can
10523 -- cause it, and we did see this recursion during testing.
10525 if Analyzed (N) then
10526 return;
10527 else
10528 Set_Analyzed (N);
10529 end if;
10531 Check_Restriction_No_Use_Of_Pragma (N);
10533 -- Ignore pragma if Ignore_Pragma applies. Also ignore pragma
10534 -- Default_Scalar_Storage_Order if the -gnatI switch was given.
10536 if Should_Ignore_Pragma_Sem (N)
10537 or else (Prag_Id = Pragma_Default_Scalar_Storage_Order
10538 and then Ignore_Rep_Clauses)
10539 then
10540 return;
10541 end if;
10543 -- Deal with unrecognized pragma
10545 if not Is_Pragma_Name (Pname) then
10546 if Warn_On_Unrecognized_Pragma then
10547 Error_Msg_Name_1 := Pname;
10548 Error_Msg_N ("?g?unrecognized pragma%!", Pragma_Identifier (N));
10550 for PN in First_Pragma_Name .. Last_Pragma_Name loop
10551 if Is_Bad_Spelling_Of (Pname, PN) then
10552 Error_Msg_Name_1 := PN;
10553 Error_Msg_N -- CODEFIX
10554 ("\?g?possible misspelling of %!", Pragma_Identifier (N));
10555 exit;
10556 end if;
10557 end loop;
10558 end if;
10560 return;
10561 end if;
10563 -- Here to start processing for recognized pragma
10565 Pname := Original_Aspect_Pragma_Name (N);
10567 -- Capture setting of Opt.Uneval_Old
10569 case Opt.Uneval_Old is
10570 when 'A' =>
10571 Set_Uneval_Old_Accept (N);
10573 when 'E' =>
10574 null;
10576 when 'W' =>
10577 Set_Uneval_Old_Warn (N);
10579 when others =>
10580 raise Program_Error;
10581 end case;
10583 -- Check applicable policy. We skip this if Is_Checked or Is_Ignored
10584 -- is already set, indicating that we have already checked the policy
10585 -- at the right point. This happens for example in the case of a pragma
10586 -- that is derived from an Aspect.
10588 if Is_Ignored (N) or else Is_Checked (N) then
10589 null;
10591 -- For a pragma that is a rewriting of another pragma, copy the
10592 -- Is_Checked/Is_Ignored status from the rewritten pragma.
10594 elsif Is_Rewrite_Substitution (N)
10595 and then Nkind (Original_Node (N)) = N_Pragma
10596 and then Original_Node (N) /= N
10597 then
10598 Set_Is_Ignored (N, Is_Ignored (Original_Node (N)));
10599 Set_Is_Checked (N, Is_Checked (Original_Node (N)));
10601 -- Otherwise query the applicable policy at this point
10603 else
10604 Check_Applicable_Policy (N);
10606 -- If pragma is disabled, rewrite as NULL and skip analysis
10608 if Is_Disabled (N) then
10609 Rewrite (N, Make_Null_Statement (Loc));
10610 Analyze (N);
10611 raise Pragma_Exit;
10612 end if;
10613 end if;
10615 -- Preset arguments
10617 Arg_Count := 0;
10618 Arg1 := Empty;
10619 Arg2 := Empty;
10620 Arg3 := Empty;
10621 Arg4 := Empty;
10623 if Present (Pragma_Argument_Associations (N)) then
10624 Arg_Count := List_Length (Pragma_Argument_Associations (N));
10625 Arg1 := First (Pragma_Argument_Associations (N));
10627 if Present (Arg1) then
10628 Arg2 := Next (Arg1);
10630 if Present (Arg2) then
10631 Arg3 := Next (Arg2);
10633 if Present (Arg3) then
10634 Arg4 := Next (Arg3);
10635 end if;
10636 end if;
10637 end if;
10638 end if;
10640 -- An enumeration type defines the pragmas that are supported by the
10641 -- implementation. Get_Pragma_Id (in package Prag) transforms a name
10642 -- into the corresponding enumeration value for the following case.
10644 case Prag_Id is
10646 -----------------
10647 -- Abort_Defer --
10648 -----------------
10650 -- pragma Abort_Defer;
10652 when Pragma_Abort_Defer =>
10653 GNAT_Pragma;
10654 Check_Arg_Count (0);
10656 -- The only required semantic processing is to check the
10657 -- placement. This pragma must appear at the start of the
10658 -- statement sequence of a handled sequence of statements.
10660 if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
10661 or else N /= First (Statements (Parent (N)))
10662 then
10663 Pragma_Misplaced;
10664 end if;
10666 --------------------
10667 -- Abstract_State --
10668 --------------------
10670 -- pragma Abstract_State (ABSTRACT_STATE_LIST);
10672 -- ABSTRACT_STATE_LIST ::=
10673 -- null
10674 -- | STATE_NAME_WITH_OPTIONS
10675 -- | (STATE_NAME_WITH_OPTIONS {, STATE_NAME_WITH_OPTIONS})
10677 -- STATE_NAME_WITH_OPTIONS ::=
10678 -- STATE_NAME
10679 -- | (STATE_NAME with OPTION_LIST)
10681 -- OPTION_LIST ::= OPTION {, OPTION}
10683 -- OPTION ::=
10684 -- SIMPLE_OPTION
10685 -- | NAME_VALUE_OPTION
10687 -- SIMPLE_OPTION ::= Ghost | Synchronous
10689 -- NAME_VALUE_OPTION ::=
10690 -- Part_Of => ABSTRACT_STATE
10691 -- | External [=> EXTERNAL_PROPERTY_LIST]
10693 -- EXTERNAL_PROPERTY_LIST ::=
10694 -- EXTERNAL_PROPERTY
10695 -- | (EXTERNAL_PROPERTY {, EXTERNAL_PROPERTY})
10697 -- EXTERNAL_PROPERTY ::=
10698 -- Async_Readers [=> boolean_EXPRESSION]
10699 -- | Async_Writers [=> boolean_EXPRESSION]
10700 -- | Effective_Reads [=> boolean_EXPRESSION]
10701 -- | Effective_Writes [=> boolean_EXPRESSION]
10702 -- others => boolean_EXPRESSION
10704 -- STATE_NAME ::= defining_identifier
10706 -- ABSTRACT_STATE ::= name
10708 -- Characteristics:
10710 -- * Analysis - The annotation is fully analyzed immediately upon
10711 -- elaboration as it cannot forward reference entities.
10713 -- * Expansion - None.
10715 -- * Template - The annotation utilizes the generic template of the
10716 -- related package declaration.
10718 -- * Globals - The annotation cannot reference global entities.
10720 -- * Instance - The annotation is instantiated automatically when
10721 -- the related generic package is instantiated.
10723 when Pragma_Abstract_State => Abstract_State : declare
10724 Missing_Parentheses : Boolean := False;
10725 -- Flag set when a state declaration with options is not properly
10726 -- parenthesized.
10728 -- Flags used to verify the consistency of states
10730 Non_Null_Seen : Boolean := False;
10731 Null_Seen : Boolean := False;
10733 procedure Analyze_Abstract_State
10734 (State : Node_Id;
10735 Pack_Id : Entity_Id);
10736 -- Verify the legality of a single state declaration. Create and
10737 -- decorate a state abstraction entity and introduce it into the
10738 -- visibility chain. Pack_Id denotes the entity or the related
10739 -- package where pragma Abstract_State appears.
10741 procedure Malformed_State_Error (State : Node_Id);
10742 -- Emit an error concerning the illegal declaration of abstract
10743 -- state State. This routine diagnoses syntax errors that lead to
10744 -- a different parse tree. The error is issued regardless of the
10745 -- SPARK mode in effect.
10747 ----------------------------
10748 -- Analyze_Abstract_State --
10749 ----------------------------
10751 procedure Analyze_Abstract_State
10752 (State : Node_Id;
10753 Pack_Id : Entity_Id)
10755 -- Flags used to verify the consistency of options
10757 AR_Seen : Boolean := False;
10758 AW_Seen : Boolean := False;
10759 ER_Seen : Boolean := False;
10760 EW_Seen : Boolean := False;
10761 External_Seen : Boolean := False;
10762 Ghost_Seen : Boolean := False;
10763 Others_Seen : Boolean := False;
10764 Part_Of_Seen : Boolean := False;
10765 Synchronous_Seen : Boolean := False;
10767 -- Flags used to store the static value of all external states'
10768 -- expressions.
10770 AR_Val : Boolean := False;
10771 AW_Val : Boolean := False;
10772 ER_Val : Boolean := False;
10773 EW_Val : Boolean := False;
10775 State_Id : Entity_Id := Empty;
10776 -- The entity to be generated for the current state declaration
10778 procedure Analyze_External_Option (Opt : Node_Id);
10779 -- Verify the legality of option External
10781 procedure Analyze_External_Property
10782 (Prop : Node_Id;
10783 Expr : Node_Id := Empty);
10784 -- Verify the legailty of a single external property. Prop
10785 -- denotes the external property. Expr is the expression used
10786 -- to set the property.
10788 procedure Analyze_Part_Of_Option (Opt : Node_Id);
10789 -- Verify the legality of option Part_Of
10791 procedure Check_Duplicate_Option
10792 (Opt : Node_Id;
10793 Status : in out Boolean);
10794 -- Flag Status denotes whether a particular option has been
10795 -- seen while processing a state. This routine verifies that
10796 -- Opt is not a duplicate option and sets the flag Status
10797 -- (SPARK RM 7.1.4(1)).
10799 procedure Check_Duplicate_Property
10800 (Prop : Node_Id;
10801 Status : in out Boolean);
10802 -- Flag Status denotes whether a particular property has been
10803 -- seen while processing option External. This routine verifies
10804 -- that Prop is not a duplicate property and sets flag Status.
10805 -- Opt is not a duplicate property and sets the flag Status.
10806 -- (SPARK RM 7.1.4(2))
10808 procedure Check_Ghost_Synchronous;
10809 -- Ensure that the abstract state is not subject to both Ghost
10810 -- and Synchronous simple options. Emit an error if this is the
10811 -- case.
10813 procedure Create_Abstract_State
10814 (Nam : Name_Id;
10815 Decl : Node_Id;
10816 Loc : Source_Ptr;
10817 Is_Null : Boolean);
10818 -- Generate an abstract state entity with name Nam and enter it
10819 -- into visibility. Decl is the "declaration" of the state as
10820 -- it appears in pragma Abstract_State. Loc is the location of
10821 -- the related state "declaration". Flag Is_Null should be set
10822 -- when the associated Abstract_State pragma defines a null
10823 -- state.
10825 -----------------------------
10826 -- Analyze_External_Option --
10827 -----------------------------
10829 procedure Analyze_External_Option (Opt : Node_Id) is
10830 Errors : constant Nat := Serious_Errors_Detected;
10831 Prop : Node_Id;
10832 Props : Node_Id := Empty;
10834 begin
10835 if Nkind (Opt) = N_Component_Association then
10836 Props := Expression (Opt);
10837 end if;
10839 -- External state with properties
10841 if Present (Props) then
10843 -- Multiple properties appear as an aggregate
10845 if Nkind (Props) = N_Aggregate then
10847 -- Simple property form
10849 Prop := First (Expressions (Props));
10850 while Present (Prop) loop
10851 Analyze_External_Property (Prop);
10852 Next (Prop);
10853 end loop;
10855 -- Property with expression form
10857 Prop := First (Component_Associations (Props));
10858 while Present (Prop) loop
10859 Analyze_External_Property
10860 (Prop => First (Choices (Prop)),
10861 Expr => Expression (Prop));
10863 Next (Prop);
10864 end loop;
10866 -- Single property
10868 else
10869 Analyze_External_Property (Props);
10870 end if;
10872 -- An external state defined without any properties defaults
10873 -- all properties to True.
10875 else
10876 AR_Val := True;
10877 AW_Val := True;
10878 ER_Val := True;
10879 EW_Val := True;
10880 end if;
10882 -- Once all external properties have been processed, verify
10883 -- their mutual interaction. Do not perform the check when
10884 -- at least one of the properties is illegal as this will
10885 -- produce a bogus error.
10887 if Errors = Serious_Errors_Detected then
10888 Check_External_Properties
10889 (State, AR_Val, AW_Val, ER_Val, EW_Val);
10890 end if;
10891 end Analyze_External_Option;
10893 -------------------------------
10894 -- Analyze_External_Property --
10895 -------------------------------
10897 procedure Analyze_External_Property
10898 (Prop : Node_Id;
10899 Expr : Node_Id := Empty)
10901 Expr_Val : Boolean;
10903 begin
10904 -- Check the placement of "others" (if available)
10906 if Nkind (Prop) = N_Others_Choice then
10907 if Others_Seen then
10908 SPARK_Msg_N
10909 ("only one others choice allowed in option External",
10910 Prop);
10911 else
10912 Others_Seen := True;
10913 end if;
10915 elsif Others_Seen then
10916 SPARK_Msg_N
10917 ("others must be the last property in option External",
10918 Prop);
10920 -- The only remaining legal options are the four predefined
10921 -- external properties.
10923 elsif Nkind (Prop) = N_Identifier
10924 and then Nam_In (Chars (Prop), Name_Async_Readers,
10925 Name_Async_Writers,
10926 Name_Effective_Reads,
10927 Name_Effective_Writes)
10928 then
10929 null;
10931 -- Otherwise the construct is not a valid property
10933 else
10934 SPARK_Msg_N ("invalid external state property", Prop);
10935 return;
10936 end if;
10938 -- Ensure that the expression of the external state property
10939 -- is static Boolean (if applicable) (SPARK RM 7.1.2(5)).
10941 if Present (Expr) then
10942 Analyze_And_Resolve (Expr, Standard_Boolean);
10944 if Is_OK_Static_Expression (Expr) then
10945 Expr_Val := Is_True (Expr_Value (Expr));
10946 else
10947 SPARK_Msg_N
10948 ("expression of external state property must be "
10949 & "static", Expr);
10950 end if;
10952 -- The lack of expression defaults the property to True
10954 else
10955 Expr_Val := True;
10956 end if;
10958 -- Named properties
10960 if Nkind (Prop) = N_Identifier then
10961 if Chars (Prop) = Name_Async_Readers then
10962 Check_Duplicate_Property (Prop, AR_Seen);
10963 AR_Val := Expr_Val;
10965 elsif Chars (Prop) = Name_Async_Writers then
10966 Check_Duplicate_Property (Prop, AW_Seen);
10967 AW_Val := Expr_Val;
10969 elsif Chars (Prop) = Name_Effective_Reads then
10970 Check_Duplicate_Property (Prop, ER_Seen);
10971 ER_Val := Expr_Val;
10973 else
10974 Check_Duplicate_Property (Prop, EW_Seen);
10975 EW_Val := Expr_Val;
10976 end if;
10978 -- The handling of property "others" must take into account
10979 -- all other named properties that have been encountered so
10980 -- far. Only those that have not been seen are affected by
10981 -- "others".
10983 else
10984 if not AR_Seen then
10985 AR_Val := Expr_Val;
10986 end if;
10988 if not AW_Seen then
10989 AW_Val := Expr_Val;
10990 end if;
10992 if not ER_Seen then
10993 ER_Val := Expr_Val;
10994 end if;
10996 if not EW_Seen then
10997 EW_Val := Expr_Val;
10998 end if;
10999 end if;
11000 end Analyze_External_Property;
11002 ----------------------------
11003 -- Analyze_Part_Of_Option --
11004 ----------------------------
11006 procedure Analyze_Part_Of_Option (Opt : Node_Id) is
11007 Encap : constant Node_Id := Expression (Opt);
11008 Constits : Elist_Id;
11009 Encap_Id : Entity_Id;
11010 Legal : Boolean;
11012 begin
11013 Check_Duplicate_Option (Opt, Part_Of_Seen);
11015 Analyze_Part_Of
11016 (Indic => First (Choices (Opt)),
11017 Item_Id => State_Id,
11018 Encap => Encap,
11019 Encap_Id => Encap_Id,
11020 Legal => Legal);
11022 -- The Part_Of indicator transforms the abstract state into
11023 -- a constituent of the encapsulating state or single
11024 -- concurrent type.
11026 if Legal then
11027 pragma Assert (Present (Encap_Id));
11028 Constits := Part_Of_Constituents (Encap_Id);
11030 if No (Constits) then
11031 Constits := New_Elmt_List;
11032 Set_Part_Of_Constituents (Encap_Id, Constits);
11033 end if;
11035 Append_Elmt (State_Id, Constits);
11036 Set_Encapsulating_State (State_Id, Encap_Id);
11037 end if;
11038 end Analyze_Part_Of_Option;
11040 ----------------------------
11041 -- Check_Duplicate_Option --
11042 ----------------------------
11044 procedure Check_Duplicate_Option
11045 (Opt : Node_Id;
11046 Status : in out Boolean)
11048 begin
11049 if Status then
11050 SPARK_Msg_N ("duplicate state option", Opt);
11051 end if;
11053 Status := True;
11054 end Check_Duplicate_Option;
11056 ------------------------------
11057 -- Check_Duplicate_Property --
11058 ------------------------------
11060 procedure Check_Duplicate_Property
11061 (Prop : Node_Id;
11062 Status : in out Boolean)
11064 begin
11065 if Status then
11066 SPARK_Msg_N ("duplicate external property", Prop);
11067 end if;
11069 Status := True;
11070 end Check_Duplicate_Property;
11072 -----------------------------
11073 -- Check_Ghost_Synchronous --
11074 -----------------------------
11076 procedure Check_Ghost_Synchronous is
11077 begin
11078 -- A synchronized abstract state cannot be Ghost and vice
11079 -- versa (SPARK RM 6.9(19)).
11081 if Ghost_Seen and Synchronous_Seen then
11082 SPARK_Msg_N ("synchronized state cannot be ghost", State);
11083 end if;
11084 end Check_Ghost_Synchronous;
11086 ---------------------------
11087 -- Create_Abstract_State --
11088 ---------------------------
11090 procedure Create_Abstract_State
11091 (Nam : Name_Id;
11092 Decl : Node_Id;
11093 Loc : Source_Ptr;
11094 Is_Null : Boolean)
11096 begin
11097 -- The abstract state may be semi-declared when the related
11098 -- package was withed through a limited with clause. In that
11099 -- case reuse the entity to fully declare the state.
11101 if Present (Decl) and then Present (Entity (Decl)) then
11102 State_Id := Entity (Decl);
11104 -- Otherwise the elaboration of pragma Abstract_State
11105 -- declares the state.
11107 else
11108 State_Id := Make_Defining_Identifier (Loc, Nam);
11110 if Present (Decl) then
11111 Set_Entity (Decl, State_Id);
11112 end if;
11113 end if;
11115 -- Null states never come from source
11117 Set_Comes_From_Source (State_Id, not Is_Null);
11118 Set_Parent (State_Id, State);
11119 Set_Ekind (State_Id, E_Abstract_State);
11120 Set_Etype (State_Id, Standard_Void_Type);
11121 Set_Encapsulating_State (State_Id, Empty);
11123 -- An abstract state declared within a Ghost region becomes
11124 -- Ghost (SPARK RM 6.9(2)).
11126 if Ghost_Mode > None or else Is_Ghost_Entity (Pack_Id) then
11127 Set_Is_Ghost_Entity (State_Id);
11128 end if;
11130 -- Establish a link between the state declaration and the
11131 -- abstract state entity. Note that a null state remains as
11132 -- N_Null and does not carry any linkages.
11134 if not Is_Null then
11135 if Present (Decl) then
11136 Set_Entity (Decl, State_Id);
11137 Set_Etype (Decl, Standard_Void_Type);
11138 end if;
11140 -- Every non-null state must be defined, nameable and
11141 -- resolvable.
11143 Push_Scope (Pack_Id);
11144 Generate_Definition (State_Id);
11145 Enter_Name (State_Id);
11146 Pop_Scope;
11147 end if;
11148 end Create_Abstract_State;
11150 -- Local variables
11152 Opt : Node_Id;
11153 Opt_Nam : Node_Id;
11155 -- Start of processing for Analyze_Abstract_State
11157 begin
11158 -- A package with a null abstract state is not allowed to
11159 -- declare additional states.
11161 if Null_Seen then
11162 SPARK_Msg_NE
11163 ("package & has null abstract state", State, Pack_Id);
11165 -- Null states appear as internally generated entities
11167 elsif Nkind (State) = N_Null then
11168 Create_Abstract_State
11169 (Nam => New_Internal_Name ('S'),
11170 Decl => Empty,
11171 Loc => Sloc (State),
11172 Is_Null => True);
11173 Null_Seen := True;
11175 -- Catch a case where a null state appears in a list of
11176 -- non-null states.
11178 if Non_Null_Seen then
11179 SPARK_Msg_NE
11180 ("package & has non-null abstract state",
11181 State, Pack_Id);
11182 end if;
11184 -- Simple state declaration
11186 elsif Nkind (State) = N_Identifier then
11187 Create_Abstract_State
11188 (Nam => Chars (State),
11189 Decl => State,
11190 Loc => Sloc (State),
11191 Is_Null => False);
11192 Non_Null_Seen := True;
11194 -- State declaration with various options. This construct
11195 -- appears as an extension aggregate in the tree.
11197 elsif Nkind (State) = N_Extension_Aggregate then
11198 if Nkind (Ancestor_Part (State)) = N_Identifier then
11199 Create_Abstract_State
11200 (Nam => Chars (Ancestor_Part (State)),
11201 Decl => Ancestor_Part (State),
11202 Loc => Sloc (Ancestor_Part (State)),
11203 Is_Null => False);
11204 Non_Null_Seen := True;
11205 else
11206 SPARK_Msg_N
11207 ("state name must be an identifier",
11208 Ancestor_Part (State));
11209 end if;
11211 -- Options External, Ghost and Synchronous appear as
11212 -- expressions.
11214 Opt := First (Expressions (State));
11215 while Present (Opt) loop
11216 if Nkind (Opt) = N_Identifier then
11218 -- External
11220 if Chars (Opt) = Name_External then
11221 Check_Duplicate_Option (Opt, External_Seen);
11222 Analyze_External_Option (Opt);
11224 -- Ghost
11226 elsif Chars (Opt) = Name_Ghost then
11227 Check_Duplicate_Option (Opt, Ghost_Seen);
11228 Check_Ghost_Synchronous;
11230 if Present (State_Id) then
11231 Set_Is_Ghost_Entity (State_Id);
11232 end if;
11234 -- Synchronous
11236 elsif Chars (Opt) = Name_Synchronous then
11237 Check_Duplicate_Option (Opt, Synchronous_Seen);
11238 Check_Ghost_Synchronous;
11240 -- Option Part_Of without an encapsulating state is
11241 -- illegal (SPARK RM 7.1.4(9)).
11243 elsif Chars (Opt) = Name_Part_Of then
11244 SPARK_Msg_N
11245 ("indicator Part_Of must denote abstract state, "
11246 & "single protected type or single task type",
11247 Opt);
11249 -- Do not emit an error message when a previous state
11250 -- declaration with options was not parenthesized as
11251 -- the option is actually another state declaration.
11253 -- with Abstract_State
11254 -- (State_1 with ..., -- missing parentheses
11255 -- (State_2 with ...),
11256 -- State_3) -- ok state declaration
11258 elsif Missing_Parentheses then
11259 null;
11261 -- Otherwise the option is not allowed. Note that it
11262 -- is not possible to distinguish between an option
11263 -- and a state declaration when a previous state with
11264 -- options not properly parentheses.
11266 -- with Abstract_State
11267 -- (State_1 with ..., -- missing parentheses
11268 -- State_2); -- could be an option
11270 else
11271 SPARK_Msg_N
11272 ("simple option not allowed in state declaration",
11273 Opt);
11274 end if;
11276 -- Catch a case where missing parentheses around a state
11277 -- declaration with options cause a subsequent state
11278 -- declaration with options to be treated as an option.
11280 -- with Abstract_State
11281 -- (State_1 with ..., -- missing parentheses
11282 -- (State_2 with ...))
11284 elsif Nkind (Opt) = N_Extension_Aggregate then
11285 Missing_Parentheses := True;
11286 SPARK_Msg_N
11287 ("state declaration must be parenthesized",
11288 Ancestor_Part (State));
11290 -- Otherwise the option is malformed
11292 else
11293 SPARK_Msg_N ("malformed option", Opt);
11294 end if;
11296 Next (Opt);
11297 end loop;
11299 -- Options External and Part_Of appear as component
11300 -- associations.
11302 Opt := First (Component_Associations (State));
11303 while Present (Opt) loop
11304 Opt_Nam := First (Choices (Opt));
11306 if Nkind (Opt_Nam) = N_Identifier then
11307 if Chars (Opt_Nam) = Name_External then
11308 Analyze_External_Option (Opt);
11310 elsif Chars (Opt_Nam) = Name_Part_Of then
11311 Analyze_Part_Of_Option (Opt);
11313 else
11314 SPARK_Msg_N ("invalid state option", Opt);
11315 end if;
11316 else
11317 SPARK_Msg_N ("invalid state option", Opt);
11318 end if;
11320 Next (Opt);
11321 end loop;
11323 -- Any other attempt to declare a state is illegal
11325 else
11326 Malformed_State_Error (State);
11327 return;
11328 end if;
11330 -- Guard against a junk state. In such cases no entity is
11331 -- generated and the subsequent checks cannot be applied.
11333 if Present (State_Id) then
11335 -- Verify whether the state does not introduce an illegal
11336 -- hidden state within a package subject to a null abstract
11337 -- state.
11339 Check_No_Hidden_State (State_Id);
11341 -- Check whether the lack of option Part_Of agrees with the
11342 -- placement of the abstract state with respect to the state
11343 -- space.
11345 if not Part_Of_Seen then
11346 Check_Missing_Part_Of (State_Id);
11347 end if;
11349 -- Associate the state with its related package
11351 if No (Abstract_States (Pack_Id)) then
11352 Set_Abstract_States (Pack_Id, New_Elmt_List);
11353 end if;
11355 Append_Elmt (State_Id, Abstract_States (Pack_Id));
11356 end if;
11357 end Analyze_Abstract_State;
11359 ---------------------------
11360 -- Malformed_State_Error --
11361 ---------------------------
11363 procedure Malformed_State_Error (State : Node_Id) is
11364 begin
11365 Error_Msg_N ("malformed abstract state declaration", State);
11367 -- An abstract state with a simple option is being declared
11368 -- with "=>" rather than the legal "with". The state appears
11369 -- as a component association.
11371 if Nkind (State) = N_Component_Association then
11372 Error_Msg_N ("\use WITH to specify simple option", State);
11373 end if;
11374 end Malformed_State_Error;
11376 -- Local variables
11378 Pack_Decl : Node_Id;
11379 Pack_Id : Entity_Id;
11380 State : Node_Id;
11381 States : Node_Id;
11383 -- Start of processing for Abstract_State
11385 begin
11386 GNAT_Pragma;
11387 Check_No_Identifiers;
11388 Check_Arg_Count (1);
11390 Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
11392 -- Ensure the proper placement of the pragma. Abstract states must
11393 -- be associated with a package declaration.
11395 if Nkind_In (Pack_Decl, N_Generic_Package_Declaration,
11396 N_Package_Declaration)
11397 then
11398 null;
11400 -- Otherwise the pragma is associated with an illegal construct
11402 else
11403 Pragma_Misplaced;
11404 return;
11405 end if;
11407 Pack_Id := Defining_Entity (Pack_Decl);
11409 -- A pragma that applies to a Ghost entity becomes Ghost for the
11410 -- purposes of legality checks and removal of ignored Ghost code.
11412 Mark_Ghost_Pragma (N, Pack_Id);
11413 Ensure_Aggregate_Form (Get_Argument (N, Pack_Id));
11415 -- Chain the pragma on the contract for completeness
11417 Add_Contract_Item (N, Pack_Id);
11419 -- The legality checks of pragmas Abstract_State, Initializes, and
11420 -- Initial_Condition are affected by the SPARK mode in effect. In
11421 -- addition, these three pragmas are subject to an inherent order:
11423 -- 1) Abstract_State
11424 -- 2) Initializes
11425 -- 3) Initial_Condition
11427 -- Analyze all these pragmas in the order outlined above
11429 Analyze_If_Present (Pragma_SPARK_Mode);
11430 States := Expression (Get_Argument (N, Pack_Id));
11432 -- Multiple non-null abstract states appear as an aggregate
11434 if Nkind (States) = N_Aggregate then
11435 State := First (Expressions (States));
11436 while Present (State) loop
11437 Analyze_Abstract_State (State, Pack_Id);
11438 Next (State);
11439 end loop;
11441 -- An abstract state with a simple option is being illegaly
11442 -- declared with "=>" rather than "with". In this case the
11443 -- state declaration appears as a component association.
11445 if Present (Component_Associations (States)) then
11446 State := First (Component_Associations (States));
11447 while Present (State) loop
11448 Malformed_State_Error (State);
11449 Next (State);
11450 end loop;
11451 end if;
11453 -- Various forms of a single abstract state. Note that these may
11454 -- include malformed state declarations.
11456 else
11457 Analyze_Abstract_State (States, Pack_Id);
11458 end if;
11460 Analyze_If_Present (Pragma_Initializes);
11461 Analyze_If_Present (Pragma_Initial_Condition);
11462 end Abstract_State;
11464 ------------
11465 -- Ada_83 --
11466 ------------
11468 -- pragma Ada_83;
11470 -- Note: this pragma also has some specific processing in Par.Prag
11471 -- because we want to set the Ada version mode during parsing.
11473 when Pragma_Ada_83 =>
11474 GNAT_Pragma;
11475 Check_Arg_Count (0);
11477 -- We really should check unconditionally for proper configuration
11478 -- pragma placement, since we really don't want mixed Ada modes
11479 -- within a single unit, and the GNAT reference manual has always
11480 -- said this was a configuration pragma, but we did not check and
11481 -- are hesitant to add the check now.
11483 -- However, we really cannot tolerate mixing Ada 2005 or Ada 2012
11484 -- with Ada 83 or Ada 95, so we must check if we are in Ada 2005
11485 -- or Ada 2012 mode.
11487 if Ada_Version >= Ada_2005 then
11488 Check_Valid_Configuration_Pragma;
11489 end if;
11491 -- Now set Ada 83 mode
11493 if Latest_Ada_Only then
11494 Error_Pragma ("??pragma% ignored");
11495 else
11496 Ada_Version := Ada_83;
11497 Ada_Version_Explicit := Ada_83;
11498 Ada_Version_Pragma := N;
11499 end if;
11501 ------------
11502 -- Ada_95 --
11503 ------------
11505 -- pragma Ada_95;
11507 -- Note: this pragma also has some specific processing in Par.Prag
11508 -- because we want to set the Ada 83 version mode during parsing.
11510 when Pragma_Ada_95 =>
11511 GNAT_Pragma;
11512 Check_Arg_Count (0);
11514 -- We really should check unconditionally for proper configuration
11515 -- pragma placement, since we really don't want mixed Ada modes
11516 -- within a single unit, and the GNAT reference manual has always
11517 -- said this was a configuration pragma, but we did not check and
11518 -- are hesitant to add the check now.
11520 -- However, we really cannot tolerate mixing Ada 2005 with Ada 83
11521 -- or Ada 95, so we must check if we are in Ada 2005 mode.
11523 if Ada_Version >= Ada_2005 then
11524 Check_Valid_Configuration_Pragma;
11525 end if;
11527 -- Now set Ada 95 mode
11529 if Latest_Ada_Only then
11530 Error_Pragma ("??pragma% ignored");
11531 else
11532 Ada_Version := Ada_95;
11533 Ada_Version_Explicit := Ada_95;
11534 Ada_Version_Pragma := N;
11535 end if;
11537 ---------------------
11538 -- Ada_05/Ada_2005 --
11539 ---------------------
11541 -- pragma Ada_05;
11542 -- pragma Ada_05 (LOCAL_NAME);
11544 -- pragma Ada_2005;
11545 -- pragma Ada_2005 (LOCAL_NAME):
11547 -- Note: these pragmas also have some specific processing in Par.Prag
11548 -- because we want to set the Ada 2005 version mode during parsing.
11550 -- The one argument form is used for managing the transition from
11551 -- Ada 95 to Ada 2005 in the run-time library. If an entity is marked
11552 -- as Ada_2005 only, then referencing the entity in Ada_83 or Ada_95
11553 -- mode will generate a warning. In addition, in Ada_83 or Ada_95
11554 -- mode, a preference rule is established which does not choose
11555 -- such an entity unless it is unambiguously specified. This avoids
11556 -- extra subprograms marked this way from generating ambiguities in
11557 -- otherwise legal pre-Ada_2005 programs. The one argument form is
11558 -- intended for exclusive use in the GNAT run-time library.
11560 when Pragma_Ada_05
11561 | Pragma_Ada_2005
11563 declare
11564 E_Id : Node_Id;
11566 begin
11567 GNAT_Pragma;
11569 if Arg_Count = 1 then
11570 Check_Arg_Is_Local_Name (Arg1);
11571 E_Id := Get_Pragma_Arg (Arg1);
11573 if Etype (E_Id) = Any_Type then
11574 return;
11575 end if;
11577 Set_Is_Ada_2005_Only (Entity (E_Id));
11578 Record_Rep_Item (Entity (E_Id), N);
11580 else
11581 Check_Arg_Count (0);
11583 -- For Ada_2005 we unconditionally enforce the documented
11584 -- configuration pragma placement, since we do not want to
11585 -- tolerate mixed modes in a unit involving Ada 2005. That
11586 -- would cause real difficulties for those cases where there
11587 -- are incompatibilities between Ada 95 and Ada 2005.
11589 Check_Valid_Configuration_Pragma;
11591 -- Now set appropriate Ada mode
11593 if Latest_Ada_Only then
11594 Error_Pragma ("??pragma% ignored");
11595 else
11596 Ada_Version := Ada_2005;
11597 Ada_Version_Explicit := Ada_2005;
11598 Ada_Version_Pragma := N;
11599 end if;
11600 end if;
11601 end;
11603 ---------------------
11604 -- Ada_12/Ada_2012 --
11605 ---------------------
11607 -- pragma Ada_12;
11608 -- pragma Ada_12 (LOCAL_NAME);
11610 -- pragma Ada_2012;
11611 -- pragma Ada_2012 (LOCAL_NAME):
11613 -- Note: these pragmas also have some specific processing in Par.Prag
11614 -- because we want to set the Ada 2012 version mode during parsing.
11616 -- The one argument form is used for managing the transition from Ada
11617 -- 2005 to Ada 2012 in the run-time library. If an entity is marked
11618 -- as Ada_201 only, then referencing the entity in any pre-Ada_2012
11619 -- mode will generate a warning. In addition, in any pre-Ada_2012
11620 -- mode, a preference rule is established which does not choose
11621 -- such an entity unless it is unambiguously specified. This avoids
11622 -- extra subprograms marked this way from generating ambiguities in
11623 -- otherwise legal pre-Ada_2012 programs. The one argument form is
11624 -- intended for exclusive use in the GNAT run-time library.
11626 when Pragma_Ada_12
11627 | Pragma_Ada_2012
11629 declare
11630 E_Id : Node_Id;
11632 begin
11633 GNAT_Pragma;
11635 if Arg_Count = 1 then
11636 Check_Arg_Is_Local_Name (Arg1);
11637 E_Id := Get_Pragma_Arg (Arg1);
11639 if Etype (E_Id) = Any_Type then
11640 return;
11641 end if;
11643 Set_Is_Ada_2012_Only (Entity (E_Id));
11644 Record_Rep_Item (Entity (E_Id), N);
11646 else
11647 Check_Arg_Count (0);
11649 -- For Ada_2012 we unconditionally enforce the documented
11650 -- configuration pragma placement, since we do not want to
11651 -- tolerate mixed modes in a unit involving Ada 2012. That
11652 -- would cause real difficulties for those cases where there
11653 -- are incompatibilities between Ada 95 and Ada 2012. We could
11654 -- allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
11656 Check_Valid_Configuration_Pragma;
11658 -- Now set appropriate Ada mode
11660 Ada_Version := Ada_2012;
11661 Ada_Version_Explicit := Ada_2012;
11662 Ada_Version_Pragma := N;
11663 end if;
11664 end;
11666 ----------------------
11667 -- All_Calls_Remote --
11668 ----------------------
11670 -- pragma All_Calls_Remote [(library_package_NAME)];
11672 when Pragma_All_Calls_Remote => All_Calls_Remote : declare
11673 Lib_Entity : Entity_Id;
11675 begin
11676 Check_Ada_83_Warning;
11677 Check_Valid_Library_Unit_Pragma;
11679 if Nkind (N) = N_Null_Statement then
11680 return;
11681 end if;
11683 Lib_Entity := Find_Lib_Unit_Name;
11685 -- A pragma that applies to a Ghost entity becomes Ghost for the
11686 -- purposes of legality checks and removal of ignored Ghost code.
11688 Mark_Ghost_Pragma (N, Lib_Entity);
11690 -- This pragma should only apply to a RCI unit (RM E.2.3(23))
11692 if Present (Lib_Entity) and then not Debug_Flag_U then
11693 if not Is_Remote_Call_Interface (Lib_Entity) then
11694 Error_Pragma ("pragma% only apply to rci unit");
11696 -- Set flag for entity of the library unit
11698 else
11699 Set_Has_All_Calls_Remote (Lib_Entity);
11700 end if;
11701 end if;
11702 end All_Calls_Remote;
11704 ---------------------------
11705 -- Allow_Integer_Address --
11706 ---------------------------
11708 -- pragma Allow_Integer_Address;
11710 when Pragma_Allow_Integer_Address =>
11711 GNAT_Pragma;
11712 Check_Valid_Configuration_Pragma;
11713 Check_Arg_Count (0);
11715 -- If Address is a private type, then set the flag to allow
11716 -- integer address values. If Address is not private, then this
11717 -- pragma has no purpose, so it is simply ignored. Not clear if
11718 -- there are any such targets now.
11720 if Opt.Address_Is_Private then
11721 Opt.Allow_Integer_Address := True;
11722 end if;
11724 --------------
11725 -- Annotate --
11726 --------------
11728 -- pragma Annotate
11729 -- (IDENTIFIER [, IDENTIFIER {, ARG}] [,Entity => local_NAME]);
11730 -- ARG ::= NAME | EXPRESSION
11732 -- The first two arguments are by convention intended to refer to an
11733 -- external tool and a tool-specific function. These arguments are
11734 -- not analyzed.
11736 when Pragma_Annotate => Annotate : declare
11737 Arg : Node_Id;
11738 Expr : Node_Id;
11739 Nam_Arg : Node_Id;
11741 begin
11742 GNAT_Pragma;
11743 Check_At_Least_N_Arguments (1);
11745 Nam_Arg := Last (Pragma_Argument_Associations (N));
11747 -- Determine whether the last argument is "Entity => local_NAME"
11748 -- and if it is, perform the required semantic checks. Remove the
11749 -- argument from further processing.
11751 if Nkind (Nam_Arg) = N_Pragma_Argument_Association
11752 and then Chars (Nam_Arg) = Name_Entity
11753 then
11754 Check_Arg_Is_Local_Name (Nam_Arg);
11755 Arg_Count := Arg_Count - 1;
11757 -- A pragma that applies to a Ghost entity becomes Ghost for
11758 -- the purposes of legality checks and removal of ignored Ghost
11759 -- code.
11761 if Is_Entity_Name (Get_Pragma_Arg (Nam_Arg))
11762 and then Present (Entity (Get_Pragma_Arg (Nam_Arg)))
11763 then
11764 Mark_Ghost_Pragma (N, Entity (Get_Pragma_Arg (Nam_Arg)));
11765 end if;
11767 -- Not allowed in compiler units (bootstrap issues)
11769 Check_Compiler_Unit ("Entity for pragma Annotate", N);
11770 end if;
11772 -- Continue the processing with last argument removed for now
11774 Check_Arg_Is_Identifier (Arg1);
11775 Check_No_Identifiers;
11776 Store_Note (N);
11778 -- The second parameter is optional, it is never analyzed
11780 if No (Arg2) then
11781 null;
11783 -- Otherwise there is a second parameter
11785 else
11786 -- The second parameter must be an identifier
11788 Check_Arg_Is_Identifier (Arg2);
11790 -- Process the remaining parameters (if any)
11792 Arg := Next (Arg2);
11793 while Present (Arg) loop
11794 Expr := Get_Pragma_Arg (Arg);
11795 Analyze (Expr);
11797 if Is_Entity_Name (Expr) then
11798 null;
11800 -- For string literals, we assume Standard_String as the
11801 -- type, unless the string contains wide or wide_wide
11802 -- characters.
11804 elsif Nkind (Expr) = N_String_Literal then
11805 if Has_Wide_Wide_Character (Expr) then
11806 Resolve (Expr, Standard_Wide_Wide_String);
11807 elsif Has_Wide_Character (Expr) then
11808 Resolve (Expr, Standard_Wide_String);
11809 else
11810 Resolve (Expr, Standard_String);
11811 end if;
11813 elsif Is_Overloaded (Expr) then
11814 Error_Pragma_Arg ("ambiguous argument for pragma%", Expr);
11816 else
11817 Resolve (Expr);
11818 end if;
11820 Next (Arg);
11821 end loop;
11822 end if;
11823 end Annotate;
11825 -------------------------------------------------
11826 -- Assert/Assert_And_Cut/Assume/Loop_Invariant --
11827 -------------------------------------------------
11829 -- pragma Assert
11830 -- ( [Check => ] Boolean_EXPRESSION
11831 -- [, [Message =>] Static_String_EXPRESSION]);
11833 -- pragma Assert_And_Cut
11834 -- ( [Check => ] Boolean_EXPRESSION
11835 -- [, [Message =>] Static_String_EXPRESSION]);
11837 -- pragma Assume
11838 -- ( [Check => ] Boolean_EXPRESSION
11839 -- [, [Message =>] Static_String_EXPRESSION]);
11841 -- pragma Loop_Invariant
11842 -- ( [Check => ] Boolean_EXPRESSION
11843 -- [, [Message =>] Static_String_EXPRESSION]);
11845 when Pragma_Assert
11846 | Pragma_Assert_And_Cut
11847 | Pragma_Assume
11848 | Pragma_Loop_Invariant
11850 Assert : declare
11851 function Contains_Loop_Entry (Expr : Node_Id) return Boolean;
11852 -- Determine whether expression Expr contains a Loop_Entry
11853 -- attribute reference.
11855 -------------------------
11856 -- Contains_Loop_Entry --
11857 -------------------------
11859 function Contains_Loop_Entry (Expr : Node_Id) return Boolean is
11860 Has_Loop_Entry : Boolean := False;
11862 function Process (N : Node_Id) return Traverse_Result;
11863 -- Process function for traversal to look for Loop_Entry
11865 -------------
11866 -- Process --
11867 -------------
11869 function Process (N : Node_Id) return Traverse_Result is
11870 begin
11871 if Nkind (N) = N_Attribute_Reference
11872 and then Attribute_Name (N) = Name_Loop_Entry
11873 then
11874 Has_Loop_Entry := True;
11875 return Abandon;
11876 else
11877 return OK;
11878 end if;
11879 end Process;
11881 procedure Traverse is new Traverse_Proc (Process);
11883 -- Start of processing for Contains_Loop_Entry
11885 begin
11886 Traverse (Expr);
11887 return Has_Loop_Entry;
11888 end Contains_Loop_Entry;
11890 -- Local variables
11892 Expr : Node_Id;
11893 New_Args : List_Id;
11895 -- Start of processing for Assert
11897 begin
11898 -- Assert is an Ada 2005 RM-defined pragma
11900 if Prag_Id = Pragma_Assert then
11901 Ada_2005_Pragma;
11903 -- The remaining ones are GNAT pragmas
11905 else
11906 GNAT_Pragma;
11907 end if;
11909 Check_At_Least_N_Arguments (1);
11910 Check_At_Most_N_Arguments (2);
11911 Check_Arg_Order ((Name_Check, Name_Message));
11912 Check_Optional_Identifier (Arg1, Name_Check);
11913 Expr := Get_Pragma_Arg (Arg1);
11915 -- Special processing for Loop_Invariant, Loop_Variant or for
11916 -- other cases where a Loop_Entry attribute is present. If the
11917 -- assertion pragma contains attribute Loop_Entry, ensure that
11918 -- the related pragma is within a loop.
11920 if Prag_Id = Pragma_Loop_Invariant
11921 or else Prag_Id = Pragma_Loop_Variant
11922 or else Contains_Loop_Entry (Expr)
11923 then
11924 Check_Loop_Pragma_Placement;
11926 -- Perform preanalysis to deal with embedded Loop_Entry
11927 -- attributes.
11929 Preanalyze_Assert_Expression (Expr, Any_Boolean);
11930 end if;
11932 -- Implement Assert[_And_Cut]/Assume/Loop_Invariant by generating
11933 -- a corresponding Check pragma:
11935 -- pragma Check (name, condition [, msg]);
11937 -- Where name is the identifier matching the pragma name. So
11938 -- rewrite pragma in this manner, transfer the message argument
11939 -- if present, and analyze the result
11941 -- Note: When dealing with a semantically analyzed tree, the
11942 -- information that a Check node N corresponds to a source Assert,
11943 -- Assume, or Assert_And_Cut pragma can be retrieved from the
11944 -- pragma kind of Original_Node(N).
11946 New_Args := New_List (
11947 Make_Pragma_Argument_Association (Loc,
11948 Expression => Make_Identifier (Loc, Pname)),
11949 Make_Pragma_Argument_Association (Sloc (Expr),
11950 Expression => Expr));
11952 if Arg_Count > 1 then
11953 Check_Optional_Identifier (Arg2, Name_Message);
11955 -- Provide semantic annnotations for optional argument, for
11956 -- ASIS use, before rewriting.
11958 Preanalyze_And_Resolve (Expression (Arg2), Standard_String);
11959 Append_To (New_Args, New_Copy_Tree (Arg2));
11960 end if;
11962 -- Rewrite as Check pragma
11964 Rewrite (N,
11965 Make_Pragma (Loc,
11966 Chars => Name_Check,
11967 Pragma_Argument_Associations => New_Args));
11969 Analyze (N);
11970 end Assert;
11972 ----------------------
11973 -- Assertion_Policy --
11974 ----------------------
11976 -- pragma Assertion_Policy (POLICY_IDENTIFIER);
11978 -- The following form is Ada 2012 only, but we allow it in all modes
11980 -- Pragma Assertion_Policy (
11981 -- ASSERTION_KIND => POLICY_IDENTIFIER
11982 -- {, ASSERTION_KIND => POLICY_IDENTIFIER});
11984 -- ASSERTION_KIND ::= RM_ASSERTION_KIND | ID_ASSERTION_KIND
11986 -- RM_ASSERTION_KIND ::= Assert |
11987 -- Static_Predicate |
11988 -- Dynamic_Predicate |
11989 -- Pre |
11990 -- Pre'Class |
11991 -- Post |
11992 -- Post'Class |
11993 -- Type_Invariant |
11994 -- Type_Invariant'Class
11996 -- ID_ASSERTION_KIND ::= Assert_And_Cut |
11997 -- Assume |
11998 -- Contract_Cases |
11999 -- Debug |
12000 -- Default_Initial_Condition |
12001 -- Ghost |
12002 -- Initial_Condition |
12003 -- Loop_Invariant |
12004 -- Loop_Variant |
12005 -- Postcondition |
12006 -- Precondition |
12007 -- Predicate |
12008 -- Refined_Post |
12009 -- Statement_Assertions
12011 -- Note: The RM_ASSERTION_KIND list is language-defined, and the
12012 -- ID_ASSERTION_KIND list contains implementation-defined additions
12013 -- recognized by GNAT. The effect is to control the behavior of
12014 -- identically named aspects and pragmas, depending on the specified
12015 -- policy identifier:
12017 -- POLICY_IDENTIFIER ::= Check | Disable | Ignore | Suppressible
12019 -- Note: Check and Ignore are language-defined. Disable is a GNAT
12020 -- implementation-defined addition that results in totally ignoring
12021 -- the corresponding assertion. If Disable is specified, then the
12022 -- argument of the assertion is not even analyzed. This is useful
12023 -- when the aspect/pragma argument references entities in a with'ed
12024 -- package that is replaced by a dummy package in the final build.
12026 -- Note: the attribute forms Pre'Class, Post'Class, Invariant'Class,
12027 -- and Type_Invariant'Class were recognized by the parser and
12028 -- transformed into references to the special internal identifiers
12029 -- _Pre, _Post, _Invariant, and _Type_Invariant, so no special
12030 -- processing is required here.
12032 when Pragma_Assertion_Policy => Assertion_Policy : declare
12033 procedure Resolve_Suppressible (Policy : Node_Id);
12034 -- Converts the assertion policy 'Suppressible' to either Check or
12035 -- Ignore based on whether checks are suppressed via -gnatp.
12037 --------------------------
12038 -- Resolve_Suppressible --
12039 --------------------------
12041 procedure Resolve_Suppressible (Policy : Node_Id) is
12042 Arg : constant Node_Id := Get_Pragma_Arg (Policy);
12043 Nam : Name_Id;
12045 begin
12046 -- Transform policy argument Suppressible into either Ignore or
12047 -- Check depending on whether checks are enabled or suppressed.
12049 if Chars (Arg) = Name_Suppressible then
12050 if Suppress_Checks then
12051 Nam := Name_Ignore;
12052 else
12053 Nam := Name_Check;
12054 end if;
12056 Rewrite (Arg, Make_Identifier (Sloc (Arg), Nam));
12057 end if;
12058 end Resolve_Suppressible;
12060 -- Local variables
12062 Arg : Node_Id;
12063 Kind : Name_Id;
12064 LocP : Source_Ptr;
12065 Policy : Node_Id;
12067 begin
12068 Ada_2005_Pragma;
12070 -- This can always appear as a configuration pragma
12072 if Is_Configuration_Pragma then
12073 null;
12075 -- It can also appear in a declarative part or package spec in Ada
12076 -- 2012 mode. We allow this in other modes, but in that case we
12077 -- consider that we have an Ada 2012 pragma on our hands.
12079 else
12080 Check_Is_In_Decl_Part_Or_Package_Spec;
12081 Ada_2012_Pragma;
12082 end if;
12084 -- One argument case with no identifier (first form above)
12086 if Arg_Count = 1
12087 and then (Nkind (Arg1) /= N_Pragma_Argument_Association
12088 or else Chars (Arg1) = No_Name)
12089 then
12090 Check_Arg_Is_One_Of (Arg1,
12091 Name_Check, Name_Disable, Name_Ignore, Name_Suppressible);
12093 Resolve_Suppressible (Arg1);
12095 -- Treat one argument Assertion_Policy as equivalent to:
12097 -- pragma Check_Policy (Assertion, policy)
12099 -- So rewrite pragma in that manner and link on to the chain
12100 -- of Check_Policy pragmas, marking the pragma as analyzed.
12102 Policy := Get_Pragma_Arg (Arg1);
12104 Rewrite (N,
12105 Make_Pragma (Loc,
12106 Chars => Name_Check_Policy,
12107 Pragma_Argument_Associations => New_List (
12108 Make_Pragma_Argument_Association (Loc,
12109 Expression => Make_Identifier (Loc, Name_Assertion)),
12111 Make_Pragma_Argument_Association (Loc,
12112 Expression =>
12113 Make_Identifier (Sloc (Policy), Chars (Policy))))));
12114 Analyze (N);
12116 -- Here if we have two or more arguments
12118 else
12119 Check_At_Least_N_Arguments (1);
12120 Ada_2012_Pragma;
12122 -- Loop through arguments
12124 Arg := Arg1;
12125 while Present (Arg) loop
12126 LocP := Sloc (Arg);
12128 -- Kind must be specified
12130 if Nkind (Arg) /= N_Pragma_Argument_Association
12131 or else Chars (Arg) = No_Name
12132 then
12133 Error_Pragma_Arg
12134 ("missing assertion kind for pragma%", Arg);
12135 end if;
12137 -- Check Kind and Policy have allowed forms
12139 Kind := Chars (Arg);
12140 Policy := Get_Pragma_Arg (Arg);
12142 if not Is_Valid_Assertion_Kind (Kind) then
12143 Error_Pragma_Arg
12144 ("invalid assertion kind for pragma%", Arg);
12145 end if;
12147 Check_Arg_Is_One_Of (Arg,
12148 Name_Check, Name_Disable, Name_Ignore, Name_Suppressible);
12150 Resolve_Suppressible (Arg);
12152 if Kind = Name_Ghost then
12154 -- The Ghost policy must be either Check or Ignore
12155 -- (SPARK RM 6.9(6)).
12157 if not Nam_In (Chars (Policy), Name_Check,
12158 Name_Ignore)
12159 then
12160 Error_Pragma_Arg
12161 ("argument of pragma % Ghost must be Check or "
12162 & "Ignore", Policy);
12163 end if;
12165 -- Pragma Assertion_Policy specifying a Ghost policy
12166 -- cannot occur within a Ghost subprogram or package
12167 -- (SPARK RM 6.9(14)).
12169 if Ghost_Mode > None then
12170 Error_Pragma
12171 ("pragma % cannot appear within ghost subprogram or "
12172 & "package");
12173 end if;
12174 end if;
12176 -- Rewrite the Assertion_Policy pragma as a series of
12177 -- Check_Policy pragmas of the form:
12179 -- Check_Policy (Kind, Policy);
12181 -- Note: the insertion of the pragmas cannot be done with
12182 -- Insert_Action because in the configuration case, there
12183 -- are no scopes on the scope stack and the mechanism will
12184 -- fail.
12186 Insert_Before_And_Analyze (N,
12187 Make_Pragma (LocP,
12188 Chars => Name_Check_Policy,
12189 Pragma_Argument_Associations => New_List (
12190 Make_Pragma_Argument_Association (LocP,
12191 Expression => Make_Identifier (LocP, Kind)),
12192 Make_Pragma_Argument_Association (LocP,
12193 Expression => Policy))));
12195 Arg := Next (Arg);
12196 end loop;
12198 -- Rewrite the Assertion_Policy pragma as null since we have
12199 -- now inserted all the equivalent Check pragmas.
12201 Rewrite (N, Make_Null_Statement (Loc));
12202 Analyze (N);
12203 end if;
12204 end Assertion_Policy;
12206 ------------------------------
12207 -- Assume_No_Invalid_Values --
12208 ------------------------------
12210 -- pragma Assume_No_Invalid_Values (On | Off);
12212 when Pragma_Assume_No_Invalid_Values =>
12213 GNAT_Pragma;
12214 Check_Valid_Configuration_Pragma;
12215 Check_Arg_Count (1);
12216 Check_No_Identifiers;
12217 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
12219 if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
12220 Assume_No_Invalid_Values := True;
12221 else
12222 Assume_No_Invalid_Values := False;
12223 end if;
12225 --------------------------
12226 -- Attribute_Definition --
12227 --------------------------
12229 -- pragma Attribute_Definition
12230 -- ([Attribute =>] ATTRIBUTE_DESIGNATOR,
12231 -- [Entity =>] LOCAL_NAME,
12232 -- [Expression =>] EXPRESSION | NAME);
12234 when Pragma_Attribute_Definition => Attribute_Definition : declare
12235 Attribute_Designator : constant Node_Id := Get_Pragma_Arg (Arg1);
12236 Aname : Name_Id;
12238 begin
12239 GNAT_Pragma;
12240 Check_Arg_Count (3);
12241 Check_Optional_Identifier (Arg1, "attribute");
12242 Check_Optional_Identifier (Arg2, "entity");
12243 Check_Optional_Identifier (Arg3, "expression");
12245 if Nkind (Attribute_Designator) /= N_Identifier then
12246 Error_Msg_N ("attribute name expected", Attribute_Designator);
12247 return;
12248 end if;
12250 Check_Arg_Is_Local_Name (Arg2);
12252 -- If the attribute is not recognized, then issue a warning (not
12253 -- an error), and ignore the pragma.
12255 Aname := Chars (Attribute_Designator);
12257 if not Is_Attribute_Name (Aname) then
12258 Bad_Attribute (Attribute_Designator, Aname, Warn => True);
12259 return;
12260 end if;
12262 -- Otherwise, rewrite the pragma as an attribute definition clause
12264 Rewrite (N,
12265 Make_Attribute_Definition_Clause (Loc,
12266 Name => Get_Pragma_Arg (Arg2),
12267 Chars => Aname,
12268 Expression => Get_Pragma_Arg (Arg3)));
12269 Analyze (N);
12270 end Attribute_Definition;
12272 ------------------------------------------------------------------
12273 -- Async_Readers/Async_Writers/Effective_Reads/Effective_Writes --
12274 ------------------------------------------------------------------
12276 -- pragma Asynch_Readers [ (boolean_EXPRESSION) ];
12277 -- pragma Asynch_Writers [ (boolean_EXPRESSION) ];
12278 -- pragma Effective_Reads [ (boolean_EXPRESSION) ];
12279 -- pragma Effective_Writes [ (boolean_EXPRESSION) ];
12281 when Pragma_Async_Readers
12282 | Pragma_Async_Writers
12283 | Pragma_Effective_Reads
12284 | Pragma_Effective_Writes
12286 Async_Effective : declare
12287 Obj_Decl : Node_Id;
12288 Obj_Id : Entity_Id;
12290 begin
12291 GNAT_Pragma;
12292 Check_No_Identifiers;
12293 Check_At_Most_N_Arguments (1);
12295 Obj_Decl := Find_Related_Context (N, Do_Checks => True);
12297 -- Object declaration
12299 if Nkind (Obj_Decl) = N_Object_Declaration then
12300 null;
12302 -- Otherwise the pragma is associated with an illegal construact
12304 else
12305 Pragma_Misplaced;
12306 return;
12307 end if;
12309 Obj_Id := Defining_Entity (Obj_Decl);
12311 -- Perform minimal verification to ensure that the argument is at
12312 -- least a variable. Subsequent finer grained checks will be done
12313 -- at the end of the declarative region the contains the pragma.
12315 if Ekind (Obj_Id) = E_Variable then
12317 -- A pragma that applies to a Ghost entity becomes Ghost for
12318 -- the purposes of legality checks and removal of ignored Ghost
12319 -- code.
12321 Mark_Ghost_Pragma (N, Obj_Id);
12323 -- Chain the pragma on the contract for further processing by
12324 -- Analyze_External_Property_In_Decl_Part.
12326 Add_Contract_Item (N, Obj_Id);
12328 -- Analyze the Boolean expression (if any)
12330 if Present (Arg1) then
12331 Check_Static_Boolean_Expression (Get_Pragma_Arg (Arg1));
12332 end if;
12334 -- Otherwise the external property applies to a constant
12336 else
12337 Error_Pragma ("pragma % must apply to a volatile object");
12338 end if;
12339 end Async_Effective;
12341 ------------------
12342 -- Asynchronous --
12343 ------------------
12345 -- pragma Asynchronous (LOCAL_NAME);
12347 when Pragma_Asynchronous => Asynchronous : declare
12348 C_Ent : Entity_Id;
12349 Decl : Node_Id;
12350 Formal : Entity_Id;
12351 L : List_Id;
12352 Nm : Entity_Id;
12353 S : Node_Id;
12355 procedure Process_Async_Pragma;
12356 -- Common processing for procedure and access-to-procedure case
12358 --------------------------
12359 -- Process_Async_Pragma --
12360 --------------------------
12362 procedure Process_Async_Pragma is
12363 begin
12364 if No (L) then
12365 Set_Is_Asynchronous (Nm);
12366 return;
12367 end if;
12369 -- The formals should be of mode IN (RM E.4.1(6))
12371 S := First (L);
12372 while Present (S) loop
12373 Formal := Defining_Identifier (S);
12375 if Nkind (Formal) = N_Defining_Identifier
12376 and then Ekind (Formal) /= E_In_Parameter
12377 then
12378 Error_Pragma_Arg
12379 ("pragma% procedure can only have IN parameter",
12380 Arg1);
12381 end if;
12383 Next (S);
12384 end loop;
12386 Set_Is_Asynchronous (Nm);
12387 end Process_Async_Pragma;
12389 -- Start of processing for pragma Asynchronous
12391 begin
12392 Check_Ada_83_Warning;
12393 Check_No_Identifiers;
12394 Check_Arg_Count (1);
12395 Check_Arg_Is_Local_Name (Arg1);
12397 if Debug_Flag_U then
12398 return;
12399 end if;
12401 C_Ent := Cunit_Entity (Current_Sem_Unit);
12402 Analyze (Get_Pragma_Arg (Arg1));
12403 Nm := Entity (Get_Pragma_Arg (Arg1));
12405 -- A pragma that applies to a Ghost entity becomes Ghost for the
12406 -- purposes of legality checks and removal of ignored Ghost code.
12408 Mark_Ghost_Pragma (N, Nm);
12410 if not Is_Remote_Call_Interface (C_Ent)
12411 and then not Is_Remote_Types (C_Ent)
12412 then
12413 -- This pragma should only appear in an RCI or Remote Types
12414 -- unit (RM E.4.1(4)).
12416 Error_Pragma
12417 ("pragma% not in Remote_Call_Interface or Remote_Types unit");
12418 end if;
12420 if Ekind (Nm) = E_Procedure
12421 and then Nkind (Parent (Nm)) = N_Procedure_Specification
12422 then
12423 if not Is_Remote_Call_Interface (Nm) then
12424 Error_Pragma_Arg
12425 ("pragma% cannot be applied on non-remote procedure",
12426 Arg1);
12427 end if;
12429 L := Parameter_Specifications (Parent (Nm));
12430 Process_Async_Pragma;
12431 return;
12433 elsif Ekind (Nm) = E_Function then
12434 Error_Pragma_Arg
12435 ("pragma% cannot be applied to function", Arg1);
12437 elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
12438 if Is_Record_Type (Nm) then
12440 -- A record type that is the Equivalent_Type for a remote
12441 -- access-to-subprogram type.
12443 Decl := Declaration_Node (Corresponding_Remote_Type (Nm));
12445 else
12446 -- A non-expanded RAS type (distribution is not enabled)
12448 Decl := Declaration_Node (Nm);
12449 end if;
12451 if Nkind (Decl) = N_Full_Type_Declaration
12452 and then Nkind (Type_Definition (Decl)) =
12453 N_Access_Procedure_Definition
12454 then
12455 L := Parameter_Specifications (Type_Definition (Decl));
12456 Process_Async_Pragma;
12458 if Is_Asynchronous (Nm)
12459 and then Expander_Active
12460 and then Get_PCS_Name /= Name_No_DSA
12461 then
12462 RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
12463 end if;
12465 else
12466 Error_Pragma_Arg
12467 ("pragma% cannot reference access-to-function type",
12468 Arg1);
12469 end if;
12471 -- Only other possibility is Access-to-class-wide type
12473 elsif Is_Access_Type (Nm)
12474 and then Is_Class_Wide_Type (Designated_Type (Nm))
12475 then
12476 Check_First_Subtype (Arg1);
12477 Set_Is_Asynchronous (Nm);
12478 if Expander_Active then
12479 RACW_Type_Is_Asynchronous (Nm);
12480 end if;
12482 else
12483 Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
12484 end if;
12485 end Asynchronous;
12487 ------------
12488 -- Atomic --
12489 ------------
12491 -- pragma Atomic (LOCAL_NAME);
12493 when Pragma_Atomic =>
12494 Process_Atomic_Independent_Shared_Volatile;
12496 -----------------------
12497 -- Atomic_Components --
12498 -----------------------
12500 -- pragma Atomic_Components (array_LOCAL_NAME);
12502 -- This processing is shared by Volatile_Components
12504 when Pragma_Atomic_Components
12505 | Pragma_Volatile_Components
12507 Atomic_Components : declare
12508 D : Node_Id;
12509 E : Entity_Id;
12510 E_Id : Node_Id;
12511 K : Node_Kind;
12513 begin
12514 Check_Ada_83_Warning;
12515 Check_No_Identifiers;
12516 Check_Arg_Count (1);
12517 Check_Arg_Is_Local_Name (Arg1);
12518 E_Id := Get_Pragma_Arg (Arg1);
12520 if Etype (E_Id) = Any_Type then
12521 return;
12522 end if;
12524 E := Entity (E_Id);
12526 -- A pragma that applies to a Ghost entity becomes Ghost for the
12527 -- purposes of legality checks and removal of ignored Ghost code.
12529 Mark_Ghost_Pragma (N, E);
12530 Check_Duplicate_Pragma (E);
12532 if Rep_Item_Too_Early (E, N)
12533 or else
12534 Rep_Item_Too_Late (E, N)
12535 then
12536 return;
12537 end if;
12539 D := Declaration_Node (E);
12540 K := Nkind (D);
12542 if (K = N_Full_Type_Declaration and then Is_Array_Type (E))
12543 or else
12544 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
12545 and then Nkind (D) = N_Object_Declaration
12546 and then Nkind (Object_Definition (D)) =
12547 N_Constrained_Array_Definition)
12548 then
12549 -- The flag is set on the object, or on the base type
12551 if Nkind (D) /= N_Object_Declaration then
12552 E := Base_Type (E);
12553 end if;
12555 -- Atomic implies both Independent and Volatile
12557 if Prag_Id = Pragma_Atomic_Components then
12558 Set_Has_Atomic_Components (E);
12559 Set_Has_Independent_Components (E);
12560 end if;
12562 Set_Has_Volatile_Components (E);
12564 else
12565 Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
12566 end if;
12567 end Atomic_Components;
12569 --------------------
12570 -- Attach_Handler --
12571 --------------------
12573 -- pragma Attach_Handler (handler_NAME, EXPRESSION);
12575 when Pragma_Attach_Handler =>
12576 Check_Ada_83_Warning;
12577 Check_No_Identifiers;
12578 Check_Arg_Count (2);
12580 if No_Run_Time_Mode then
12581 Error_Msg_CRT ("Attach_Handler pragma", N);
12582 else
12583 Check_Interrupt_Or_Attach_Handler;
12585 -- The expression that designates the attribute may depend on a
12586 -- discriminant, and is therefore a per-object expression, to
12587 -- be expanded in the init proc. If expansion is enabled, then
12588 -- perform semantic checks on a copy only.
12590 declare
12591 Temp : Node_Id;
12592 Typ : Node_Id;
12593 Parg2 : constant Node_Id := Get_Pragma_Arg (Arg2);
12595 begin
12596 -- In Relaxed_RM_Semantics mode, we allow any static
12597 -- integer value, for compatibility with other compilers.
12599 if Relaxed_RM_Semantics
12600 and then Nkind (Parg2) = N_Integer_Literal
12601 then
12602 Typ := Standard_Integer;
12603 else
12604 Typ := RTE (RE_Interrupt_ID);
12605 end if;
12607 if Expander_Active then
12608 Temp := New_Copy_Tree (Parg2);
12609 Set_Parent (Temp, N);
12610 Preanalyze_And_Resolve (Temp, Typ);
12611 else
12612 Analyze (Parg2);
12613 Resolve (Parg2, Typ);
12614 end if;
12615 end;
12617 Process_Interrupt_Or_Attach_Handler;
12618 end if;
12620 --------------------
12621 -- C_Pass_By_Copy --
12622 --------------------
12624 -- pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
12626 when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
12627 Arg : Node_Id;
12628 Val : Uint;
12630 begin
12631 GNAT_Pragma;
12632 Check_Valid_Configuration_Pragma;
12633 Check_Arg_Count (1);
12634 Check_Optional_Identifier (Arg1, "max_size");
12636 Arg := Get_Pragma_Arg (Arg1);
12637 Check_Arg_Is_OK_Static_Expression (Arg, Any_Integer);
12639 Val := Expr_Value (Arg);
12641 if Val <= 0 then
12642 Error_Pragma_Arg
12643 ("maximum size for pragma% must be positive", Arg1);
12645 elsif UI_Is_In_Int_Range (Val) then
12646 Default_C_Record_Mechanism := UI_To_Int (Val);
12648 -- If a giant value is given, Int'Last will do well enough.
12649 -- If sometime someone complains that a record larger than
12650 -- two gigabytes is not copied, we will worry about it then.
12652 else
12653 Default_C_Record_Mechanism := Mechanism_Type'Last;
12654 end if;
12655 end C_Pass_By_Copy;
12657 -----------
12658 -- Check --
12659 -----------
12661 -- pragma Check ([Name =>] CHECK_KIND,
12662 -- [Check =>] Boolean_EXPRESSION
12663 -- [,[Message =>] String_EXPRESSION]);
12665 -- CHECK_KIND ::= IDENTIFIER |
12666 -- Pre'Class |
12667 -- Post'Class |
12668 -- Invariant'Class |
12669 -- Type_Invariant'Class
12671 -- The identifiers Assertions and Statement_Assertions are not
12672 -- allowed, since they have special meaning for Check_Policy.
12674 -- WARNING: The code below manages Ghost regions. Return statements
12675 -- must be replaced by gotos which jump to the end of the code and
12676 -- restore the Ghost mode.
12678 when Pragma_Check => Check : declare
12679 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
12680 -- Save the Ghost mode to restore on exit
12682 Cname : Name_Id;
12683 Eloc : Source_Ptr;
12684 Expr : Node_Id;
12685 Str : Node_Id;
12686 pragma Warnings (Off, Str);
12688 begin
12689 -- Pragma Check is Ghost when it applies to a Ghost entity. Set
12690 -- the mode now to ensure that any nodes generated during analysis
12691 -- and expansion are marked as Ghost.
12693 Set_Ghost_Mode (N);
12695 GNAT_Pragma;
12696 Check_At_Least_N_Arguments (2);
12697 Check_At_Most_N_Arguments (3);
12698 Check_Optional_Identifier (Arg1, Name_Name);
12699 Check_Optional_Identifier (Arg2, Name_Check);
12701 if Arg_Count = 3 then
12702 Check_Optional_Identifier (Arg3, Name_Message);
12703 Str := Get_Pragma_Arg (Arg3);
12704 end if;
12706 Rewrite_Assertion_Kind (Get_Pragma_Arg (Arg1));
12707 Check_Arg_Is_Identifier (Arg1);
12708 Cname := Chars (Get_Pragma_Arg (Arg1));
12710 -- Check forbidden name Assertions or Statement_Assertions
12712 case Cname is
12713 when Name_Assertions =>
12714 Error_Pragma_Arg
12715 ("""Assertions"" is not allowed as a check kind for "
12716 & "pragma%", Arg1);
12718 when Name_Statement_Assertions =>
12719 Error_Pragma_Arg
12720 ("""Statement_Assertions"" is not allowed as a check kind "
12721 & "for pragma%", Arg1);
12723 when others =>
12724 null;
12725 end case;
12727 -- Check applicable policy. We skip this if Checked/Ignored status
12728 -- is already set (e.g. in the case of a pragma from an aspect).
12730 if Is_Checked (N) or else Is_Ignored (N) then
12731 null;
12733 -- For a non-source pragma that is a rewriting of another pragma,
12734 -- copy the Is_Checked/Ignored status from the rewritten pragma.
12736 elsif Is_Rewrite_Substitution (N)
12737 and then Nkind (Original_Node (N)) = N_Pragma
12738 and then Original_Node (N) /= N
12739 then
12740 Set_Is_Ignored (N, Is_Ignored (Original_Node (N)));
12741 Set_Is_Checked (N, Is_Checked (Original_Node (N)));
12743 -- Otherwise query the applicable policy at this point
12745 else
12746 case Check_Kind (Cname) is
12747 when Name_Ignore =>
12748 Set_Is_Ignored (N, True);
12749 Set_Is_Checked (N, False);
12751 when Name_Check =>
12752 Set_Is_Ignored (N, False);
12753 Set_Is_Checked (N, True);
12755 -- For disable, rewrite pragma as null statement and skip
12756 -- rest of the analysis of the pragma.
12758 when Name_Disable =>
12759 Rewrite (N, Make_Null_Statement (Loc));
12760 Analyze (N);
12761 raise Pragma_Exit;
12763 -- No other possibilities
12765 when others =>
12766 raise Program_Error;
12767 end case;
12768 end if;
12770 -- If check kind was not Disable, then continue pragma analysis
12772 Expr := Get_Pragma_Arg (Arg2);
12774 -- Deal with SCO generation
12776 if Is_Checked (N) and then not Split_PPC (N) then
12777 Set_SCO_Pragma_Enabled (Loc);
12778 end if;
12780 -- Deal with analyzing the string argument
12782 if Arg_Count = 3 then
12784 -- If checks are not on we don't want any expansion (since
12785 -- such expansion would not get properly deleted) but
12786 -- we do want to analyze (to get proper references).
12787 -- The Preanalyze_And_Resolve routine does just what we want
12789 if Is_Ignored (N) then
12790 Preanalyze_And_Resolve (Str, Standard_String);
12792 -- Otherwise we need a proper analysis and expansion
12794 else
12795 Analyze_And_Resolve (Str, Standard_String);
12796 end if;
12797 end if;
12799 -- Now you might think we could just do the same with the Boolean
12800 -- expression if checks are off (and expansion is on) and then
12801 -- rewrite the check as a null statement. This would work but we
12802 -- would lose the useful warnings about an assertion being bound
12803 -- to fail even if assertions are turned off.
12805 -- So instead we wrap the boolean expression in an if statement
12806 -- that looks like:
12808 -- if False and then condition then
12809 -- null;
12810 -- end if;
12812 -- The reason we do this rewriting during semantic analysis rather
12813 -- than as part of normal expansion is that we cannot analyze and
12814 -- expand the code for the boolean expression directly, or it may
12815 -- cause insertion of actions that would escape the attempt to
12816 -- suppress the check code.
12818 -- Note that the Sloc for the if statement corresponds to the
12819 -- argument condition, not the pragma itself. The reason for
12820 -- this is that we may generate a warning if the condition is
12821 -- False at compile time, and we do not want to delete this
12822 -- warning when we delete the if statement.
12824 if Expander_Active and Is_Ignored (N) then
12825 Eloc := Sloc (Expr);
12827 Rewrite (N,
12828 Make_If_Statement (Eloc,
12829 Condition =>
12830 Make_And_Then (Eloc,
12831 Left_Opnd => Make_Identifier (Eloc, Name_False),
12832 Right_Opnd => Expr),
12833 Then_Statements => New_List (
12834 Make_Null_Statement (Eloc))));
12836 -- Now go ahead and analyze the if statement
12838 In_Assertion_Expr := In_Assertion_Expr + 1;
12840 -- One rather special treatment. If we are now in Eliminated
12841 -- overflow mode, then suppress overflow checking since we do
12842 -- not want to drag in the bignum stuff if we are in Ignore
12843 -- mode anyway. This is particularly important if we are using
12844 -- a configurable run time that does not support bignum ops.
12846 if Scope_Suppress.Overflow_Mode_Assertions = Eliminated then
12847 declare
12848 Svo : constant Boolean :=
12849 Scope_Suppress.Suppress (Overflow_Check);
12850 begin
12851 Scope_Suppress.Overflow_Mode_Assertions := Strict;
12852 Scope_Suppress.Suppress (Overflow_Check) := True;
12853 Analyze (N);
12854 Scope_Suppress.Suppress (Overflow_Check) := Svo;
12855 Scope_Suppress.Overflow_Mode_Assertions := Eliminated;
12856 end;
12858 -- Not that special case
12860 else
12861 Analyze (N);
12862 end if;
12864 -- All done with this check
12866 In_Assertion_Expr := In_Assertion_Expr - 1;
12868 -- Check is active or expansion not active. In these cases we can
12869 -- just go ahead and analyze the boolean with no worries.
12871 else
12872 In_Assertion_Expr := In_Assertion_Expr + 1;
12873 Analyze_And_Resolve (Expr, Any_Boolean);
12874 In_Assertion_Expr := In_Assertion_Expr - 1;
12875 end if;
12877 Restore_Ghost_Mode (Saved_GM);
12878 end Check;
12880 --------------------------
12881 -- Check_Float_Overflow --
12882 --------------------------
12884 -- pragma Check_Float_Overflow;
12886 when Pragma_Check_Float_Overflow =>
12887 GNAT_Pragma;
12888 Check_Valid_Configuration_Pragma;
12889 Check_Arg_Count (0);
12890 Check_Float_Overflow := not Machine_Overflows_On_Target;
12892 ----------------
12893 -- Check_Name --
12894 ----------------
12896 -- pragma Check_Name (check_IDENTIFIER);
12898 when Pragma_Check_Name =>
12899 GNAT_Pragma;
12900 Check_No_Identifiers;
12901 Check_Valid_Configuration_Pragma;
12902 Check_Arg_Count (1);
12903 Check_Arg_Is_Identifier (Arg1);
12905 declare
12906 Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
12908 begin
12909 for J in Check_Names.First .. Check_Names.Last loop
12910 if Check_Names.Table (J) = Nam then
12911 return;
12912 end if;
12913 end loop;
12915 Check_Names.Append (Nam);
12916 end;
12918 ------------------
12919 -- Check_Policy --
12920 ------------------
12922 -- This is the old style syntax, which is still allowed in all modes:
12924 -- pragma Check_Policy ([Name =>] CHECK_KIND
12925 -- [Policy =>] POLICY_IDENTIFIER);
12927 -- POLICY_IDENTIFIER ::= On | Off | Check | Disable | Ignore
12929 -- CHECK_KIND ::= IDENTIFIER |
12930 -- Pre'Class |
12931 -- Post'Class |
12932 -- Type_Invariant'Class |
12933 -- Invariant'Class
12935 -- This is the new style syntax, compatible with Assertion_Policy
12936 -- and also allowed in all modes.
12938 -- Pragma Check_Policy (
12939 -- CHECK_KIND => POLICY_IDENTIFIER
12940 -- {, CHECK_KIND => POLICY_IDENTIFIER});
12942 -- Note: the identifiers Name and Policy are not allowed as
12943 -- Check_Kind values. This avoids ambiguities between the old and
12944 -- new form syntax.
12946 when Pragma_Check_Policy => Check_Policy : declare
12947 Kind : Node_Id;
12949 begin
12950 GNAT_Pragma;
12951 Check_At_Least_N_Arguments (1);
12953 -- A Check_Policy pragma can appear either as a configuration
12954 -- pragma, or in a declarative part or a package spec (see RM
12955 -- 11.5(5) for rules for Suppress/Unsuppress which are also
12956 -- followed for Check_Policy).
12958 if not Is_Configuration_Pragma then
12959 Check_Is_In_Decl_Part_Or_Package_Spec;
12960 end if;
12962 -- Figure out if we have the old or new syntax. We have the
12963 -- old syntax if the first argument has no identifier, or the
12964 -- identifier is Name.
12966 if Nkind (Arg1) /= N_Pragma_Argument_Association
12967 or else Nam_In (Chars (Arg1), No_Name, Name_Name)
12968 then
12969 -- Old syntax
12971 Check_Arg_Count (2);
12972 Check_Optional_Identifier (Arg1, Name_Name);
12973 Kind := Get_Pragma_Arg (Arg1);
12974 Rewrite_Assertion_Kind (Kind,
12975 From_Policy => Comes_From_Source (N));
12976 Check_Arg_Is_Identifier (Arg1);
12978 -- Check forbidden check kind
12980 if Nam_In (Chars (Kind), Name_Name, Name_Policy) then
12981 Error_Msg_Name_2 := Chars (Kind);
12982 Error_Pragma_Arg
12983 ("pragma% does not allow% as check name", Arg1);
12984 end if;
12986 -- Check policy
12988 Check_Optional_Identifier (Arg2, Name_Policy);
12989 Check_Arg_Is_One_Of
12990 (Arg2,
12991 Name_On, Name_Off, Name_Check, Name_Disable, Name_Ignore);
12993 -- And chain pragma on the Check_Policy_List for search
12995 Set_Next_Pragma (N, Opt.Check_Policy_List);
12996 Opt.Check_Policy_List := N;
12998 -- For the new syntax, what we do is to convert each argument to
12999 -- an old syntax equivalent. We do that because we want to chain
13000 -- old style Check_Policy pragmas for the search (we don't want
13001 -- to have to deal with multiple arguments in the search).
13003 else
13004 declare
13005 Arg : Node_Id;
13006 Argx : Node_Id;
13007 LocP : Source_Ptr;
13008 New_P : Node_Id;
13010 begin
13011 Arg := Arg1;
13012 while Present (Arg) loop
13013 LocP := Sloc (Arg);
13014 Argx := Get_Pragma_Arg (Arg);
13016 -- Kind must be specified
13018 if Nkind (Arg) /= N_Pragma_Argument_Association
13019 or else Chars (Arg) = No_Name
13020 then
13021 Error_Pragma_Arg
13022 ("missing assertion kind for pragma%", Arg);
13023 end if;
13025 -- Construct equivalent old form syntax Check_Policy
13026 -- pragma and insert it to get remaining checks.
13028 New_P :=
13029 Make_Pragma (LocP,
13030 Chars => Name_Check_Policy,
13031 Pragma_Argument_Associations => New_List (
13032 Make_Pragma_Argument_Association (LocP,
13033 Expression =>
13034 Make_Identifier (LocP, Chars (Arg))),
13035 Make_Pragma_Argument_Association (Sloc (Argx),
13036 Expression => Argx)));
13038 Arg := Next (Arg);
13040 -- For a configuration pragma, insert old form in
13041 -- the corresponding file.
13043 if Is_Configuration_Pragma then
13044 Insert_After (N, New_P);
13045 Analyze (New_P);
13047 else
13048 Insert_Action (N, New_P);
13049 end if;
13050 end loop;
13052 -- Rewrite original Check_Policy pragma to null, since we
13053 -- have converted it into a series of old syntax pragmas.
13055 Rewrite (N, Make_Null_Statement (Loc));
13056 Analyze (N);
13057 end;
13058 end if;
13059 end Check_Policy;
13061 -------------
13062 -- Comment --
13063 -------------
13065 -- pragma Comment (static_string_EXPRESSION)
13067 -- Processing for pragma Comment shares the circuitry for pragma
13068 -- Ident. The only differences are that Ident enforces a limit of 31
13069 -- characters on its argument, and also enforces limitations on
13070 -- placement for DEC compatibility. Pragma Comment shares neither of
13071 -- these restrictions.
13073 -------------------
13074 -- Common_Object --
13075 -------------------
13077 -- pragma Common_Object (
13078 -- [Internal =>] LOCAL_NAME
13079 -- [, [External =>] EXTERNAL_SYMBOL]
13080 -- [, [Size =>] EXTERNAL_SYMBOL]);
13082 -- Processing for this pragma is shared with Psect_Object
13084 ------------------------
13085 -- Compile_Time_Error --
13086 ------------------------
13088 -- pragma Compile_Time_Error
13089 -- (boolean_EXPRESSION, static_string_EXPRESSION);
13091 when Pragma_Compile_Time_Error =>
13092 GNAT_Pragma;
13093 Process_Compile_Time_Warning_Or_Error;
13095 --------------------------
13096 -- Compile_Time_Warning --
13097 --------------------------
13099 -- pragma Compile_Time_Warning
13100 -- (boolean_EXPRESSION, static_string_EXPRESSION);
13102 when Pragma_Compile_Time_Warning =>
13103 GNAT_Pragma;
13104 Process_Compile_Time_Warning_Or_Error;
13106 ---------------------------
13107 -- Compiler_Unit_Warning --
13108 ---------------------------
13110 -- pragma Compiler_Unit_Warning;
13112 -- Historical note
13114 -- Originally, we had only pragma Compiler_Unit, and it resulted in
13115 -- errors not warnings. This means that we had introduced a big extra
13116 -- inertia to compiler changes, since even if we implemented a new
13117 -- feature, and even if all versions to be used for bootstrapping
13118 -- implemented this new feature, we could not use it, since old
13119 -- compilers would give errors for using this feature in units
13120 -- having Compiler_Unit pragmas.
13122 -- By changing Compiler_Unit to Compiler_Unit_Warning, we solve the
13123 -- problem. We no longer have any units mentioning Compiler_Unit,
13124 -- so old compilers see Compiler_Unit_Warning which is unrecognized,
13125 -- and thus generates a warning which can be ignored. So that deals
13126 -- with the problem of old compilers not implementing the newer form
13127 -- of the pragma.
13129 -- Newer compilers recognize the new pragma, but generate warning
13130 -- messages instead of errors, which again can be ignored in the
13131 -- case of an old compiler which implements a wanted new feature
13132 -- but at the time felt like warning about it for older compilers.
13134 -- We retain Compiler_Unit so that new compilers can be used to build
13135 -- older run-times that use this pragma. That's an unusual case, but
13136 -- it's easy enough to handle, so why not?
13138 when Pragma_Compiler_Unit
13139 | Pragma_Compiler_Unit_Warning
13141 GNAT_Pragma;
13142 Check_Arg_Count (0);
13144 -- Only recognized in main unit
13146 if Current_Sem_Unit = Main_Unit then
13147 Compiler_Unit := True;
13148 end if;
13150 -----------------------------
13151 -- Complete_Representation --
13152 -----------------------------
13154 -- pragma Complete_Representation;
13156 when Pragma_Complete_Representation =>
13157 GNAT_Pragma;
13158 Check_Arg_Count (0);
13160 if Nkind (Parent (N)) /= N_Record_Representation_Clause then
13161 Error_Pragma
13162 ("pragma & must appear within record representation clause");
13163 end if;
13165 ----------------------------
13166 -- Complex_Representation --
13167 ----------------------------
13169 -- pragma Complex_Representation ([Entity =>] LOCAL_NAME);
13171 when Pragma_Complex_Representation => Complex_Representation : declare
13172 E_Id : Entity_Id;
13173 E : Entity_Id;
13174 Ent : Entity_Id;
13176 begin
13177 GNAT_Pragma;
13178 Check_Arg_Count (1);
13179 Check_Optional_Identifier (Arg1, Name_Entity);
13180 Check_Arg_Is_Local_Name (Arg1);
13181 E_Id := Get_Pragma_Arg (Arg1);
13183 if Etype (E_Id) = Any_Type then
13184 return;
13185 end if;
13187 E := Entity (E_Id);
13189 if not Is_Record_Type (E) then
13190 Error_Pragma_Arg
13191 ("argument for pragma% must be record type", Arg1);
13192 end if;
13194 Ent := First_Entity (E);
13196 if No (Ent)
13197 or else No (Next_Entity (Ent))
13198 or else Present (Next_Entity (Next_Entity (Ent)))
13199 or else not Is_Floating_Point_Type (Etype (Ent))
13200 or else Etype (Ent) /= Etype (Next_Entity (Ent))
13201 then
13202 Error_Pragma_Arg
13203 ("record for pragma% must have two fields of the same "
13204 & "floating-point type", Arg1);
13206 else
13207 Set_Has_Complex_Representation (Base_Type (E));
13209 -- We need to treat the type has having a non-standard
13210 -- representation, for back-end purposes, even though in
13211 -- general a complex will have the default representation
13212 -- of a record with two real components.
13214 Set_Has_Non_Standard_Rep (Base_Type (E));
13215 end if;
13216 end Complex_Representation;
13218 -------------------------
13219 -- Component_Alignment --
13220 -------------------------
13222 -- pragma Component_Alignment (
13223 -- [Form =>] ALIGNMENT_CHOICE
13224 -- [, [Name =>] type_LOCAL_NAME]);
13226 -- ALIGNMENT_CHOICE ::=
13227 -- Component_Size
13228 -- | Component_Size_4
13229 -- | Storage_Unit
13230 -- | Default
13232 when Pragma_Component_Alignment => Component_AlignmentP : declare
13233 Args : Args_List (1 .. 2);
13234 Names : constant Name_List (1 .. 2) := (
13235 Name_Form,
13236 Name_Name);
13238 Form : Node_Id renames Args (1);
13239 Name : Node_Id renames Args (2);
13241 Atype : Component_Alignment_Kind;
13242 Typ : Entity_Id;
13244 begin
13245 GNAT_Pragma;
13246 Gather_Associations (Names, Args);
13248 if No (Form) then
13249 Error_Pragma ("missing Form argument for pragma%");
13250 end if;
13252 Check_Arg_Is_Identifier (Form);
13254 -- Get proper alignment, note that Default = Component_Size on all
13255 -- machines we have so far, and we want to set this value rather
13256 -- than the default value to indicate that it has been explicitly
13257 -- set (and thus will not get overridden by the default component
13258 -- alignment for the current scope)
13260 if Chars (Form) = Name_Component_Size then
13261 Atype := Calign_Component_Size;
13263 elsif Chars (Form) = Name_Component_Size_4 then
13264 Atype := Calign_Component_Size_4;
13266 elsif Chars (Form) = Name_Default then
13267 Atype := Calign_Component_Size;
13269 elsif Chars (Form) = Name_Storage_Unit then
13270 Atype := Calign_Storage_Unit;
13272 else
13273 Error_Pragma_Arg
13274 ("invalid Form parameter for pragma%", Form);
13275 end if;
13277 -- The pragma appears in a configuration file
13279 if No (Parent (N)) then
13280 Check_Valid_Configuration_Pragma;
13282 -- Capture the component alignment in a global variable when
13283 -- the pragma appears in a configuration file. Note that the
13284 -- scope stack is empty at this point and cannot be used to
13285 -- store the alignment value.
13287 Configuration_Component_Alignment := Atype;
13289 -- Case with no name, supplied, affects scope table entry
13291 elsif No (Name) then
13292 Scope_Stack.Table
13293 (Scope_Stack.Last).Component_Alignment_Default := Atype;
13295 -- Case of name supplied
13297 else
13298 Check_Arg_Is_Local_Name (Name);
13299 Find_Type (Name);
13300 Typ := Entity (Name);
13302 if Typ = Any_Type
13303 or else Rep_Item_Too_Early (Typ, N)
13304 then
13305 return;
13306 else
13307 Typ := Underlying_Type (Typ);
13308 end if;
13310 if not Is_Record_Type (Typ)
13311 and then not Is_Array_Type (Typ)
13312 then
13313 Error_Pragma_Arg
13314 ("Name parameter of pragma% must identify record or "
13315 & "array type", Name);
13316 end if;
13318 -- An explicit Component_Alignment pragma overrides an
13319 -- implicit pragma Pack, but not an explicit one.
13321 if not Has_Pragma_Pack (Base_Type (Typ)) then
13322 Set_Is_Packed (Base_Type (Typ), False);
13323 Set_Component_Alignment (Base_Type (Typ), Atype);
13324 end if;
13325 end if;
13326 end Component_AlignmentP;
13328 --------------------------------
13329 -- Constant_After_Elaboration --
13330 --------------------------------
13332 -- pragma Constant_After_Elaboration [ (boolean_EXPRESSION) ];
13334 when Pragma_Constant_After_Elaboration => Constant_After_Elaboration :
13335 declare
13336 Obj_Decl : Node_Id;
13337 Obj_Id : Entity_Id;
13339 begin
13340 GNAT_Pragma;
13341 Check_No_Identifiers;
13342 Check_At_Most_N_Arguments (1);
13344 Obj_Decl := Find_Related_Context (N, Do_Checks => True);
13346 -- Object declaration
13348 if Nkind (Obj_Decl) = N_Object_Declaration then
13349 null;
13351 -- Otherwise the pragma is associated with an illegal construct
13353 else
13354 Pragma_Misplaced;
13355 return;
13356 end if;
13358 Obj_Id := Defining_Entity (Obj_Decl);
13360 -- The object declaration must be a library-level variable which
13361 -- is either explicitly initialized or obtains a value during the
13362 -- elaboration of a package body (SPARK RM 3.3.1).
13364 if Ekind (Obj_Id) = E_Variable then
13365 if not Is_Library_Level_Entity (Obj_Id) then
13366 Error_Pragma
13367 ("pragma % must apply to a library level variable");
13368 return;
13369 end if;
13371 -- Otherwise the pragma applies to a constant, which is illegal
13373 else
13374 Error_Pragma ("pragma % must apply to a variable declaration");
13375 return;
13376 end if;
13378 -- A pragma that applies to a Ghost entity becomes Ghost for the
13379 -- purposes of legality checks and removal of ignored Ghost code.
13381 Mark_Ghost_Pragma (N, Obj_Id);
13383 -- Chain the pragma on the contract for completeness
13385 Add_Contract_Item (N, Obj_Id);
13387 -- Analyze the Boolean expression (if any)
13389 if Present (Arg1) then
13390 Check_Static_Boolean_Expression (Get_Pragma_Arg (Arg1));
13391 end if;
13392 end Constant_After_Elaboration;
13394 --------------------
13395 -- Contract_Cases --
13396 --------------------
13398 -- pragma Contract_Cases ((CONTRACT_CASE {, CONTRACT_CASE));
13400 -- CONTRACT_CASE ::= CASE_GUARD => CONSEQUENCE
13402 -- CASE_GUARD ::= boolean_EXPRESSION | others
13404 -- CONSEQUENCE ::= boolean_EXPRESSION
13406 -- Characteristics:
13408 -- * Analysis - The annotation undergoes initial checks to verify
13409 -- the legal placement and context. Secondary checks preanalyze the
13410 -- expressions in:
13412 -- Analyze_Contract_Cases_In_Decl_Part
13414 -- * Expansion - The annotation is expanded during the expansion of
13415 -- the related subprogram [body] contract as performed in:
13417 -- Expand_Subprogram_Contract
13419 -- * Template - The annotation utilizes the generic template of the
13420 -- related subprogram [body] when it is:
13422 -- aspect on subprogram declaration
13423 -- aspect on stand alone subprogram body
13424 -- pragma on stand alone subprogram body
13426 -- The annotation must prepare its own template when it is:
13428 -- pragma on subprogram declaration
13430 -- * Globals - Capture of global references must occur after full
13431 -- analysis.
13433 -- * Instance - The annotation is instantiated automatically when
13434 -- the related generic subprogram [body] is instantiated except for
13435 -- the "pragma on subprogram declaration" case. In that scenario
13436 -- the annotation must instantiate itself.
13438 when Pragma_Contract_Cases => Contract_Cases : declare
13439 Spec_Id : Entity_Id;
13440 Subp_Decl : Node_Id;
13441 Subp_Spec : Node_Id;
13443 begin
13444 GNAT_Pragma;
13445 Check_No_Identifiers;
13446 Check_Arg_Count (1);
13448 -- Ensure the proper placement of the pragma. Contract_Cases must
13449 -- be associated with a subprogram declaration or a body that acts
13450 -- as a spec.
13452 Subp_Decl :=
13453 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
13455 -- Entry
13457 if Nkind (Subp_Decl) = N_Entry_Declaration then
13458 null;
13460 -- Generic subprogram
13462 elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
13463 null;
13465 -- Body acts as spec
13467 elsif Nkind (Subp_Decl) = N_Subprogram_Body
13468 and then No (Corresponding_Spec (Subp_Decl))
13469 then
13470 null;
13472 -- Body stub acts as spec
13474 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
13475 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
13476 then
13477 null;
13479 -- Subprogram
13481 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
13482 Subp_Spec := Specification (Subp_Decl);
13484 -- Pragma Contract_Cases is forbidden on null procedures, as
13485 -- this may lead to potential ambiguities in behavior when
13486 -- interface null procedures are involved.
13488 if Nkind (Subp_Spec) = N_Procedure_Specification
13489 and then Null_Present (Subp_Spec)
13490 then
13491 Error_Msg_N (Fix_Error
13492 ("pragma % cannot apply to null procedure"), N);
13493 return;
13494 end if;
13496 else
13497 Pragma_Misplaced;
13498 return;
13499 end if;
13501 Spec_Id := Unique_Defining_Entity (Subp_Decl);
13503 -- A pragma that applies to a Ghost entity becomes Ghost for the
13504 -- purposes of legality checks and removal of ignored Ghost code.
13506 Mark_Ghost_Pragma (N, Spec_Id);
13507 Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
13509 -- Chain the pragma on the contract for further processing by
13510 -- Analyze_Contract_Cases_In_Decl_Part.
13512 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
13514 -- Fully analyze the pragma when it appears inside an entry
13515 -- or subprogram body because it cannot benefit from forward
13516 -- references.
13518 if Nkind_In (Subp_Decl, N_Entry_Body,
13519 N_Subprogram_Body,
13520 N_Subprogram_Body_Stub)
13521 then
13522 -- The legality checks of pragma Contract_Cases are affected by
13523 -- the SPARK mode in effect and the volatility of the context.
13524 -- Analyze all pragmas in a specific order.
13526 Analyze_If_Present (Pragma_SPARK_Mode);
13527 Analyze_If_Present (Pragma_Volatile_Function);
13528 Analyze_Contract_Cases_In_Decl_Part (N);
13529 end if;
13530 end Contract_Cases;
13532 ----------------
13533 -- Controlled --
13534 ----------------
13536 -- pragma Controlled (first_subtype_LOCAL_NAME);
13538 when Pragma_Controlled => Controlled : declare
13539 Arg : Node_Id;
13541 begin
13542 Check_No_Identifiers;
13543 Check_Arg_Count (1);
13544 Check_Arg_Is_Local_Name (Arg1);
13545 Arg := Get_Pragma_Arg (Arg1);
13547 if not Is_Entity_Name (Arg)
13548 or else not Is_Access_Type (Entity (Arg))
13549 then
13550 Error_Pragma_Arg ("pragma% requires access type", Arg1);
13551 else
13552 Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
13553 end if;
13554 end Controlled;
13556 ----------------
13557 -- Convention --
13558 ----------------
13560 -- pragma Convention ([Convention =>] convention_IDENTIFIER,
13561 -- [Entity =>] LOCAL_NAME);
13563 when Pragma_Convention => Convention : declare
13564 C : Convention_Id;
13565 E : Entity_Id;
13566 pragma Warnings (Off, C);
13567 pragma Warnings (Off, E);
13569 begin
13570 Check_Arg_Order ((Name_Convention, Name_Entity));
13571 Check_Ada_83_Warning;
13572 Check_Arg_Count (2);
13573 Process_Convention (C, E);
13575 -- A pragma that applies to a Ghost entity becomes Ghost for the
13576 -- purposes of legality checks and removal of ignored Ghost code.
13578 Mark_Ghost_Pragma (N, E);
13579 end Convention;
13581 ---------------------------
13582 -- Convention_Identifier --
13583 ---------------------------
13585 -- pragma Convention_Identifier ([Name =>] IDENTIFIER,
13586 -- [Convention =>] convention_IDENTIFIER);
13588 when Pragma_Convention_Identifier => Convention_Identifier : declare
13589 Idnam : Name_Id;
13590 Cname : Name_Id;
13592 begin
13593 GNAT_Pragma;
13594 Check_Arg_Order ((Name_Name, Name_Convention));
13595 Check_Arg_Count (2);
13596 Check_Optional_Identifier (Arg1, Name_Name);
13597 Check_Optional_Identifier (Arg2, Name_Convention);
13598 Check_Arg_Is_Identifier (Arg1);
13599 Check_Arg_Is_Identifier (Arg2);
13600 Idnam := Chars (Get_Pragma_Arg (Arg1));
13601 Cname := Chars (Get_Pragma_Arg (Arg2));
13603 if Is_Convention_Name (Cname) then
13604 Record_Convention_Identifier
13605 (Idnam, Get_Convention_Id (Cname));
13606 else
13607 Error_Pragma_Arg
13608 ("second arg for % pragma must be convention", Arg2);
13609 end if;
13610 end Convention_Identifier;
13612 ---------------
13613 -- CPP_Class --
13614 ---------------
13616 -- pragma CPP_Class ([Entity =>] LOCAL_NAME)
13618 when Pragma_CPP_Class =>
13619 GNAT_Pragma;
13621 if Warn_On_Obsolescent_Feature then
13622 Error_Msg_N
13623 ("'G'N'A'T pragma cpp'_class is now obsolete and has no "
13624 & "effect; replace it by pragma import?j?", N);
13625 end if;
13627 Check_Arg_Count (1);
13629 Rewrite (N,
13630 Make_Pragma (Loc,
13631 Chars => Name_Import,
13632 Pragma_Argument_Associations => New_List (
13633 Make_Pragma_Argument_Association (Loc,
13634 Expression => Make_Identifier (Loc, Name_CPP)),
13635 New_Copy (First (Pragma_Argument_Associations (N))))));
13636 Analyze (N);
13638 ---------------------
13639 -- CPP_Constructor --
13640 ---------------------
13642 -- pragma CPP_Constructor ([Entity =>] LOCAL_NAME
13643 -- [, [External_Name =>] static_string_EXPRESSION ]
13644 -- [, [Link_Name =>] static_string_EXPRESSION ]);
13646 when Pragma_CPP_Constructor => CPP_Constructor : declare
13647 Elmt : Elmt_Id;
13648 Id : Entity_Id;
13649 Def_Id : Entity_Id;
13650 Tag_Typ : Entity_Id;
13652 begin
13653 GNAT_Pragma;
13654 Check_At_Least_N_Arguments (1);
13655 Check_At_Most_N_Arguments (3);
13656 Check_Optional_Identifier (Arg1, Name_Entity);
13657 Check_Arg_Is_Local_Name (Arg1);
13659 Id := Get_Pragma_Arg (Arg1);
13660 Find_Program_Unit_Name (Id);
13662 -- If we did not find the name, we are done
13664 if Etype (Id) = Any_Type then
13665 return;
13666 end if;
13668 Def_Id := Entity (Id);
13670 -- Check if already defined as constructor
13672 if Is_Constructor (Def_Id) then
13673 Error_Msg_N
13674 ("??duplicate argument for pragma 'C'P'P_Constructor", Arg1);
13675 return;
13676 end if;
13678 if Ekind (Def_Id) = E_Function
13679 and then (Is_CPP_Class (Etype (Def_Id))
13680 or else (Is_Class_Wide_Type (Etype (Def_Id))
13681 and then
13682 Is_CPP_Class (Root_Type (Etype (Def_Id)))))
13683 then
13684 if Scope (Def_Id) /= Scope (Etype (Def_Id)) then
13685 Error_Msg_N
13686 ("'C'P'P constructor must be defined in the scope of "
13687 & "its returned type", Arg1);
13688 end if;
13690 if Arg_Count >= 2 then
13691 Set_Imported (Def_Id);
13692 Set_Is_Public (Def_Id);
13693 Process_Interface_Name (Def_Id, Arg2, Arg3, N);
13694 end if;
13696 Set_Has_Completion (Def_Id);
13697 Set_Is_Constructor (Def_Id);
13698 Set_Convention (Def_Id, Convention_CPP);
13700 -- Imported C++ constructors are not dispatching primitives
13701 -- because in C++ they don't have a dispatch table slot.
13702 -- However, in Ada the constructor has the profile of a
13703 -- function that returns a tagged type and therefore it has
13704 -- been treated as a primitive operation during semantic
13705 -- analysis. We now remove it from the list of primitive
13706 -- operations of the type.
13708 if Is_Tagged_Type (Etype (Def_Id))
13709 and then not Is_Class_Wide_Type (Etype (Def_Id))
13710 and then Is_Dispatching_Operation (Def_Id)
13711 then
13712 Tag_Typ := Etype (Def_Id);
13714 Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
13715 while Present (Elmt) and then Node (Elmt) /= Def_Id loop
13716 Next_Elmt (Elmt);
13717 end loop;
13719 Remove_Elmt (Primitive_Operations (Tag_Typ), Elmt);
13720 Set_Is_Dispatching_Operation (Def_Id, False);
13721 end if;
13723 -- For backward compatibility, if the constructor returns a
13724 -- class wide type, and we internally change the return type to
13725 -- the corresponding root type.
13727 if Is_Class_Wide_Type (Etype (Def_Id)) then
13728 Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
13729 end if;
13730 else
13731 Error_Pragma_Arg
13732 ("pragma% requires function returning a 'C'P'P_Class type",
13733 Arg1);
13734 end if;
13735 end CPP_Constructor;
13737 -----------------
13738 -- CPP_Virtual --
13739 -----------------
13741 when Pragma_CPP_Virtual =>
13742 GNAT_Pragma;
13744 if Warn_On_Obsolescent_Feature then
13745 Error_Msg_N
13746 ("'G'N'A'T pragma Cpp'_Virtual is now obsolete and has no "
13747 & "effect?j?", N);
13748 end if;
13750 ----------------
13751 -- CPP_Vtable --
13752 ----------------
13754 when Pragma_CPP_Vtable =>
13755 GNAT_Pragma;
13757 if Warn_On_Obsolescent_Feature then
13758 Error_Msg_N
13759 ("'G'N'A'T pragma Cpp'_Vtable is now obsolete and has no "
13760 & "effect?j?", N);
13761 end if;
13763 ---------
13764 -- CPU --
13765 ---------
13767 -- pragma CPU (EXPRESSION);
13769 when Pragma_CPU => CPU : declare
13770 P : constant Node_Id := Parent (N);
13771 Arg : Node_Id;
13772 Ent : Entity_Id;
13774 begin
13775 Ada_2012_Pragma;
13776 Check_No_Identifiers;
13777 Check_Arg_Count (1);
13779 -- Subprogram case
13781 if Nkind (P) = N_Subprogram_Body then
13782 Check_In_Main_Program;
13784 Arg := Get_Pragma_Arg (Arg1);
13785 Analyze_And_Resolve (Arg, Any_Integer);
13787 Ent := Defining_Unit_Name (Specification (P));
13789 if Nkind (Ent) = N_Defining_Program_Unit_Name then
13790 Ent := Defining_Identifier (Ent);
13791 end if;
13793 -- Must be static
13795 if not Is_OK_Static_Expression (Arg) then
13796 Flag_Non_Static_Expr
13797 ("main subprogram affinity is not static!", Arg);
13798 raise Pragma_Exit;
13800 -- If constraint error, then we already signalled an error
13802 elsif Raises_Constraint_Error (Arg) then
13803 null;
13805 -- Otherwise check in range
13807 else
13808 declare
13809 CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
13810 -- This is the entity System.Multiprocessors.CPU_Range;
13812 Val : constant Uint := Expr_Value (Arg);
13814 begin
13815 if Val < Expr_Value (Type_Low_Bound (CPU_Id))
13816 or else
13817 Val > Expr_Value (Type_High_Bound (CPU_Id))
13818 then
13819 Error_Pragma_Arg
13820 ("main subprogram CPU is out of range", Arg1);
13821 end if;
13822 end;
13823 end if;
13825 Set_Main_CPU
13826 (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
13828 -- Task case
13830 elsif Nkind (P) = N_Task_Definition then
13831 Arg := Get_Pragma_Arg (Arg1);
13832 Ent := Defining_Identifier (Parent (P));
13834 -- The expression must be analyzed in the special manner
13835 -- described in "Handling of Default and Per-Object
13836 -- Expressions" in sem.ads.
13838 Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
13840 -- Anything else is incorrect
13842 else
13843 Pragma_Misplaced;
13844 end if;
13846 -- Check duplicate pragma before we chain the pragma in the Rep
13847 -- Item chain of Ent.
13849 Check_Duplicate_Pragma (Ent);
13850 Record_Rep_Item (Ent, N);
13851 end CPU;
13853 --------------------
13854 -- Deadline_Floor --
13855 --------------------
13857 -- pragma Deadline_Floor (time_span_EXPRESSION);
13859 when Pragma_Deadline_Floor => Deadline_Floor : declare
13860 P : constant Node_Id := Parent (N);
13861 Arg : Node_Id;
13862 Ent : Entity_Id;
13864 begin
13865 GNAT_Pragma;
13866 Check_No_Identifiers;
13867 Check_Arg_Count (1);
13869 Arg := Get_Pragma_Arg (Arg1);
13871 -- The expression must be analyzed in the special manner described
13872 -- in "Handling of Default and Per-Object Expressions" in sem.ads.
13874 Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
13876 -- Only protected types allowed
13878 if Nkind (P) /= N_Protected_Definition then
13879 Pragma_Misplaced;
13881 else
13882 Ent := Defining_Identifier (Parent (P));
13884 -- Check duplicate pragma before we chain the pragma in the Rep
13885 -- Item chain of Ent.
13887 Check_Duplicate_Pragma (Ent);
13888 Record_Rep_Item (Ent, N);
13889 end if;
13890 end Deadline_Floor;
13892 -----------
13893 -- Debug --
13894 -----------
13896 -- pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
13898 when Pragma_Debug => Debug : declare
13899 Cond : Node_Id;
13900 Call : Node_Id;
13902 begin
13903 GNAT_Pragma;
13905 -- The condition for executing the call is that the expander
13906 -- is active and that we are not ignoring this debug pragma.
13908 Cond :=
13909 New_Occurrence_Of
13910 (Boolean_Literals
13911 (Expander_Active and then not Is_Ignored (N)),
13912 Loc);
13914 if not Is_Ignored (N) then
13915 Set_SCO_Pragma_Enabled (Loc);
13916 end if;
13918 if Arg_Count = 2 then
13919 Cond :=
13920 Make_And_Then (Loc,
13921 Left_Opnd => Relocate_Node (Cond),
13922 Right_Opnd => Get_Pragma_Arg (Arg1));
13923 Call := Get_Pragma_Arg (Arg2);
13924 else
13925 Call := Get_Pragma_Arg (Arg1);
13926 end if;
13928 if Nkind_In (Call,
13929 N_Indexed_Component,
13930 N_Function_Call,
13931 N_Identifier,
13932 N_Expanded_Name,
13933 N_Selected_Component)
13934 then
13935 -- If this pragma Debug comes from source, its argument was
13936 -- parsed as a name form (which is syntactically identical).
13937 -- In a generic context a parameterless call will be left as
13938 -- an expanded name (if global) or selected_component if local.
13939 -- Change it to a procedure call statement now.
13941 Change_Name_To_Procedure_Call_Statement (Call);
13943 elsif Nkind (Call) = N_Procedure_Call_Statement then
13945 -- Already in the form of a procedure call statement: nothing
13946 -- to do (could happen in case of an internally generated
13947 -- pragma Debug).
13949 null;
13951 else
13952 -- All other cases: diagnose error
13954 Error_Msg
13955 ("argument of pragma ""Debug"" is not procedure call",
13956 Sloc (Call));
13957 return;
13958 end if;
13960 -- Rewrite into a conditional with an appropriate condition. We
13961 -- wrap the procedure call in a block so that overhead from e.g.
13962 -- use of the secondary stack does not generate execution overhead
13963 -- for suppressed conditions.
13965 -- Normally the analysis that follows will freeze the subprogram
13966 -- being called. However, if the call is to a null procedure,
13967 -- we want to freeze it before creating the block, because the
13968 -- analysis that follows may be done with expansion disabled, in
13969 -- which case the body will not be generated, leading to spurious
13970 -- errors.
13972 if Nkind (Call) = N_Procedure_Call_Statement
13973 and then Is_Entity_Name (Name (Call))
13974 then
13975 Analyze (Name (Call));
13976 Freeze_Before (N, Entity (Name (Call)));
13977 end if;
13979 Rewrite (N,
13980 Make_Implicit_If_Statement (N,
13981 Condition => Cond,
13982 Then_Statements => New_List (
13983 Make_Block_Statement (Loc,
13984 Handled_Statement_Sequence =>
13985 Make_Handled_Sequence_Of_Statements (Loc,
13986 Statements => New_List (Relocate_Node (Call)))))));
13987 Analyze (N);
13989 -- Ignore pragma Debug in GNATprove mode. Do this rewriting
13990 -- after analysis of the normally rewritten node, to capture all
13991 -- references to entities, which avoids issuing wrong warnings
13992 -- about unused entities.
13994 if GNATprove_Mode then
13995 Rewrite (N, Make_Null_Statement (Loc));
13996 end if;
13997 end Debug;
13999 ------------------
14000 -- Debug_Policy --
14001 ------------------
14003 -- pragma Debug_Policy (On | Off | Check | Disable | Ignore)
14005 when Pragma_Debug_Policy =>
14006 GNAT_Pragma;
14007 Check_Arg_Count (1);
14008 Check_No_Identifiers;
14009 Check_Arg_Is_Identifier (Arg1);
14011 -- Exactly equivalent to pragma Check_Policy (Debug, arg), so
14012 -- rewrite it that way, and let the rest of the checking come
14013 -- from analyzing the rewritten pragma.
14015 Rewrite (N,
14016 Make_Pragma (Loc,
14017 Chars => Name_Check_Policy,
14018 Pragma_Argument_Associations => New_List (
14019 Make_Pragma_Argument_Association (Loc,
14020 Expression => Make_Identifier (Loc, Name_Debug)),
14022 Make_Pragma_Argument_Association (Loc,
14023 Expression => Get_Pragma_Arg (Arg1)))));
14024 Analyze (N);
14026 -------------------------------
14027 -- Default_Initial_Condition --
14028 -------------------------------
14030 -- pragma Default_Initial_Condition [ (null | boolean_EXPRESSION) ];
14032 when Pragma_Default_Initial_Condition => DIC : declare
14033 Discard : Boolean;
14034 Stmt : Node_Id;
14035 Typ : Entity_Id;
14037 begin
14038 GNAT_Pragma;
14039 Check_No_Identifiers;
14040 Check_At_Most_N_Arguments (1);
14042 Typ := Empty;
14043 Stmt := Prev (N);
14044 while Present (Stmt) loop
14046 -- Skip prior pragmas, but check for duplicates
14048 if Nkind (Stmt) = N_Pragma then
14049 if Pragma_Name (Stmt) = Pname then
14050 Duplication_Error
14051 (Prag => N,
14052 Prev => Stmt);
14053 raise Pragma_Exit;
14054 end if;
14056 -- Skip internally generated code. Note that derived type
14057 -- declarations of untagged types with discriminants are
14058 -- rewritten as private type declarations.
14060 elsif not Comes_From_Source (Stmt)
14061 and then Nkind (Stmt) /= N_Private_Type_Declaration
14062 then
14063 null;
14065 -- The associated private type [extension] has been found, stop
14066 -- the search.
14068 elsif Nkind_In (Stmt, N_Private_Extension_Declaration,
14069 N_Private_Type_Declaration)
14070 then
14071 Typ := Defining_Entity (Stmt);
14072 exit;
14074 -- The pragma does not apply to a legal construct, issue an
14075 -- error and stop the analysis.
14077 else
14078 Pragma_Misplaced;
14079 return;
14080 end if;
14082 Stmt := Prev (Stmt);
14083 end loop;
14085 -- The pragma does not apply to a legal construct, issue an error
14086 -- and stop the analysis.
14088 if No (Typ) then
14089 Pragma_Misplaced;
14090 return;
14091 end if;
14093 -- A pragma that applies to a Ghost entity becomes Ghost for the
14094 -- purposes of legality checks and removal of ignored Ghost code.
14096 Mark_Ghost_Pragma (N, Typ);
14098 -- The pragma signals that the type defines its own DIC assertion
14099 -- expression.
14101 Set_Has_Own_DIC (Typ);
14103 -- Chain the pragma on the rep item chain for further processing
14105 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
14107 -- Create the declaration of the procedure which verifies the
14108 -- assertion expression of pragma DIC at runtime.
14110 Build_DIC_Procedure_Declaration (Typ);
14111 end DIC;
14113 ----------------------------------
14114 -- Default_Scalar_Storage_Order --
14115 ----------------------------------
14117 -- pragma Default_Scalar_Storage_Order
14118 -- (High_Order_First | Low_Order_First);
14120 when Pragma_Default_Scalar_Storage_Order => DSSO : declare
14121 Default : Character;
14123 begin
14124 GNAT_Pragma;
14125 Check_Arg_Count (1);
14127 -- Default_Scalar_Storage_Order can appear as a configuration
14128 -- pragma, or in a declarative part of a package spec.
14130 if not Is_Configuration_Pragma then
14131 Check_Is_In_Decl_Part_Or_Package_Spec;
14132 end if;
14134 Check_No_Identifiers;
14135 Check_Arg_Is_One_Of
14136 (Arg1, Name_High_Order_First, Name_Low_Order_First);
14137 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
14138 Default := Fold_Upper (Name_Buffer (1));
14140 if not Support_Nondefault_SSO_On_Target
14141 and then (Ttypes.Bytes_Big_Endian /= (Default = 'H'))
14142 then
14143 if Warn_On_Unrecognized_Pragma then
14144 Error_Msg_N
14145 ("non-default Scalar_Storage_Order not supported "
14146 & "on target?g?", N);
14147 Error_Msg_N
14148 ("\pragma Default_Scalar_Storage_Order ignored?g?", N);
14149 end if;
14151 -- Here set the specified default
14153 else
14154 Opt.Default_SSO := Default;
14155 end if;
14156 end DSSO;
14158 --------------------------
14159 -- Default_Storage_Pool --
14160 --------------------------
14162 -- pragma Default_Storage_Pool (storage_pool_NAME | null);
14164 when Pragma_Default_Storage_Pool => Default_Storage_Pool : declare
14165 Pool : Node_Id;
14167 begin
14168 Ada_2012_Pragma;
14169 Check_Arg_Count (1);
14171 -- Default_Storage_Pool can appear as a configuration pragma, or
14172 -- in a declarative part of a package spec.
14174 if not Is_Configuration_Pragma then
14175 Check_Is_In_Decl_Part_Or_Package_Spec;
14176 end if;
14178 if From_Aspect_Specification (N) then
14179 declare
14180 E : constant Entity_Id := Entity (Corresponding_Aspect (N));
14181 begin
14182 if not In_Open_Scopes (E) then
14183 Error_Msg_N
14184 ("aspect must apply to package or subprogram", N);
14185 end if;
14186 end;
14187 end if;
14189 if Present (Arg1) then
14190 Pool := Get_Pragma_Arg (Arg1);
14192 -- Case of Default_Storage_Pool (null);
14194 if Nkind (Pool) = N_Null then
14195 Analyze (Pool);
14197 -- This is an odd case, this is not really an expression,
14198 -- so we don't have a type for it. So just set the type to
14199 -- Empty.
14201 Set_Etype (Pool, Empty);
14203 -- Case of Default_Storage_Pool (storage_pool_NAME);
14205 else
14206 -- If it's a configuration pragma, then the only allowed
14207 -- argument is "null".
14209 if Is_Configuration_Pragma then
14210 Error_Pragma_Arg ("NULL expected", Arg1);
14211 end if;
14213 -- The expected type for a non-"null" argument is
14214 -- Root_Storage_Pool'Class, and the pool must be a variable.
14216 Analyze_And_Resolve
14217 (Pool, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
14219 if Is_Variable (Pool) then
14221 -- A pragma that applies to a Ghost entity becomes Ghost
14222 -- for the purposes of legality checks and removal of
14223 -- ignored Ghost code.
14225 Mark_Ghost_Pragma (N, Entity (Pool));
14227 else
14228 Error_Pragma_Arg
14229 ("default storage pool must be a variable", Arg1);
14230 end if;
14231 end if;
14233 -- Record the pool name (or null). Freeze.Freeze_Entity for an
14234 -- access type will use this information to set the appropriate
14235 -- attributes of the access type.
14237 Default_Pool := Pool;
14238 end if;
14239 end Default_Storage_Pool;
14241 -------------
14242 -- Depends --
14243 -------------
14245 -- pragma Depends (DEPENDENCY_RELATION);
14247 -- DEPENDENCY_RELATION ::=
14248 -- null
14249 -- | (DEPENDENCY_CLAUSE {, DEPENDENCY_CLAUSE})
14251 -- DEPENDENCY_CLAUSE ::=
14252 -- OUTPUT_LIST =>[+] INPUT_LIST
14253 -- | NULL_DEPENDENCY_CLAUSE
14255 -- NULL_DEPENDENCY_CLAUSE ::= null => INPUT_LIST
14257 -- OUTPUT_LIST ::= OUTPUT | (OUTPUT {, OUTPUT})
14259 -- INPUT_LIST ::= null | INPUT | (INPUT {, INPUT})
14261 -- OUTPUT ::= NAME | FUNCTION_RESULT
14262 -- INPUT ::= NAME
14264 -- where FUNCTION_RESULT is a function Result attribute_reference
14266 -- Characteristics:
14268 -- * Analysis - The annotation undergoes initial checks to verify
14269 -- the legal placement and context. Secondary checks fully analyze
14270 -- the dependency clauses in:
14272 -- Analyze_Depends_In_Decl_Part
14274 -- * Expansion - None.
14276 -- * Template - The annotation utilizes the generic template of the
14277 -- related subprogram [body] when it is:
14279 -- aspect on subprogram declaration
14280 -- aspect on stand alone subprogram body
14281 -- pragma on stand alone subprogram body
14283 -- The annotation must prepare its own template when it is:
14285 -- pragma on subprogram declaration
14287 -- * Globals - Capture of global references must occur after full
14288 -- analysis.
14290 -- * Instance - The annotation is instantiated automatically when
14291 -- the related generic subprogram [body] is instantiated except for
14292 -- the "pragma on subprogram declaration" case. In that scenario
14293 -- the annotation must instantiate itself.
14295 when Pragma_Depends => Depends : declare
14296 Legal : Boolean;
14297 Spec_Id : Entity_Id;
14298 Subp_Decl : Node_Id;
14300 begin
14301 Analyze_Depends_Global (Spec_Id, Subp_Decl, Legal);
14303 if Legal then
14305 -- Chain the pragma on the contract for further processing by
14306 -- Analyze_Depends_In_Decl_Part.
14308 Add_Contract_Item (N, Spec_Id);
14310 -- Fully analyze the pragma when it appears inside an entry
14311 -- or subprogram body because it cannot benefit from forward
14312 -- references.
14314 if Nkind_In (Subp_Decl, N_Entry_Body,
14315 N_Subprogram_Body,
14316 N_Subprogram_Body_Stub)
14317 then
14318 -- The legality checks of pragmas Depends and Global are
14319 -- affected by the SPARK mode in effect and the volatility
14320 -- of the context. In addition these two pragmas are subject
14321 -- to an inherent order:
14323 -- 1) Global
14324 -- 2) Depends
14326 -- Analyze all these pragmas in the order outlined above
14328 Analyze_If_Present (Pragma_SPARK_Mode);
14329 Analyze_If_Present (Pragma_Volatile_Function);
14330 Analyze_If_Present (Pragma_Global);
14331 Analyze_Depends_In_Decl_Part (N);
14332 end if;
14333 end if;
14334 end Depends;
14336 ---------------------
14337 -- Detect_Blocking --
14338 ---------------------
14340 -- pragma Detect_Blocking;
14342 when Pragma_Detect_Blocking =>
14343 Ada_2005_Pragma;
14344 Check_Arg_Count (0);
14345 Check_Valid_Configuration_Pragma;
14346 Detect_Blocking := True;
14348 ------------------------------------
14349 -- Disable_Atomic_Synchronization --
14350 ------------------------------------
14352 -- pragma Disable_Atomic_Synchronization [(Entity)];
14354 when Pragma_Disable_Atomic_Synchronization =>
14355 GNAT_Pragma;
14356 Process_Disable_Enable_Atomic_Sync (Name_Suppress);
14358 -------------------
14359 -- Discard_Names --
14360 -------------------
14362 -- pragma Discard_Names [([On =>] LOCAL_NAME)];
14364 when Pragma_Discard_Names => Discard_Names : declare
14365 E : Entity_Id;
14366 E_Id : Node_Id;
14368 begin
14369 Check_Ada_83_Warning;
14371 -- Deal with configuration pragma case
14373 if Arg_Count = 0 and then Is_Configuration_Pragma then
14374 Global_Discard_Names := True;
14375 return;
14377 -- Otherwise, check correct appropriate context
14379 else
14380 Check_Is_In_Decl_Part_Or_Package_Spec;
14382 if Arg_Count = 0 then
14384 -- If there is no parameter, then from now on this pragma
14385 -- applies to any enumeration, exception or tagged type
14386 -- defined in the current declarative part, and recursively
14387 -- to any nested scope.
14389 Set_Discard_Names (Current_Scope);
14390 return;
14392 else
14393 Check_Arg_Count (1);
14394 Check_Optional_Identifier (Arg1, Name_On);
14395 Check_Arg_Is_Local_Name (Arg1);
14397 E_Id := Get_Pragma_Arg (Arg1);
14399 if Etype (E_Id) = Any_Type then
14400 return;
14401 else
14402 E := Entity (E_Id);
14403 end if;
14405 -- A pragma that applies to a Ghost entity becomes Ghost for
14406 -- the purposes of legality checks and removal of ignored
14407 -- Ghost code.
14409 Mark_Ghost_Pragma (N, E);
14411 if (Is_First_Subtype (E)
14412 and then
14413 (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
14414 or else Ekind (E) = E_Exception
14415 then
14416 Set_Discard_Names (E);
14417 Record_Rep_Item (E, N);
14419 else
14420 Error_Pragma_Arg
14421 ("inappropriate entity for pragma%", Arg1);
14422 end if;
14423 end if;
14424 end if;
14425 end Discard_Names;
14427 ------------------------
14428 -- Dispatching_Domain --
14429 ------------------------
14431 -- pragma Dispatching_Domain (EXPRESSION);
14433 when Pragma_Dispatching_Domain => Dispatching_Domain : declare
14434 P : constant Node_Id := Parent (N);
14435 Arg : Node_Id;
14436 Ent : Entity_Id;
14438 begin
14439 Ada_2012_Pragma;
14440 Check_No_Identifiers;
14441 Check_Arg_Count (1);
14443 -- This pragma is born obsolete, but not the aspect
14445 if not From_Aspect_Specification (N) then
14446 Check_Restriction
14447 (No_Obsolescent_Features, Pragma_Identifier (N));
14448 end if;
14450 if Nkind (P) = N_Task_Definition then
14451 Arg := Get_Pragma_Arg (Arg1);
14452 Ent := Defining_Identifier (Parent (P));
14454 -- A pragma that applies to a Ghost entity becomes Ghost for
14455 -- the purposes of legality checks and removal of ignored Ghost
14456 -- code.
14458 Mark_Ghost_Pragma (N, Ent);
14460 -- The expression must be analyzed in the special manner
14461 -- described in "Handling of Default and Per-Object
14462 -- Expressions" in sem.ads.
14464 Preanalyze_Spec_Expression (Arg, RTE (RE_Dispatching_Domain));
14466 -- Check duplicate pragma before we chain the pragma in the Rep
14467 -- Item chain of Ent.
14469 Check_Duplicate_Pragma (Ent);
14470 Record_Rep_Item (Ent, N);
14472 -- Anything else is incorrect
14474 else
14475 Pragma_Misplaced;
14476 end if;
14477 end Dispatching_Domain;
14479 ---------------
14480 -- Elaborate --
14481 ---------------
14483 -- pragma Elaborate (library_unit_NAME {, library_unit_NAME});
14485 when Pragma_Elaborate => Elaborate : declare
14486 Arg : Node_Id;
14487 Citem : Node_Id;
14489 begin
14490 -- Pragma must be in context items list of a compilation unit
14492 if not Is_In_Context_Clause then
14493 Pragma_Misplaced;
14494 end if;
14496 -- Must be at least one argument
14498 if Arg_Count = 0 then
14499 Error_Pragma ("pragma% requires at least one argument");
14500 end if;
14502 -- In Ada 83 mode, there can be no items following it in the
14503 -- context list except other pragmas and implicit with clauses
14504 -- (e.g. those added by use of Rtsfind). In Ada 95 mode, this
14505 -- placement rule does not apply.
14507 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
14508 Citem := Next (N);
14509 while Present (Citem) loop
14510 if Nkind (Citem) = N_Pragma
14511 or else (Nkind (Citem) = N_With_Clause
14512 and then Implicit_With (Citem))
14513 then
14514 null;
14515 else
14516 Error_Pragma
14517 ("(Ada 83) pragma% must be at end of context clause");
14518 end if;
14520 Next (Citem);
14521 end loop;
14522 end if;
14524 -- Finally, the arguments must all be units mentioned in a with
14525 -- clause in the same context clause. Note we already checked (in
14526 -- Par.Prag) that the arguments are all identifiers or selected
14527 -- components.
14529 Arg := Arg1;
14530 Outer : while Present (Arg) loop
14531 Citem := First (List_Containing (N));
14532 Inner : while Citem /= N loop
14533 if Nkind (Citem) = N_With_Clause
14534 and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
14535 then
14536 Set_Elaborate_Present (Citem, True);
14537 Set_Elab_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
14539 -- With the pragma present, elaboration calls on
14540 -- subprograms from the named unit need no further
14541 -- checks, as long as the pragma appears in the current
14542 -- compilation unit. If the pragma appears in some unit
14543 -- in the context, there might still be a need for an
14544 -- Elaborate_All_Desirable from the current compilation
14545 -- to the named unit, so we keep the check enabled.
14547 if In_Extended_Main_Source_Unit (N) then
14549 -- This does not apply in SPARK mode, where we allow
14550 -- pragma Elaborate, but we don't trust it to be right
14551 -- so we will still insist on the Elaborate_All.
14553 if SPARK_Mode /= On then
14554 Set_Suppress_Elaboration_Warnings
14555 (Entity (Name (Citem)));
14556 end if;
14557 end if;
14559 exit Inner;
14560 end if;
14562 Next (Citem);
14563 end loop Inner;
14565 if Citem = N then
14566 Error_Pragma_Arg
14567 ("argument of pragma% is not withed unit", Arg);
14568 end if;
14570 Next (Arg);
14571 end loop Outer;
14573 -- Give a warning if operating in static mode with one of the
14574 -- gnatwl/-gnatwE (elaboration warnings enabled) switches set.
14576 if Elab_Warnings
14577 and not Dynamic_Elaboration_Checks
14579 -- pragma Elaborate not allowed in SPARK mode anyway. We
14580 -- already complained about it, no point in generating any
14581 -- further complaint.
14583 and SPARK_Mode /= On
14584 then
14585 Error_Msg_N
14586 ("?l?use of pragma Elaborate may not be safe", N);
14587 Error_Msg_N
14588 ("?l?use pragma Elaborate_All instead if possible", N);
14589 end if;
14590 end Elaborate;
14592 -------------------
14593 -- Elaborate_All --
14594 -------------------
14596 -- pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
14598 when Pragma_Elaborate_All => Elaborate_All : declare
14599 Arg : Node_Id;
14600 Citem : Node_Id;
14602 begin
14603 Check_Ada_83_Warning;
14605 -- Pragma must be in context items list of a compilation unit
14607 if not Is_In_Context_Clause then
14608 Pragma_Misplaced;
14609 end if;
14611 -- Must be at least one argument
14613 if Arg_Count = 0 then
14614 Error_Pragma ("pragma% requires at least one argument");
14615 end if;
14617 -- Note: unlike pragma Elaborate, pragma Elaborate_All does not
14618 -- have to appear at the end of the context clause, but may
14619 -- appear mixed in with other items, even in Ada 83 mode.
14621 -- Final check: the arguments must all be units mentioned in
14622 -- a with clause in the same context clause. Note that we
14623 -- already checked (in Par.Prag) that all the arguments are
14624 -- either identifiers or selected components.
14626 Arg := Arg1;
14627 Outr : while Present (Arg) loop
14628 Citem := First (List_Containing (N));
14629 Innr : while Citem /= N loop
14630 if Nkind (Citem) = N_With_Clause
14631 and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
14632 then
14633 Set_Elaborate_All_Present (Citem, True);
14634 Set_Elab_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
14636 -- Suppress warnings and elaboration checks on the named
14637 -- unit if the pragma is in the current compilation, as
14638 -- for pragma Elaborate.
14640 if In_Extended_Main_Source_Unit (N) then
14641 Set_Suppress_Elaboration_Warnings
14642 (Entity (Name (Citem)));
14643 end if;
14644 exit Innr;
14645 end if;
14647 Next (Citem);
14648 end loop Innr;
14650 if Citem = N then
14651 Set_Error_Posted (N);
14652 Error_Pragma_Arg
14653 ("argument of pragma% is not withed unit", Arg);
14654 end if;
14656 Next (Arg);
14657 end loop Outr;
14658 end Elaborate_All;
14660 --------------------
14661 -- Elaborate_Body --
14662 --------------------
14664 -- pragma Elaborate_Body [( library_unit_NAME )];
14666 when Pragma_Elaborate_Body => Elaborate_Body : declare
14667 Cunit_Node : Node_Id;
14668 Cunit_Ent : Entity_Id;
14670 begin
14671 Check_Ada_83_Warning;
14672 Check_Valid_Library_Unit_Pragma;
14674 if Nkind (N) = N_Null_Statement then
14675 return;
14676 end if;
14678 Cunit_Node := Cunit (Current_Sem_Unit);
14679 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
14681 -- A pragma that applies to a Ghost entity becomes Ghost for the
14682 -- purposes of legality checks and removal of ignored Ghost code.
14684 Mark_Ghost_Pragma (N, Cunit_Ent);
14686 if Nkind_In (Unit (Cunit_Node), N_Package_Body,
14687 N_Subprogram_Body)
14688 then
14689 Error_Pragma ("pragma% must refer to a spec, not a body");
14690 else
14691 Set_Body_Required (Cunit_Node, True);
14692 Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
14694 -- If we are in dynamic elaboration mode, then we suppress
14695 -- elaboration warnings for the unit, since it is definitely
14696 -- fine NOT to do dynamic checks at the first level (and such
14697 -- checks will be suppressed because no elaboration boolean
14698 -- is created for Elaborate_Body packages).
14700 -- But in the static model of elaboration, Elaborate_Body is
14701 -- definitely NOT good enough to ensure elaboration safety on
14702 -- its own, since the body may WITH other units that are not
14703 -- safe from an elaboration point of view, so a client must
14704 -- still do an Elaborate_All on such units.
14706 -- Debug flag -gnatdD restores the old behavior of 3.13, where
14707 -- Elaborate_Body always suppressed elab warnings.
14709 if Dynamic_Elaboration_Checks or Debug_Flag_DD then
14710 Set_Suppress_Elaboration_Warnings (Cunit_Ent);
14711 end if;
14712 end if;
14713 end Elaborate_Body;
14715 ------------------------
14716 -- Elaboration_Checks --
14717 ------------------------
14719 -- pragma Elaboration_Checks (Static | Dynamic);
14721 when Pragma_Elaboration_Checks =>
14722 GNAT_Pragma;
14723 Check_Arg_Count (1);
14724 Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
14726 -- Set flag accordingly (ignore attempt at dynamic elaboration
14727 -- checks in SPARK mode).
14729 Dynamic_Elaboration_Checks :=
14730 Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic;
14732 ---------------
14733 -- Eliminate --
14734 ---------------
14736 -- pragma Eliminate (
14737 -- [Unit_Name =>] IDENTIFIER | SELECTED_COMPONENT,
14738 -- [,[Entity =>] IDENTIFIER |
14739 -- SELECTED_COMPONENT |
14740 -- STRING_LITERAL]
14741 -- [, OVERLOADING_RESOLUTION]);
14743 -- OVERLOADING_RESOLUTION ::= PARAMETER_AND_RESULT_TYPE_PROFILE |
14744 -- SOURCE_LOCATION
14746 -- PARAMETER_AND_RESULT_TYPE_PROFILE ::= PROCEDURE_PROFILE |
14747 -- FUNCTION_PROFILE
14749 -- PROCEDURE_PROFILE ::= Parameter_Types => PARAMETER_TYPES
14751 -- FUNCTION_PROFILE ::= [Parameter_Types => PARAMETER_TYPES,]
14752 -- Result_Type => result_SUBTYPE_NAME]
14754 -- PARAMETER_TYPES ::= (SUBTYPE_NAME {, SUBTYPE_NAME})
14755 -- SUBTYPE_NAME ::= STRING_LITERAL
14757 -- SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
14758 -- SOURCE_TRACE ::= STRING_LITERAL
14760 when Pragma_Eliminate => Eliminate : declare
14761 Args : Args_List (1 .. 5);
14762 Names : constant Name_List (1 .. 5) := (
14763 Name_Unit_Name,
14764 Name_Entity,
14765 Name_Parameter_Types,
14766 Name_Result_Type,
14767 Name_Source_Location);
14769 Unit_Name : Node_Id renames Args (1);
14770 Entity : Node_Id renames Args (2);
14771 Parameter_Types : Node_Id renames Args (3);
14772 Result_Type : Node_Id renames Args (4);
14773 Source_Location : Node_Id renames Args (5);
14775 begin
14776 GNAT_Pragma;
14777 Check_Valid_Configuration_Pragma;
14778 Gather_Associations (Names, Args);
14780 if No (Unit_Name) then
14781 Error_Pragma ("missing Unit_Name argument for pragma%");
14782 end if;
14784 if No (Entity)
14785 and then (Present (Parameter_Types)
14786 or else
14787 Present (Result_Type)
14788 or else
14789 Present (Source_Location))
14790 then
14791 Error_Pragma ("missing Entity argument for pragma%");
14792 end if;
14794 if (Present (Parameter_Types)
14795 or else
14796 Present (Result_Type))
14797 and then
14798 Present (Source_Location)
14799 then
14800 Error_Pragma
14801 ("parameter profile and source location cannot be used "
14802 & "together in pragma%");
14803 end if;
14805 Process_Eliminate_Pragma
14807 Unit_Name,
14808 Entity,
14809 Parameter_Types,
14810 Result_Type,
14811 Source_Location);
14812 end Eliminate;
14814 -----------------------------------
14815 -- Enable_Atomic_Synchronization --
14816 -----------------------------------
14818 -- pragma Enable_Atomic_Synchronization [(Entity)];
14820 when Pragma_Enable_Atomic_Synchronization =>
14821 GNAT_Pragma;
14822 Process_Disable_Enable_Atomic_Sync (Name_Unsuppress);
14824 ------------
14825 -- Export --
14826 ------------
14828 -- pragma Export (
14829 -- [ Convention =>] convention_IDENTIFIER,
14830 -- [ Entity =>] LOCAL_NAME
14831 -- [, [External_Name =>] static_string_EXPRESSION ]
14832 -- [, [Link_Name =>] static_string_EXPRESSION ]);
14834 when Pragma_Export => Export : declare
14835 C : Convention_Id;
14836 Def_Id : Entity_Id;
14838 pragma Warnings (Off, C);
14840 begin
14841 Check_Ada_83_Warning;
14842 Check_Arg_Order
14843 ((Name_Convention,
14844 Name_Entity,
14845 Name_External_Name,
14846 Name_Link_Name));
14848 Check_At_Least_N_Arguments (2);
14849 Check_At_Most_N_Arguments (4);
14851 -- In Relaxed_RM_Semantics, support old Ada 83 style:
14852 -- pragma Export (Entity, "external name");
14854 if Relaxed_RM_Semantics
14855 and then Arg_Count = 2
14856 and then Nkind (Expression (Arg2)) = N_String_Literal
14857 then
14858 C := Convention_C;
14859 Def_Id := Get_Pragma_Arg (Arg1);
14860 Analyze (Def_Id);
14862 if not Is_Entity_Name (Def_Id) then
14863 Error_Pragma_Arg ("entity name required", Arg1);
14864 end if;
14866 Def_Id := Entity (Def_Id);
14867 Set_Exported (Def_Id, Arg1);
14869 else
14870 Process_Convention (C, Def_Id);
14872 -- A pragma that applies to a Ghost entity becomes Ghost for
14873 -- the purposes of legality checks and removal of ignored Ghost
14874 -- code.
14876 Mark_Ghost_Pragma (N, Def_Id);
14878 if Ekind (Def_Id) /= E_Constant then
14879 Note_Possible_Modification
14880 (Get_Pragma_Arg (Arg2), Sure => False);
14881 end if;
14883 Process_Interface_Name (Def_Id, Arg3, Arg4, N);
14884 Set_Exported (Def_Id, Arg2);
14885 end if;
14887 -- If the entity is a deferred constant, propagate the information
14888 -- to the full view, because gigi elaborates the full view only.
14890 if Ekind (Def_Id) = E_Constant
14891 and then Present (Full_View (Def_Id))
14892 then
14893 declare
14894 Id2 : constant Entity_Id := Full_View (Def_Id);
14895 begin
14896 Set_Is_Exported (Id2, Is_Exported (Def_Id));
14897 Set_First_Rep_Item (Id2, First_Rep_Item (Def_Id));
14898 Set_Interface_Name (Id2, Einfo.Interface_Name (Def_Id));
14899 end;
14900 end if;
14901 end Export;
14903 ---------------------
14904 -- Export_Function --
14905 ---------------------
14907 -- pragma Export_Function (
14908 -- [Internal =>] LOCAL_NAME
14909 -- [, [External =>] EXTERNAL_SYMBOL]
14910 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
14911 -- [, [Result_Type =>] TYPE_DESIGNATOR]
14912 -- [, [Mechanism =>] MECHANISM]
14913 -- [, [Result_Mechanism =>] MECHANISM_NAME]);
14915 -- EXTERNAL_SYMBOL ::=
14916 -- IDENTIFIER
14917 -- | static_string_EXPRESSION
14919 -- PARAMETER_TYPES ::=
14920 -- null
14921 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
14923 -- TYPE_DESIGNATOR ::=
14924 -- subtype_NAME
14925 -- | subtype_Name ' Access
14927 -- MECHANISM ::=
14928 -- MECHANISM_NAME
14929 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
14931 -- MECHANISM_ASSOCIATION ::=
14932 -- [formal_parameter_NAME =>] MECHANISM_NAME
14934 -- MECHANISM_NAME ::=
14935 -- Value
14936 -- | Reference
14938 when Pragma_Export_Function => Export_Function : declare
14939 Args : Args_List (1 .. 6);
14940 Names : constant Name_List (1 .. 6) := (
14941 Name_Internal,
14942 Name_External,
14943 Name_Parameter_Types,
14944 Name_Result_Type,
14945 Name_Mechanism,
14946 Name_Result_Mechanism);
14948 Internal : Node_Id renames Args (1);
14949 External : Node_Id renames Args (2);
14950 Parameter_Types : Node_Id renames Args (3);
14951 Result_Type : Node_Id renames Args (4);
14952 Mechanism : Node_Id renames Args (5);
14953 Result_Mechanism : Node_Id renames Args (6);
14955 begin
14956 GNAT_Pragma;
14957 Gather_Associations (Names, Args);
14958 Process_Extended_Import_Export_Subprogram_Pragma (
14959 Arg_Internal => Internal,
14960 Arg_External => External,
14961 Arg_Parameter_Types => Parameter_Types,
14962 Arg_Result_Type => Result_Type,
14963 Arg_Mechanism => Mechanism,
14964 Arg_Result_Mechanism => Result_Mechanism);
14965 end Export_Function;
14967 -------------------
14968 -- Export_Object --
14969 -------------------
14971 -- pragma Export_Object (
14972 -- [Internal =>] LOCAL_NAME
14973 -- [, [External =>] EXTERNAL_SYMBOL]
14974 -- [, [Size =>] EXTERNAL_SYMBOL]);
14976 -- EXTERNAL_SYMBOL ::=
14977 -- IDENTIFIER
14978 -- | static_string_EXPRESSION
14980 -- PARAMETER_TYPES ::=
14981 -- null
14982 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
14984 -- TYPE_DESIGNATOR ::=
14985 -- subtype_NAME
14986 -- | subtype_Name ' Access
14988 -- MECHANISM ::=
14989 -- MECHANISM_NAME
14990 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
14992 -- MECHANISM_ASSOCIATION ::=
14993 -- [formal_parameter_NAME =>] MECHANISM_NAME
14995 -- MECHANISM_NAME ::=
14996 -- Value
14997 -- | Reference
14999 when Pragma_Export_Object => Export_Object : declare
15000 Args : Args_List (1 .. 3);
15001 Names : constant Name_List (1 .. 3) := (
15002 Name_Internal,
15003 Name_External,
15004 Name_Size);
15006 Internal : Node_Id renames Args (1);
15007 External : Node_Id renames Args (2);
15008 Size : Node_Id renames Args (3);
15010 begin
15011 GNAT_Pragma;
15012 Gather_Associations (Names, Args);
15013 Process_Extended_Import_Export_Object_Pragma (
15014 Arg_Internal => Internal,
15015 Arg_External => External,
15016 Arg_Size => Size);
15017 end Export_Object;
15019 ----------------------
15020 -- Export_Procedure --
15021 ----------------------
15023 -- pragma Export_Procedure (
15024 -- [Internal =>] LOCAL_NAME
15025 -- [, [External =>] EXTERNAL_SYMBOL]
15026 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
15027 -- [, [Mechanism =>] MECHANISM]);
15029 -- EXTERNAL_SYMBOL ::=
15030 -- IDENTIFIER
15031 -- | static_string_EXPRESSION
15033 -- PARAMETER_TYPES ::=
15034 -- null
15035 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
15037 -- TYPE_DESIGNATOR ::=
15038 -- subtype_NAME
15039 -- | subtype_Name ' Access
15041 -- MECHANISM ::=
15042 -- MECHANISM_NAME
15043 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
15045 -- MECHANISM_ASSOCIATION ::=
15046 -- [formal_parameter_NAME =>] MECHANISM_NAME
15048 -- MECHANISM_NAME ::=
15049 -- Value
15050 -- | Reference
15052 when Pragma_Export_Procedure => Export_Procedure : declare
15053 Args : Args_List (1 .. 4);
15054 Names : constant Name_List (1 .. 4) := (
15055 Name_Internal,
15056 Name_External,
15057 Name_Parameter_Types,
15058 Name_Mechanism);
15060 Internal : Node_Id renames Args (1);
15061 External : Node_Id renames Args (2);
15062 Parameter_Types : Node_Id renames Args (3);
15063 Mechanism : Node_Id renames Args (4);
15065 begin
15066 GNAT_Pragma;
15067 Gather_Associations (Names, Args);
15068 Process_Extended_Import_Export_Subprogram_Pragma (
15069 Arg_Internal => Internal,
15070 Arg_External => External,
15071 Arg_Parameter_Types => Parameter_Types,
15072 Arg_Mechanism => Mechanism);
15073 end Export_Procedure;
15075 ------------------
15076 -- Export_Value --
15077 ------------------
15079 -- pragma Export_Value (
15080 -- [Value =>] static_integer_EXPRESSION,
15081 -- [Link_Name =>] static_string_EXPRESSION);
15083 when Pragma_Export_Value =>
15084 GNAT_Pragma;
15085 Check_Arg_Order ((Name_Value, Name_Link_Name));
15086 Check_Arg_Count (2);
15088 Check_Optional_Identifier (Arg1, Name_Value);
15089 Check_Arg_Is_OK_Static_Expression (Arg1, Any_Integer);
15091 Check_Optional_Identifier (Arg2, Name_Link_Name);
15092 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
15094 -----------------------------
15095 -- Export_Valued_Procedure --
15096 -----------------------------
15098 -- pragma Export_Valued_Procedure (
15099 -- [Internal =>] LOCAL_NAME
15100 -- [, [External =>] EXTERNAL_SYMBOL,]
15101 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
15102 -- [, [Mechanism =>] MECHANISM]);
15104 -- EXTERNAL_SYMBOL ::=
15105 -- IDENTIFIER
15106 -- | static_string_EXPRESSION
15108 -- PARAMETER_TYPES ::=
15109 -- null
15110 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
15112 -- TYPE_DESIGNATOR ::=
15113 -- subtype_NAME
15114 -- | subtype_Name ' Access
15116 -- MECHANISM ::=
15117 -- MECHANISM_NAME
15118 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
15120 -- MECHANISM_ASSOCIATION ::=
15121 -- [formal_parameter_NAME =>] MECHANISM_NAME
15123 -- MECHANISM_NAME ::=
15124 -- Value
15125 -- | Reference
15127 when Pragma_Export_Valued_Procedure =>
15128 Export_Valued_Procedure : declare
15129 Args : Args_List (1 .. 4);
15130 Names : constant Name_List (1 .. 4) := (
15131 Name_Internal,
15132 Name_External,
15133 Name_Parameter_Types,
15134 Name_Mechanism);
15136 Internal : Node_Id renames Args (1);
15137 External : Node_Id renames Args (2);
15138 Parameter_Types : Node_Id renames Args (3);
15139 Mechanism : Node_Id renames Args (4);
15141 begin
15142 GNAT_Pragma;
15143 Gather_Associations (Names, Args);
15144 Process_Extended_Import_Export_Subprogram_Pragma (
15145 Arg_Internal => Internal,
15146 Arg_External => External,
15147 Arg_Parameter_Types => Parameter_Types,
15148 Arg_Mechanism => Mechanism);
15149 end Export_Valued_Procedure;
15151 -------------------
15152 -- Extend_System --
15153 -------------------
15155 -- pragma Extend_System ([Name =>] Identifier);
15157 when Pragma_Extend_System =>
15158 GNAT_Pragma;
15159 Check_Valid_Configuration_Pragma;
15160 Check_Arg_Count (1);
15161 Check_Optional_Identifier (Arg1, Name_Name);
15162 Check_Arg_Is_Identifier (Arg1);
15164 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
15166 if Name_Len > 4
15167 and then Name_Buffer (1 .. 4) = "aux_"
15168 then
15169 if Present (System_Extend_Pragma_Arg) then
15170 if Chars (Get_Pragma_Arg (Arg1)) =
15171 Chars (Expression (System_Extend_Pragma_Arg))
15172 then
15173 null;
15174 else
15175 Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
15176 Error_Pragma ("pragma% conflicts with that #");
15177 end if;
15179 else
15180 System_Extend_Pragma_Arg := Arg1;
15182 if not GNAT_Mode then
15183 System_Extend_Unit := Arg1;
15184 end if;
15185 end if;
15186 else
15187 Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
15188 end if;
15190 ------------------------
15191 -- Extensions_Allowed --
15192 ------------------------
15194 -- pragma Extensions_Allowed (ON | OFF);
15196 when Pragma_Extensions_Allowed =>
15197 GNAT_Pragma;
15198 Check_Arg_Count (1);
15199 Check_No_Identifiers;
15200 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
15202 if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
15203 Extensions_Allowed := True;
15204 Ada_Version := Ada_Version_Type'Last;
15206 else
15207 Extensions_Allowed := False;
15208 Ada_Version := Ada_Version_Explicit;
15209 Ada_Version_Pragma := Empty;
15210 end if;
15212 ------------------------
15213 -- Extensions_Visible --
15214 ------------------------
15216 -- pragma Extensions_Visible [ (boolean_EXPRESSION) ];
15218 -- Characteristics:
15220 -- * Analysis - The annotation is fully analyzed immediately upon
15221 -- elaboration as its expression must be static.
15223 -- * Expansion - None.
15225 -- * Template - The annotation utilizes the generic template of the
15226 -- related subprogram [body] when it is:
15228 -- aspect on subprogram declaration
15229 -- aspect on stand alone subprogram body
15230 -- pragma on stand alone subprogram body
15232 -- The annotation must prepare its own template when it is:
15234 -- pragma on subprogram declaration
15236 -- * Globals - Capture of global references must occur after full
15237 -- analysis.
15239 -- * Instance - The annotation is instantiated automatically when
15240 -- the related generic subprogram [body] is instantiated except for
15241 -- the "pragma on subprogram declaration" case. In that scenario
15242 -- the annotation must instantiate itself.
15244 when Pragma_Extensions_Visible => Extensions_Visible : declare
15245 Formal : Entity_Id;
15246 Has_OK_Formal : Boolean := False;
15247 Spec_Id : Entity_Id;
15248 Subp_Decl : Node_Id;
15250 begin
15251 GNAT_Pragma;
15252 Check_No_Identifiers;
15253 Check_At_Most_N_Arguments (1);
15255 Subp_Decl :=
15256 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
15258 -- Abstract subprogram declaration
15260 if Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
15261 null;
15263 -- Generic subprogram declaration
15265 elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
15266 null;
15268 -- Body acts as spec
15270 elsif Nkind (Subp_Decl) = N_Subprogram_Body
15271 and then No (Corresponding_Spec (Subp_Decl))
15272 then
15273 null;
15275 -- Body stub acts as spec
15277 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
15278 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
15279 then
15280 null;
15282 -- Subprogram declaration
15284 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
15285 null;
15287 -- Otherwise the pragma is associated with an illegal construct
15289 else
15290 Error_Pragma ("pragma % must apply to a subprogram");
15291 return;
15292 end if;
15294 -- Mark the pragma as Ghost if the related subprogram is also
15295 -- Ghost. This also ensures that any expansion performed further
15296 -- below will produce Ghost nodes.
15298 Spec_Id := Unique_Defining_Entity (Subp_Decl);
15299 Mark_Ghost_Pragma (N, Spec_Id);
15301 -- Chain the pragma on the contract for completeness
15303 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
15305 -- The legality checks of pragma Extension_Visible are affected
15306 -- by the SPARK mode in effect. Analyze all pragmas in specific
15307 -- order.
15309 Analyze_If_Present (Pragma_SPARK_Mode);
15311 -- Examine the formals of the related subprogram
15313 Formal := First_Formal (Spec_Id);
15314 while Present (Formal) loop
15316 -- At least one of the formals is of a specific tagged type,
15317 -- the pragma is legal.
15319 if Is_Specific_Tagged_Type (Etype (Formal)) then
15320 Has_OK_Formal := True;
15321 exit;
15323 -- A generic subprogram with at least one formal of a private
15324 -- type ensures the legality of the pragma because the actual
15325 -- may be specifically tagged. Note that this is verified by
15326 -- the check above at instantiation time.
15328 elsif Is_Private_Type (Etype (Formal))
15329 and then Is_Generic_Type (Etype (Formal))
15330 then
15331 Has_OK_Formal := True;
15332 exit;
15333 end if;
15335 Next_Formal (Formal);
15336 end loop;
15338 if not Has_OK_Formal then
15339 Error_Msg_Name_1 := Pname;
15340 Error_Msg_N (Fix_Error ("incorrect placement of pragma %"), N);
15341 Error_Msg_NE
15342 ("\subprogram & lacks parameter of specific tagged or "
15343 & "generic private type", N, Spec_Id);
15345 return;
15346 end if;
15348 -- Analyze the Boolean expression (if any)
15350 if Present (Arg1) then
15351 Check_Static_Boolean_Expression
15352 (Expression (Get_Argument (N, Spec_Id)));
15353 end if;
15354 end Extensions_Visible;
15356 --------------
15357 -- External --
15358 --------------
15360 -- pragma External (
15361 -- [ Convention =>] convention_IDENTIFIER,
15362 -- [ Entity =>] LOCAL_NAME
15363 -- [, [External_Name =>] static_string_EXPRESSION ]
15364 -- [, [Link_Name =>] static_string_EXPRESSION ]);
15366 when Pragma_External => External : declare
15367 C : Convention_Id;
15368 E : Entity_Id;
15369 pragma Warnings (Off, C);
15371 begin
15372 GNAT_Pragma;
15373 Check_Arg_Order
15374 ((Name_Convention,
15375 Name_Entity,
15376 Name_External_Name,
15377 Name_Link_Name));
15378 Check_At_Least_N_Arguments (2);
15379 Check_At_Most_N_Arguments (4);
15380 Process_Convention (C, E);
15382 -- A pragma that applies to a Ghost entity becomes Ghost for the
15383 -- purposes of legality checks and removal of ignored Ghost code.
15385 Mark_Ghost_Pragma (N, E);
15387 Note_Possible_Modification
15388 (Get_Pragma_Arg (Arg2), Sure => False);
15389 Process_Interface_Name (E, Arg3, Arg4, N);
15390 Set_Exported (E, Arg2);
15391 end External;
15393 --------------------------
15394 -- External_Name_Casing --
15395 --------------------------
15397 -- pragma External_Name_Casing (
15398 -- UPPERCASE | LOWERCASE
15399 -- [, AS_IS | UPPERCASE | LOWERCASE]);
15401 when Pragma_External_Name_Casing =>
15402 GNAT_Pragma;
15403 Check_No_Identifiers;
15405 if Arg_Count = 2 then
15406 Check_Arg_Is_One_Of
15407 (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
15409 case Chars (Get_Pragma_Arg (Arg2)) is
15410 when Name_As_Is =>
15411 Opt.External_Name_Exp_Casing := As_Is;
15413 when Name_Uppercase =>
15414 Opt.External_Name_Exp_Casing := Uppercase;
15416 when Name_Lowercase =>
15417 Opt.External_Name_Exp_Casing := Lowercase;
15419 when others =>
15420 null;
15421 end case;
15423 else
15424 Check_Arg_Count (1);
15425 end if;
15427 Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
15429 case Chars (Get_Pragma_Arg (Arg1)) is
15430 when Name_Uppercase =>
15431 Opt.External_Name_Imp_Casing := Uppercase;
15433 when Name_Lowercase =>
15434 Opt.External_Name_Imp_Casing := Lowercase;
15436 when others =>
15437 null;
15438 end case;
15440 ---------------
15441 -- Fast_Math --
15442 ---------------
15444 -- pragma Fast_Math;
15446 when Pragma_Fast_Math =>
15447 GNAT_Pragma;
15448 Check_No_Identifiers;
15449 Check_Valid_Configuration_Pragma;
15450 Fast_Math := True;
15452 --------------------------
15453 -- Favor_Top_Level --
15454 --------------------------
15456 -- pragma Favor_Top_Level (type_NAME);
15458 when Pragma_Favor_Top_Level => Favor_Top_Level : declare
15459 Typ : Entity_Id;
15461 begin
15462 GNAT_Pragma;
15463 Check_No_Identifiers;
15464 Check_Arg_Count (1);
15465 Check_Arg_Is_Local_Name (Arg1);
15466 Typ := Entity (Get_Pragma_Arg (Arg1));
15468 -- A pragma that applies to a Ghost entity becomes Ghost for the
15469 -- purposes of legality checks and removal of ignored Ghost code.
15471 Mark_Ghost_Pragma (N, Typ);
15473 -- If it's an access-to-subprogram type (in particular, not a
15474 -- subtype), set the flag on that type.
15476 if Is_Access_Subprogram_Type (Typ) then
15477 Set_Can_Use_Internal_Rep (Typ, False);
15479 -- Otherwise it's an error (name denotes the wrong sort of entity)
15481 else
15482 Error_Pragma_Arg
15483 ("access-to-subprogram type expected",
15484 Get_Pragma_Arg (Arg1));
15485 end if;
15486 end Favor_Top_Level;
15488 ---------------------------
15489 -- Finalize_Storage_Only --
15490 ---------------------------
15492 -- pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
15494 when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
15495 Assoc : constant Node_Id := Arg1;
15496 Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
15497 Typ : Entity_Id;
15499 begin
15500 GNAT_Pragma;
15501 Check_No_Identifiers;
15502 Check_Arg_Count (1);
15503 Check_Arg_Is_Local_Name (Arg1);
15505 Find_Type (Type_Id);
15506 Typ := Entity (Type_Id);
15508 if Typ = Any_Type
15509 or else Rep_Item_Too_Early (Typ, N)
15510 then
15511 return;
15512 else
15513 Typ := Underlying_Type (Typ);
15514 end if;
15516 if not Is_Controlled (Typ) then
15517 Error_Pragma ("pragma% must specify controlled type");
15518 end if;
15520 Check_First_Subtype (Arg1);
15522 if Finalize_Storage_Only (Typ) then
15523 Error_Pragma ("duplicate pragma%, only one allowed");
15525 elsif not Rep_Item_Too_Late (Typ, N) then
15526 Set_Finalize_Storage_Only (Base_Type (Typ), True);
15527 end if;
15528 end Finalize_Storage;
15530 -----------
15531 -- Ghost --
15532 -----------
15534 -- pragma Ghost [ (boolean_EXPRESSION) ];
15536 when Pragma_Ghost => Ghost : declare
15537 Context : Node_Id;
15538 Expr : Node_Id;
15539 Id : Entity_Id;
15540 Orig_Stmt : Node_Id;
15541 Prev_Id : Entity_Id;
15542 Stmt : Node_Id;
15544 begin
15545 GNAT_Pragma;
15546 Check_No_Identifiers;
15547 Check_At_Most_N_Arguments (1);
15549 Id := Empty;
15550 Stmt := Prev (N);
15551 while Present (Stmt) loop
15553 -- Skip prior pragmas, but check for duplicates
15555 if Nkind (Stmt) = N_Pragma then
15556 if Pragma_Name (Stmt) = Pname then
15557 Duplication_Error
15558 (Prag => N,
15559 Prev => Stmt);
15560 raise Pragma_Exit;
15561 end if;
15563 -- Task unit declared without a definition cannot be subject to
15564 -- pragma Ghost (SPARK RM 6.9(19)).
15566 elsif Nkind_In (Stmt, N_Single_Task_Declaration,
15567 N_Task_Type_Declaration)
15568 then
15569 Error_Pragma ("pragma % cannot apply to a task type");
15570 return;
15572 -- Skip internally generated code
15574 elsif not Comes_From_Source (Stmt) then
15575 Orig_Stmt := Original_Node (Stmt);
15577 -- When pragma Ghost applies to an untagged derivation, the
15578 -- derivation is transformed into a [sub]type declaration.
15580 if Nkind_In (Stmt, N_Full_Type_Declaration,
15581 N_Subtype_Declaration)
15582 and then Comes_From_Source (Orig_Stmt)
15583 and then Nkind (Orig_Stmt) = N_Full_Type_Declaration
15584 and then Nkind (Type_Definition (Orig_Stmt)) =
15585 N_Derived_Type_Definition
15586 then
15587 Id := Defining_Entity (Stmt);
15588 exit;
15590 -- When pragma Ghost applies to an object declaration which
15591 -- is initialized by means of a function call that returns
15592 -- on the secondary stack, the object declaration becomes a
15593 -- renaming.
15595 elsif Nkind (Stmt) = N_Object_Renaming_Declaration
15596 and then Comes_From_Source (Orig_Stmt)
15597 and then Nkind (Orig_Stmt) = N_Object_Declaration
15598 then
15599 Id := Defining_Entity (Stmt);
15600 exit;
15602 -- When pragma Ghost applies to an expression function, the
15603 -- expression function is transformed into a subprogram.
15605 elsif Nkind (Stmt) = N_Subprogram_Declaration
15606 and then Comes_From_Source (Orig_Stmt)
15607 and then Nkind (Orig_Stmt) = N_Expression_Function
15608 then
15609 Id := Defining_Entity (Stmt);
15610 exit;
15611 end if;
15613 -- The pragma applies to a legal construct, stop the traversal
15615 elsif Nkind_In (Stmt, N_Abstract_Subprogram_Declaration,
15616 N_Full_Type_Declaration,
15617 N_Generic_Subprogram_Declaration,
15618 N_Object_Declaration,
15619 N_Private_Extension_Declaration,
15620 N_Private_Type_Declaration,
15621 N_Subprogram_Declaration,
15622 N_Subtype_Declaration)
15623 then
15624 Id := Defining_Entity (Stmt);
15625 exit;
15627 -- The pragma does not apply to a legal construct, issue an
15628 -- error and stop the analysis.
15630 else
15631 Error_Pragma
15632 ("pragma % must apply to an object, package, subprogram "
15633 & "or type");
15634 return;
15635 end if;
15637 Stmt := Prev (Stmt);
15638 end loop;
15640 Context := Parent (N);
15642 -- Handle compilation units
15644 if Nkind (Context) = N_Compilation_Unit_Aux then
15645 Context := Unit (Parent (Context));
15646 end if;
15648 -- Protected and task types cannot be subject to pragma Ghost
15649 -- (SPARK RM 6.9(19)).
15651 if Nkind_In (Context, N_Protected_Body, N_Protected_Definition)
15652 then
15653 Error_Pragma ("pragma % cannot apply to a protected type");
15654 return;
15656 elsif Nkind_In (Context, N_Task_Body, N_Task_Definition) then
15657 Error_Pragma ("pragma % cannot apply to a task type");
15658 return;
15659 end if;
15661 if No (Id) then
15663 -- When pragma Ghost is associated with a [generic] package, it
15664 -- appears in the visible declarations.
15666 if Nkind (Context) = N_Package_Specification
15667 and then Present (Visible_Declarations (Context))
15668 and then List_Containing (N) = Visible_Declarations (Context)
15669 then
15670 Id := Defining_Entity (Context);
15672 -- Pragma Ghost applies to a stand alone subprogram body
15674 elsif Nkind (Context) = N_Subprogram_Body
15675 and then No (Corresponding_Spec (Context))
15676 then
15677 Id := Defining_Entity (Context);
15679 -- Pragma Ghost applies to a subprogram declaration that acts
15680 -- as a compilation unit.
15682 elsif Nkind (Context) = N_Subprogram_Declaration then
15683 Id := Defining_Entity (Context);
15684 end if;
15685 end if;
15687 if No (Id) then
15688 Error_Pragma
15689 ("pragma % must apply to an object, package, subprogram or "
15690 & "type");
15691 return;
15692 end if;
15694 -- Handle completions of types and constants that are subject to
15695 -- pragma Ghost.
15697 if Is_Record_Type (Id) or else Ekind (Id) = E_Constant then
15698 Prev_Id := Incomplete_Or_Partial_View (Id);
15700 if Present (Prev_Id) and then not Is_Ghost_Entity (Prev_Id) then
15701 Error_Msg_Name_1 := Pname;
15703 -- The full declaration of a deferred constant cannot be
15704 -- subject to pragma Ghost unless the deferred declaration
15705 -- is also Ghost (SPARK RM 6.9(9)).
15707 if Ekind (Prev_Id) = E_Constant then
15708 Error_Msg_Name_1 := Pname;
15709 Error_Msg_NE (Fix_Error
15710 ("pragma % must apply to declaration of deferred "
15711 & "constant &"), N, Id);
15712 return;
15714 -- Pragma Ghost may appear on the full view of an incomplete
15715 -- type because the incomplete declaration lacks aspects and
15716 -- cannot be subject to pragma Ghost.
15718 elsif Ekind (Prev_Id) = E_Incomplete_Type then
15719 null;
15721 -- The full declaration of a type cannot be subject to
15722 -- pragma Ghost unless the partial view is also Ghost
15723 -- (SPARK RM 6.9(9)).
15725 else
15726 Error_Msg_NE (Fix_Error
15727 ("pragma % must apply to partial view of type &"),
15728 N, Id);
15729 return;
15730 end if;
15731 end if;
15733 -- A synchronized object cannot be subject to pragma Ghost
15734 -- (SPARK RM 6.9(19)).
15736 elsif Ekind (Id) = E_Variable then
15737 if Is_Protected_Type (Etype (Id)) then
15738 Error_Pragma ("pragma % cannot apply to a protected object");
15739 return;
15741 elsif Is_Task_Type (Etype (Id)) then
15742 Error_Pragma ("pragma % cannot apply to a task object");
15743 return;
15744 end if;
15745 end if;
15747 -- Analyze the Boolean expression (if any)
15749 if Present (Arg1) then
15750 Expr := Get_Pragma_Arg (Arg1);
15752 Analyze_And_Resolve (Expr, Standard_Boolean);
15754 if Is_OK_Static_Expression (Expr) then
15756 -- "Ghostness" cannot be turned off once enabled within a
15757 -- region (SPARK RM 6.9(6)).
15759 if Is_False (Expr_Value (Expr))
15760 and then Ghost_Mode > None
15761 then
15762 Error_Pragma
15763 ("pragma % with value False cannot appear in enabled "
15764 & "ghost region");
15765 return;
15766 end if;
15768 -- Otherwie the expression is not static
15770 else
15771 Error_Pragma_Arg
15772 ("expression of pragma % must be static", Expr);
15773 return;
15774 end if;
15775 end if;
15777 Set_Is_Ghost_Entity (Id);
15778 end Ghost;
15780 ------------
15781 -- Global --
15782 ------------
15784 -- pragma Global (GLOBAL_SPECIFICATION);
15786 -- GLOBAL_SPECIFICATION ::=
15787 -- null
15788 -- | (GLOBAL_LIST)
15789 -- | (MODED_GLOBAL_LIST {, MODED_GLOBAL_LIST})
15791 -- MODED_GLOBAL_LIST ::= MODE_SELECTOR => GLOBAL_LIST
15793 -- MODE_SELECTOR ::= In_Out | Input | Output | Proof_In
15794 -- GLOBAL_LIST ::= GLOBAL_ITEM | (GLOBAL_ITEM {, GLOBAL_ITEM})
15795 -- GLOBAL_ITEM ::= NAME
15797 -- Characteristics:
15799 -- * Analysis - The annotation undergoes initial checks to verify
15800 -- the legal placement and context. Secondary checks fully analyze
15801 -- the dependency clauses in:
15803 -- Analyze_Global_In_Decl_Part
15805 -- * Expansion - None.
15807 -- * Template - The annotation utilizes the generic template of the
15808 -- related subprogram [body] when it is:
15810 -- aspect on subprogram declaration
15811 -- aspect on stand alone subprogram body
15812 -- pragma on stand alone subprogram body
15814 -- The annotation must prepare its own template when it is:
15816 -- pragma on subprogram declaration
15818 -- * Globals - Capture of global references must occur after full
15819 -- analysis.
15821 -- * Instance - The annotation is instantiated automatically when
15822 -- the related generic subprogram [body] is instantiated except for
15823 -- the "pragma on subprogram declaration" case. In that scenario
15824 -- the annotation must instantiate itself.
15826 when Pragma_Global => Global : declare
15827 Legal : Boolean;
15828 Spec_Id : Entity_Id;
15829 Subp_Decl : Node_Id;
15831 begin
15832 Analyze_Depends_Global (Spec_Id, Subp_Decl, Legal);
15834 if Legal then
15836 -- Chain the pragma on the contract for further processing by
15837 -- Analyze_Global_In_Decl_Part.
15839 Add_Contract_Item (N, Spec_Id);
15841 -- Fully analyze the pragma when it appears inside an entry
15842 -- or subprogram body because it cannot benefit from forward
15843 -- references.
15845 if Nkind_In (Subp_Decl, N_Entry_Body,
15846 N_Subprogram_Body,
15847 N_Subprogram_Body_Stub)
15848 then
15849 -- The legality checks of pragmas Depends and Global are
15850 -- affected by the SPARK mode in effect and the volatility
15851 -- of the context. In addition these two pragmas are subject
15852 -- to an inherent order:
15854 -- 1) Global
15855 -- 2) Depends
15857 -- Analyze all these pragmas in the order outlined above
15859 Analyze_If_Present (Pragma_SPARK_Mode);
15860 Analyze_If_Present (Pragma_Volatile_Function);
15861 Analyze_Global_In_Decl_Part (N);
15862 Analyze_If_Present (Pragma_Depends);
15863 end if;
15864 end if;
15865 end Global;
15867 -----------
15868 -- Ident --
15869 -----------
15871 -- pragma Ident (static_string_EXPRESSION)
15873 -- Note: pragma Comment shares this processing. Pragma Ident is
15874 -- identical in effect to pragma Commment.
15876 when Pragma_Comment
15877 | Pragma_Ident
15879 Ident : declare
15880 Str : Node_Id;
15882 begin
15883 GNAT_Pragma;
15884 Check_Arg_Count (1);
15885 Check_No_Identifiers;
15886 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
15887 Store_Note (N);
15889 Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
15891 declare
15892 CS : Node_Id;
15893 GP : Node_Id;
15895 begin
15896 GP := Parent (Parent (N));
15898 if Nkind_In (GP, N_Package_Declaration,
15899 N_Generic_Package_Declaration)
15900 then
15901 GP := Parent (GP);
15902 end if;
15904 -- If we have a compilation unit, then record the ident value,
15905 -- checking for improper duplication.
15907 if Nkind (GP) = N_Compilation_Unit then
15908 CS := Ident_String (Current_Sem_Unit);
15910 if Present (CS) then
15912 -- If we have multiple instances, concatenate them, but
15913 -- not in ASIS, where we want the original tree.
15915 if not ASIS_Mode then
15916 Start_String (Strval (CS));
15917 Store_String_Char (' ');
15918 Store_String_Chars (Strval (Str));
15919 Set_Strval (CS, End_String);
15920 end if;
15922 else
15923 Set_Ident_String (Current_Sem_Unit, Str);
15924 end if;
15926 -- For subunits, we just ignore the Ident, since in GNAT these
15927 -- are not separate object files, and hence not separate units
15928 -- in the unit table.
15930 elsif Nkind (GP) = N_Subunit then
15931 null;
15932 end if;
15933 end;
15934 end Ident;
15936 -------------------
15937 -- Ignore_Pragma --
15938 -------------------
15940 -- pragma Ignore_Pragma (pragma_IDENTIFIER);
15942 -- Entirely handled in the parser, nothing to do here
15944 when Pragma_Ignore_Pragma =>
15945 null;
15947 ----------------------------
15948 -- Implementation_Defined --
15949 ----------------------------
15951 -- pragma Implementation_Defined (LOCAL_NAME);
15953 -- Marks previously declared entity as implementation defined. For
15954 -- an overloaded entity, applies to the most recent homonym.
15956 -- pragma Implementation_Defined;
15958 -- The form with no arguments appears anywhere within a scope, most
15959 -- typically a package spec, and indicates that all entities that are
15960 -- defined within the package spec are Implementation_Defined.
15962 when Pragma_Implementation_Defined => Implementation_Defined : declare
15963 Ent : Entity_Id;
15965 begin
15966 GNAT_Pragma;
15967 Check_No_Identifiers;
15969 -- Form with no arguments
15971 if Arg_Count = 0 then
15972 Set_Is_Implementation_Defined (Current_Scope);
15974 -- Form with one argument
15976 else
15977 Check_Arg_Count (1);
15978 Check_Arg_Is_Local_Name (Arg1);
15979 Ent := Entity (Get_Pragma_Arg (Arg1));
15980 Set_Is_Implementation_Defined (Ent);
15981 end if;
15982 end Implementation_Defined;
15984 -----------------
15985 -- Implemented --
15986 -----------------
15988 -- pragma Implemented (procedure_LOCAL_NAME, IMPLEMENTATION_KIND);
15990 -- IMPLEMENTATION_KIND ::=
15991 -- By_Entry | By_Protected_Procedure | By_Any | Optional
15993 -- "By_Any" and "Optional" are treated as synonyms in order to
15994 -- support Ada 2012 aspect Synchronization.
15996 when Pragma_Implemented => Implemented : declare
15997 Proc_Id : Entity_Id;
15998 Typ : Entity_Id;
16000 begin
16001 Ada_2012_Pragma;
16002 Check_Arg_Count (2);
16003 Check_No_Identifiers;
16004 Check_Arg_Is_Identifier (Arg1);
16005 Check_Arg_Is_Local_Name (Arg1);
16006 Check_Arg_Is_One_Of (Arg2,
16007 Name_By_Any,
16008 Name_By_Entry,
16009 Name_By_Protected_Procedure,
16010 Name_Optional);
16012 -- Extract the name of the local procedure
16014 Proc_Id := Entity (Get_Pragma_Arg (Arg1));
16016 -- Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
16017 -- primitive procedure of a synchronized tagged type.
16019 if Ekind (Proc_Id) = E_Procedure
16020 and then Is_Primitive (Proc_Id)
16021 and then Present (First_Formal (Proc_Id))
16022 then
16023 Typ := Etype (First_Formal (Proc_Id));
16025 if Is_Tagged_Type (Typ)
16026 and then
16028 -- Check for a protected, a synchronized or a task interface
16030 ((Is_Interface (Typ)
16031 and then Is_Synchronized_Interface (Typ))
16033 -- Check for a protected type or a task type that implements
16034 -- an interface.
16036 or else
16037 (Is_Concurrent_Record_Type (Typ)
16038 and then Present (Interfaces (Typ)))
16040 -- In analysis-only mode, examine original protected type
16042 or else
16043 (Nkind (Parent (Typ)) = N_Protected_Type_Declaration
16044 and then Present (Interface_List (Parent (Typ))))
16046 -- Check for a private record extension with keyword
16047 -- "synchronized".
16049 or else
16050 (Ekind_In (Typ, E_Record_Type_With_Private,
16051 E_Record_Subtype_With_Private)
16052 and then Synchronized_Present (Parent (Typ))))
16053 then
16054 null;
16055 else
16056 Error_Pragma_Arg
16057 ("controlling formal must be of synchronized tagged type",
16058 Arg1);
16059 return;
16060 end if;
16062 -- Procedures declared inside a protected type must be accepted
16064 elsif Ekind (Proc_Id) = E_Procedure
16065 and then Is_Protected_Type (Scope (Proc_Id))
16066 then
16067 null;
16069 -- The first argument is not a primitive procedure
16071 else
16072 Error_Pragma_Arg
16073 ("pragma % must be applied to a primitive procedure", Arg1);
16074 return;
16075 end if;
16077 -- Ada 2012 (AI05-0030): Cannot apply the implementation_kind
16078 -- By_Protected_Procedure to the primitive procedure of a task
16079 -- interface.
16081 if Chars (Arg2) = Name_By_Protected_Procedure
16082 and then Is_Interface (Typ)
16083 and then Is_Task_Interface (Typ)
16084 then
16085 Error_Pragma_Arg
16086 ("implementation kind By_Protected_Procedure cannot be "
16087 & "applied to a task interface primitive", Arg2);
16088 return;
16089 end if;
16091 Record_Rep_Item (Proc_Id, N);
16092 end Implemented;
16094 ----------------------
16095 -- Implicit_Packing --
16096 ----------------------
16098 -- pragma Implicit_Packing;
16100 when Pragma_Implicit_Packing =>
16101 GNAT_Pragma;
16102 Check_Arg_Count (0);
16103 Implicit_Packing := True;
16105 ------------
16106 -- Import --
16107 ------------
16109 -- pragma Import (
16110 -- [Convention =>] convention_IDENTIFIER,
16111 -- [Entity =>] LOCAL_NAME
16112 -- [, [External_Name =>] static_string_EXPRESSION ]
16113 -- [, [Link_Name =>] static_string_EXPRESSION ]);
16115 when Pragma_Import =>
16116 Check_Ada_83_Warning;
16117 Check_Arg_Order
16118 ((Name_Convention,
16119 Name_Entity,
16120 Name_External_Name,
16121 Name_Link_Name));
16123 Check_At_Least_N_Arguments (2);
16124 Check_At_Most_N_Arguments (4);
16125 Process_Import_Or_Interface;
16127 ---------------------
16128 -- Import_Function --
16129 ---------------------
16131 -- pragma Import_Function (
16132 -- [Internal =>] LOCAL_NAME,
16133 -- [, [External =>] EXTERNAL_SYMBOL]
16134 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
16135 -- [, [Result_Type =>] SUBTYPE_MARK]
16136 -- [, [Mechanism =>] MECHANISM]
16137 -- [, [Result_Mechanism =>] MECHANISM_NAME]);
16139 -- EXTERNAL_SYMBOL ::=
16140 -- IDENTIFIER
16141 -- | static_string_EXPRESSION
16143 -- PARAMETER_TYPES ::=
16144 -- null
16145 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
16147 -- TYPE_DESIGNATOR ::=
16148 -- subtype_NAME
16149 -- | subtype_Name ' Access
16151 -- MECHANISM ::=
16152 -- MECHANISM_NAME
16153 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
16155 -- MECHANISM_ASSOCIATION ::=
16156 -- [formal_parameter_NAME =>] MECHANISM_NAME
16158 -- MECHANISM_NAME ::=
16159 -- Value
16160 -- | Reference
16162 when Pragma_Import_Function => Import_Function : declare
16163 Args : Args_List (1 .. 6);
16164 Names : constant Name_List (1 .. 6) := (
16165 Name_Internal,
16166 Name_External,
16167 Name_Parameter_Types,
16168 Name_Result_Type,
16169 Name_Mechanism,
16170 Name_Result_Mechanism);
16172 Internal : Node_Id renames Args (1);
16173 External : Node_Id renames Args (2);
16174 Parameter_Types : Node_Id renames Args (3);
16175 Result_Type : Node_Id renames Args (4);
16176 Mechanism : Node_Id renames Args (5);
16177 Result_Mechanism : Node_Id renames Args (6);
16179 begin
16180 GNAT_Pragma;
16181 Gather_Associations (Names, Args);
16182 Process_Extended_Import_Export_Subprogram_Pragma (
16183 Arg_Internal => Internal,
16184 Arg_External => External,
16185 Arg_Parameter_Types => Parameter_Types,
16186 Arg_Result_Type => Result_Type,
16187 Arg_Mechanism => Mechanism,
16188 Arg_Result_Mechanism => Result_Mechanism);
16189 end Import_Function;
16191 -------------------
16192 -- Import_Object --
16193 -------------------
16195 -- pragma Import_Object (
16196 -- [Internal =>] LOCAL_NAME
16197 -- [, [External =>] EXTERNAL_SYMBOL]
16198 -- [, [Size =>] EXTERNAL_SYMBOL]);
16200 -- EXTERNAL_SYMBOL ::=
16201 -- IDENTIFIER
16202 -- | static_string_EXPRESSION
16204 when Pragma_Import_Object => Import_Object : declare
16205 Args : Args_List (1 .. 3);
16206 Names : constant Name_List (1 .. 3) := (
16207 Name_Internal,
16208 Name_External,
16209 Name_Size);
16211 Internal : Node_Id renames Args (1);
16212 External : Node_Id renames Args (2);
16213 Size : Node_Id renames Args (3);
16215 begin
16216 GNAT_Pragma;
16217 Gather_Associations (Names, Args);
16218 Process_Extended_Import_Export_Object_Pragma (
16219 Arg_Internal => Internal,
16220 Arg_External => External,
16221 Arg_Size => Size);
16222 end Import_Object;
16224 ----------------------
16225 -- Import_Procedure --
16226 ----------------------
16228 -- pragma Import_Procedure (
16229 -- [Internal =>] LOCAL_NAME
16230 -- [, [External =>] EXTERNAL_SYMBOL]
16231 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
16232 -- [, [Mechanism =>] MECHANISM]);
16234 -- EXTERNAL_SYMBOL ::=
16235 -- IDENTIFIER
16236 -- | static_string_EXPRESSION
16238 -- PARAMETER_TYPES ::=
16239 -- null
16240 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
16242 -- TYPE_DESIGNATOR ::=
16243 -- subtype_NAME
16244 -- | subtype_Name ' Access
16246 -- MECHANISM ::=
16247 -- MECHANISM_NAME
16248 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
16250 -- MECHANISM_ASSOCIATION ::=
16251 -- [formal_parameter_NAME =>] MECHANISM_NAME
16253 -- MECHANISM_NAME ::=
16254 -- Value
16255 -- | Reference
16257 when Pragma_Import_Procedure => Import_Procedure : declare
16258 Args : Args_List (1 .. 4);
16259 Names : constant Name_List (1 .. 4) := (
16260 Name_Internal,
16261 Name_External,
16262 Name_Parameter_Types,
16263 Name_Mechanism);
16265 Internal : Node_Id renames Args (1);
16266 External : Node_Id renames Args (2);
16267 Parameter_Types : Node_Id renames Args (3);
16268 Mechanism : Node_Id renames Args (4);
16270 begin
16271 GNAT_Pragma;
16272 Gather_Associations (Names, Args);
16273 Process_Extended_Import_Export_Subprogram_Pragma (
16274 Arg_Internal => Internal,
16275 Arg_External => External,
16276 Arg_Parameter_Types => Parameter_Types,
16277 Arg_Mechanism => Mechanism);
16278 end Import_Procedure;
16280 -----------------------------
16281 -- Import_Valued_Procedure --
16282 -----------------------------
16284 -- pragma Import_Valued_Procedure (
16285 -- [Internal =>] LOCAL_NAME
16286 -- [, [External =>] EXTERNAL_SYMBOL]
16287 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
16288 -- [, [Mechanism =>] MECHANISM]);
16290 -- EXTERNAL_SYMBOL ::=
16291 -- IDENTIFIER
16292 -- | static_string_EXPRESSION
16294 -- PARAMETER_TYPES ::=
16295 -- null
16296 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
16298 -- TYPE_DESIGNATOR ::=
16299 -- subtype_NAME
16300 -- | subtype_Name ' Access
16302 -- MECHANISM ::=
16303 -- MECHANISM_NAME
16304 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
16306 -- MECHANISM_ASSOCIATION ::=
16307 -- [formal_parameter_NAME =>] MECHANISM_NAME
16309 -- MECHANISM_NAME ::=
16310 -- Value
16311 -- | Reference
16313 when Pragma_Import_Valued_Procedure =>
16314 Import_Valued_Procedure : declare
16315 Args : Args_List (1 .. 4);
16316 Names : constant Name_List (1 .. 4) := (
16317 Name_Internal,
16318 Name_External,
16319 Name_Parameter_Types,
16320 Name_Mechanism);
16322 Internal : Node_Id renames Args (1);
16323 External : Node_Id renames Args (2);
16324 Parameter_Types : Node_Id renames Args (3);
16325 Mechanism : Node_Id renames Args (4);
16327 begin
16328 GNAT_Pragma;
16329 Gather_Associations (Names, Args);
16330 Process_Extended_Import_Export_Subprogram_Pragma (
16331 Arg_Internal => Internal,
16332 Arg_External => External,
16333 Arg_Parameter_Types => Parameter_Types,
16334 Arg_Mechanism => Mechanism);
16335 end Import_Valued_Procedure;
16337 -----------------
16338 -- Independent --
16339 -----------------
16341 -- pragma Independent (LOCAL_NAME);
16343 when Pragma_Independent =>
16344 Process_Atomic_Independent_Shared_Volatile;
16346 ----------------------------
16347 -- Independent_Components --
16348 ----------------------------
16350 -- pragma Independent_Components (array_or_record_LOCAL_NAME);
16352 when Pragma_Independent_Components => Independent_Components : declare
16353 C : Node_Id;
16354 D : Node_Id;
16355 E_Id : Node_Id;
16356 E : Entity_Id;
16357 K : Node_Kind;
16359 begin
16360 Check_Ada_83_Warning;
16361 Ada_2012_Pragma;
16362 Check_No_Identifiers;
16363 Check_Arg_Count (1);
16364 Check_Arg_Is_Local_Name (Arg1);
16365 E_Id := Get_Pragma_Arg (Arg1);
16367 if Etype (E_Id) = Any_Type then
16368 return;
16369 end if;
16371 E := Entity (E_Id);
16373 -- A pragma that applies to a Ghost entity becomes Ghost for the
16374 -- purposes of legality checks and removal of ignored Ghost code.
16376 Mark_Ghost_Pragma (N, E);
16378 -- Check duplicate before we chain ourselves
16380 Check_Duplicate_Pragma (E);
16382 -- Check appropriate entity
16384 if Rep_Item_Too_Early (E, N)
16385 or else
16386 Rep_Item_Too_Late (E, N)
16387 then
16388 return;
16389 end if;
16391 D := Declaration_Node (E);
16392 K := Nkind (D);
16394 -- The flag is set on the base type, or on the object
16396 if K = N_Full_Type_Declaration
16397 and then (Is_Array_Type (E) or else Is_Record_Type (E))
16398 then
16399 Set_Has_Independent_Components (Base_Type (E));
16400 Record_Independence_Check (N, Base_Type (E));
16402 -- For record type, set all components independent
16404 if Is_Record_Type (E) then
16405 C := First_Component (E);
16406 while Present (C) loop
16407 Set_Is_Independent (C);
16408 Next_Component (C);
16409 end loop;
16410 end if;
16412 elsif (Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
16413 and then Nkind (D) = N_Object_Declaration
16414 and then Nkind (Object_Definition (D)) =
16415 N_Constrained_Array_Definition
16416 then
16417 Set_Has_Independent_Components (E);
16418 Record_Independence_Check (N, E);
16420 else
16421 Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
16422 end if;
16423 end Independent_Components;
16425 -----------------------
16426 -- Initial_Condition --
16427 -----------------------
16429 -- pragma Initial_Condition (boolean_EXPRESSION);
16431 -- Characteristics:
16433 -- * Analysis - The annotation undergoes initial checks to verify
16434 -- the legal placement and context. Secondary checks preanalyze the
16435 -- expression in:
16437 -- Analyze_Initial_Condition_In_Decl_Part
16439 -- * Expansion - The annotation is expanded during the expansion of
16440 -- the package body whose declaration is subject to the annotation
16441 -- as done in:
16443 -- Expand_Pragma_Initial_Condition
16445 -- * Template - The annotation utilizes the generic template of the
16446 -- related package declaration.
16448 -- * Globals - Capture of global references must occur after full
16449 -- analysis.
16451 -- * Instance - The annotation is instantiated automatically when
16452 -- the related generic package is instantiated.
16454 when Pragma_Initial_Condition => Initial_Condition : declare
16455 Pack_Decl : Node_Id;
16456 Pack_Id : Entity_Id;
16458 begin
16459 GNAT_Pragma;
16460 Check_No_Identifiers;
16461 Check_Arg_Count (1);
16463 Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
16465 -- Ensure the proper placement of the pragma. Initial_Condition
16466 -- must be associated with a package declaration.
16468 if Nkind_In (Pack_Decl, N_Generic_Package_Declaration,
16469 N_Package_Declaration)
16470 then
16471 null;
16473 -- Otherwise the pragma is associated with an illegal context
16475 else
16476 Pragma_Misplaced;
16477 return;
16478 end if;
16480 Pack_Id := Defining_Entity (Pack_Decl);
16482 -- A pragma that applies to a Ghost entity becomes Ghost for the
16483 -- purposes of legality checks and removal of ignored Ghost code.
16485 Mark_Ghost_Pragma (N, Pack_Id);
16487 -- Chain the pragma on the contract for further processing by
16488 -- Analyze_Initial_Condition_In_Decl_Part.
16490 Add_Contract_Item (N, Pack_Id);
16492 -- The legality checks of pragmas Abstract_State, Initializes, and
16493 -- Initial_Condition are affected by the SPARK mode in effect. In
16494 -- addition, these three pragmas are subject to an inherent order:
16496 -- 1) Abstract_State
16497 -- 2) Initializes
16498 -- 3) Initial_Condition
16500 -- Analyze all these pragmas in the order outlined above
16502 Analyze_If_Present (Pragma_SPARK_Mode);
16503 Analyze_If_Present (Pragma_Abstract_State);
16504 Analyze_If_Present (Pragma_Initializes);
16505 end Initial_Condition;
16507 ------------------------
16508 -- Initialize_Scalars --
16509 ------------------------
16511 -- pragma Initialize_Scalars;
16513 when Pragma_Initialize_Scalars =>
16514 GNAT_Pragma;
16515 Check_Arg_Count (0);
16516 Check_Valid_Configuration_Pragma;
16517 Check_Restriction (No_Initialize_Scalars, N);
16519 -- Initialize_Scalars creates false positives in CodePeer, and
16520 -- incorrect negative results in GNATprove mode, so ignore this
16521 -- pragma in these modes.
16523 if not Restriction_Active (No_Initialize_Scalars)
16524 and then not (CodePeer_Mode or GNATprove_Mode)
16525 then
16526 Init_Or_Norm_Scalars := True;
16527 Initialize_Scalars := True;
16528 end if;
16530 -----------------
16531 -- Initializes --
16532 -----------------
16534 -- pragma Initializes (INITIALIZATION_LIST);
16536 -- INITIALIZATION_LIST ::=
16537 -- null
16538 -- | (INITIALIZATION_ITEM {, INITIALIZATION_ITEM})
16540 -- INITIALIZATION_ITEM ::= name [=> INPUT_LIST]
16542 -- INPUT_LIST ::=
16543 -- null
16544 -- | INPUT
16545 -- | (INPUT {, INPUT})
16547 -- INPUT ::= name
16549 -- Characteristics:
16551 -- * Analysis - The annotation undergoes initial checks to verify
16552 -- the legal placement and context. Secondary checks preanalyze the
16553 -- expression in:
16555 -- Analyze_Initializes_In_Decl_Part
16557 -- * Expansion - None.
16559 -- * Template - The annotation utilizes the generic template of the
16560 -- related package declaration.
16562 -- * Globals - Capture of global references must occur after full
16563 -- analysis.
16565 -- * Instance - The annotation is instantiated automatically when
16566 -- the related generic package is instantiated.
16568 when Pragma_Initializes => Initializes : declare
16569 Pack_Decl : Node_Id;
16570 Pack_Id : Entity_Id;
16572 begin
16573 GNAT_Pragma;
16574 Check_No_Identifiers;
16575 Check_Arg_Count (1);
16577 Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
16579 -- Ensure the proper placement of the pragma. Initializes must be
16580 -- associated with a package declaration.
16582 if Nkind_In (Pack_Decl, N_Generic_Package_Declaration,
16583 N_Package_Declaration)
16584 then
16585 null;
16587 -- Otherwise the pragma is associated with an illegal construc
16589 else
16590 Pragma_Misplaced;
16591 return;
16592 end if;
16594 Pack_Id := Defining_Entity (Pack_Decl);
16596 -- A pragma that applies to a Ghost entity becomes Ghost for the
16597 -- purposes of legality checks and removal of ignored Ghost code.
16599 Mark_Ghost_Pragma (N, Pack_Id);
16600 Ensure_Aggregate_Form (Get_Argument (N, Pack_Id));
16602 -- Chain the pragma on the contract for further processing by
16603 -- Analyze_Initializes_In_Decl_Part.
16605 Add_Contract_Item (N, Pack_Id);
16607 -- The legality checks of pragmas Abstract_State, Initializes, and
16608 -- Initial_Condition are affected by the SPARK mode in effect. In
16609 -- addition, these three pragmas are subject to an inherent order:
16611 -- 1) Abstract_State
16612 -- 2) Initializes
16613 -- 3) Initial_Condition
16615 -- Analyze all these pragmas in the order outlined above
16617 Analyze_If_Present (Pragma_SPARK_Mode);
16618 Analyze_If_Present (Pragma_Abstract_State);
16619 Analyze_If_Present (Pragma_Initial_Condition);
16620 end Initializes;
16622 ------------
16623 -- Inline --
16624 ------------
16626 -- pragma Inline ( NAME {, NAME} );
16628 when Pragma_Inline =>
16630 -- Pragma always active unless in GNATprove mode. It is disabled
16631 -- in GNATprove mode because frontend inlining is applied
16632 -- independently of pragmas Inline and Inline_Always for
16633 -- formal verification, see Can_Be_Inlined_In_GNATprove_Mode
16634 -- in inline.ads.
16636 if not GNATprove_Mode then
16638 -- Inline status is Enabled if option -gnatn is specified.
16639 -- However this status determines only the value of the
16640 -- Is_Inlined flag on the subprogram and does not prevent
16641 -- the pragma itself from being recorded for later use,
16642 -- in particular for a later modification of Is_Inlined
16643 -- independently of the -gnatn option.
16645 -- In other words, if -gnatn is specified for a unit, then
16646 -- all Inline pragmas processed for the compilation of this
16647 -- unit, including those in the spec of other units, are
16648 -- activated, so subprograms will be inlined across units.
16650 -- If -gnatn is not specified, no Inline pragma is activated
16651 -- here, which means that subprograms will not be inlined
16652 -- across units. The Is_Inlined flag will nevertheless be
16653 -- set later when bodies are analyzed, so subprograms will
16654 -- be inlined within the unit.
16656 if Inline_Active then
16657 Process_Inline (Enabled);
16658 else
16659 Process_Inline (Disabled);
16660 end if;
16661 end if;
16663 -------------------
16664 -- Inline_Always --
16665 -------------------
16667 -- pragma Inline_Always ( NAME {, NAME} );
16669 when Pragma_Inline_Always =>
16670 GNAT_Pragma;
16672 -- Pragma always active unless in CodePeer mode or GNATprove
16673 -- mode. It is disabled in CodePeer mode because inlining is
16674 -- not helpful, and enabling it caused walk order issues. It
16675 -- is disabled in GNATprove mode because frontend inlining is
16676 -- applied independently of pragmas Inline and Inline_Always for
16677 -- formal verification, see Can_Be_Inlined_In_GNATprove_Mode in
16678 -- inline.ads.
16680 if not CodePeer_Mode and not GNATprove_Mode then
16681 Process_Inline (Enabled);
16682 end if;
16684 --------------------
16685 -- Inline_Generic --
16686 --------------------
16688 -- pragma Inline_Generic (NAME {, NAME});
16690 when Pragma_Inline_Generic =>
16691 GNAT_Pragma;
16692 Process_Generic_List;
16694 ----------------------
16695 -- Inspection_Point --
16696 ----------------------
16698 -- pragma Inspection_Point [(object_NAME {, object_NAME})];
16700 when Pragma_Inspection_Point => Inspection_Point : declare
16701 Arg : Node_Id;
16702 Exp : Node_Id;
16704 begin
16707 if Arg_Count > 0 then
16708 Arg := Arg1;
16709 loop
16710 Exp := Get_Pragma_Arg (Arg);
16711 Analyze (Exp);
16713 if not Is_Entity_Name (Exp)
16714 or else not Is_Object (Entity (Exp))
16715 then
16716 Error_Pragma_Arg ("object name required", Arg);
16717 end if;
16719 Next (Arg);
16720 exit when No (Arg);
16721 end loop;
16722 end if;
16723 end Inspection_Point;
16725 ---------------
16726 -- Interface --
16727 ---------------
16729 -- pragma Interface (
16730 -- [ Convention =>] convention_IDENTIFIER,
16731 -- [ Entity =>] LOCAL_NAME
16732 -- [, [External_Name =>] static_string_EXPRESSION ]
16733 -- [, [Link_Name =>] static_string_EXPRESSION ]);
16735 when Pragma_Interface =>
16736 GNAT_Pragma;
16737 Check_Arg_Order
16738 ((Name_Convention,
16739 Name_Entity,
16740 Name_External_Name,
16741 Name_Link_Name));
16742 Check_At_Least_N_Arguments (2);
16743 Check_At_Most_N_Arguments (4);
16744 Process_Import_Or_Interface;
16746 -- In Ada 2005, the permission to use Interface (a reserved word)
16747 -- as a pragma name is considered an obsolescent feature, and this
16748 -- pragma was already obsolescent in Ada 95.
16750 if Ada_Version >= Ada_95 then
16751 Check_Restriction
16752 (No_Obsolescent_Features, Pragma_Identifier (N));
16754 if Warn_On_Obsolescent_Feature then
16755 Error_Msg_N
16756 ("pragma Interface is an obsolescent feature?j?", N);
16757 Error_Msg_N
16758 ("|use pragma Import instead?j?", N);
16759 end if;
16760 end if;
16762 --------------------
16763 -- Interface_Name --
16764 --------------------
16766 -- pragma Interface_Name (
16767 -- [ Entity =>] LOCAL_NAME
16768 -- [,[External_Name =>] static_string_EXPRESSION ]
16769 -- [,[Link_Name =>] static_string_EXPRESSION ]);
16771 when Pragma_Interface_Name => Interface_Name : declare
16772 Id : Node_Id;
16773 Def_Id : Entity_Id;
16774 Hom_Id : Entity_Id;
16775 Found : Boolean;
16777 begin
16778 GNAT_Pragma;
16779 Check_Arg_Order
16780 ((Name_Entity, Name_External_Name, Name_Link_Name));
16781 Check_At_Least_N_Arguments (2);
16782 Check_At_Most_N_Arguments (3);
16783 Id := Get_Pragma_Arg (Arg1);
16784 Analyze (Id);
16786 -- This is obsolete from Ada 95 on, but it is an implementation
16787 -- defined pragma, so we do not consider that it violates the
16788 -- restriction (No_Obsolescent_Features).
16790 if Ada_Version >= Ada_95 then
16791 if Warn_On_Obsolescent_Feature then
16792 Error_Msg_N
16793 ("pragma Interface_Name is an obsolescent feature?j?", N);
16794 Error_Msg_N
16795 ("|use pragma Import instead?j?", N);
16796 end if;
16797 end if;
16799 if not Is_Entity_Name (Id) then
16800 Error_Pragma_Arg
16801 ("first argument for pragma% must be entity name", Arg1);
16802 elsif Etype (Id) = Any_Type then
16803 return;
16804 else
16805 Def_Id := Entity (Id);
16806 end if;
16808 -- Special DEC-compatible processing for the object case, forces
16809 -- object to be imported.
16811 if Ekind (Def_Id) = E_Variable then
16812 Kill_Size_Check_Code (Def_Id);
16813 Note_Possible_Modification (Id, Sure => False);
16815 -- Initialization is not allowed for imported variable
16817 if Present (Expression (Parent (Def_Id)))
16818 and then Comes_From_Source (Expression (Parent (Def_Id)))
16819 then
16820 Error_Msg_Sloc := Sloc (Def_Id);
16821 Error_Pragma_Arg
16822 ("no initialization allowed for declaration of& #",
16823 Arg2);
16825 else
16826 -- For compatibility, support VADS usage of providing both
16827 -- pragmas Interface and Interface_Name to obtain the effect
16828 -- of a single Import pragma.
16830 if Is_Imported (Def_Id)
16831 and then Present (First_Rep_Item (Def_Id))
16832 and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
16833 and then Pragma_Name (First_Rep_Item (Def_Id)) =
16834 Name_Interface
16835 then
16836 null;
16837 else
16838 Set_Imported (Def_Id);
16839 end if;
16841 Set_Is_Public (Def_Id);
16842 Process_Interface_Name (Def_Id, Arg2, Arg3, N);
16843 end if;
16845 -- Otherwise must be subprogram
16847 elsif not Is_Subprogram (Def_Id) then
16848 Error_Pragma_Arg
16849 ("argument of pragma% is not subprogram", Arg1);
16851 else
16852 Check_At_Most_N_Arguments (3);
16853 Hom_Id := Def_Id;
16854 Found := False;
16856 -- Loop through homonyms
16858 loop
16859 Def_Id := Get_Base_Subprogram (Hom_Id);
16861 if Is_Imported (Def_Id) then
16862 Process_Interface_Name (Def_Id, Arg2, Arg3, N);
16863 Found := True;
16864 end if;
16866 exit when From_Aspect_Specification (N);
16867 Hom_Id := Homonym (Hom_Id);
16869 exit when No (Hom_Id)
16870 or else Scope (Hom_Id) /= Current_Scope;
16871 end loop;
16873 if not Found then
16874 Error_Pragma_Arg
16875 ("argument of pragma% is not imported subprogram",
16876 Arg1);
16877 end if;
16878 end if;
16879 end Interface_Name;
16881 -----------------------
16882 -- Interrupt_Handler --
16883 -----------------------
16885 -- pragma Interrupt_Handler (handler_NAME);
16887 when Pragma_Interrupt_Handler =>
16888 Check_Ada_83_Warning;
16889 Check_Arg_Count (1);
16890 Check_No_Identifiers;
16892 if No_Run_Time_Mode then
16893 Error_Msg_CRT ("Interrupt_Handler pragma", N);
16894 else
16895 Check_Interrupt_Or_Attach_Handler;
16896 Process_Interrupt_Or_Attach_Handler;
16897 end if;
16899 ------------------------
16900 -- Interrupt_Priority --
16901 ------------------------
16903 -- pragma Interrupt_Priority [(EXPRESSION)];
16905 when Pragma_Interrupt_Priority => Interrupt_Priority : declare
16906 P : constant Node_Id := Parent (N);
16907 Arg : Node_Id;
16908 Ent : Entity_Id;
16910 begin
16911 Check_Ada_83_Warning;
16913 if Arg_Count /= 0 then
16914 Arg := Get_Pragma_Arg (Arg1);
16915 Check_Arg_Count (1);
16916 Check_No_Identifiers;
16918 -- The expression must be analyzed in the special manner
16919 -- described in "Handling of Default and Per-Object
16920 -- Expressions" in sem.ads.
16922 Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
16923 end if;
16925 if not Nkind_In (P, N_Task_Definition, N_Protected_Definition) then
16926 Pragma_Misplaced;
16927 return;
16929 else
16930 Ent := Defining_Identifier (Parent (P));
16932 -- Check duplicate pragma before we chain the pragma in the Rep
16933 -- Item chain of Ent.
16935 Check_Duplicate_Pragma (Ent);
16936 Record_Rep_Item (Ent, N);
16938 -- Check the No_Task_At_Interrupt_Priority restriction
16940 if Nkind (P) = N_Task_Definition then
16941 Check_Restriction (No_Task_At_Interrupt_Priority, N);
16942 end if;
16943 end if;
16944 end Interrupt_Priority;
16946 ---------------------
16947 -- Interrupt_State --
16948 ---------------------
16950 -- pragma Interrupt_State (
16951 -- [Name =>] INTERRUPT_ID,
16952 -- [State =>] INTERRUPT_STATE);
16954 -- INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
16955 -- INTERRUPT_STATE => System | Runtime | User
16957 -- Note: if the interrupt id is given as an identifier, then it must
16958 -- be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
16959 -- given as a static integer expression which must be in the range of
16960 -- Ada.Interrupts.Interrupt_ID.
16962 when Pragma_Interrupt_State => Interrupt_State : declare
16963 Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
16964 -- This is the entity Ada.Interrupts.Interrupt_ID;
16966 State_Type : Character;
16967 -- Set to 's'/'r'/'u' for System/Runtime/User
16969 IST_Num : Pos;
16970 -- Index to entry in Interrupt_States table
16972 Int_Val : Uint;
16973 -- Value of interrupt
16975 Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
16976 -- The first argument to the pragma
16978 Int_Ent : Entity_Id;
16979 -- Interrupt entity in Ada.Interrupts.Names
16981 begin
16982 GNAT_Pragma;
16983 Check_Arg_Order ((Name_Name, Name_State));
16984 Check_Arg_Count (2);
16986 Check_Optional_Identifier (Arg1, Name_Name);
16987 Check_Optional_Identifier (Arg2, Name_State);
16988 Check_Arg_Is_Identifier (Arg2);
16990 -- First argument is identifier
16992 if Nkind (Arg1X) = N_Identifier then
16994 -- Search list of names in Ada.Interrupts.Names
16996 Int_Ent := First_Entity (RTE (RE_Names));
16997 loop
16998 if No (Int_Ent) then
16999 Error_Pragma_Arg ("invalid interrupt name", Arg1);
17001 elsif Chars (Int_Ent) = Chars (Arg1X) then
17002 Int_Val := Expr_Value (Constant_Value (Int_Ent));
17003 exit;
17004 end if;
17006 Next_Entity (Int_Ent);
17007 end loop;
17009 -- First argument is not an identifier, so it must be a static
17010 -- expression of type Ada.Interrupts.Interrupt_ID.
17012 else
17013 Check_Arg_Is_OK_Static_Expression (Arg1, Any_Integer);
17014 Int_Val := Expr_Value (Arg1X);
17016 if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
17017 or else
17018 Int_Val > Expr_Value (Type_High_Bound (Int_Id))
17019 then
17020 Error_Pragma_Arg
17021 ("value not in range of type "
17022 & """Ada.Interrupts.Interrupt_'I'D""", Arg1);
17023 end if;
17024 end if;
17026 -- Check OK state
17028 case Chars (Get_Pragma_Arg (Arg2)) is
17029 when Name_Runtime => State_Type := 'r';
17030 when Name_System => State_Type := 's';
17031 when Name_User => State_Type := 'u';
17033 when others =>
17034 Error_Pragma_Arg ("invalid interrupt state", Arg2);
17035 end case;
17037 -- Check if entry is already stored
17039 IST_Num := Interrupt_States.First;
17040 loop
17041 -- If entry not found, add it
17043 if IST_Num > Interrupt_States.Last then
17044 Interrupt_States.Append
17045 ((Interrupt_Number => UI_To_Int (Int_Val),
17046 Interrupt_State => State_Type,
17047 Pragma_Loc => Loc));
17048 exit;
17050 -- Case of entry for the same entry
17052 elsif Int_Val = Interrupt_States.Table (IST_Num).
17053 Interrupt_Number
17054 then
17055 -- If state matches, done, no need to make redundant entry
17057 exit when
17058 State_Type = Interrupt_States.Table (IST_Num).
17059 Interrupt_State;
17061 -- Otherwise if state does not match, error
17063 Error_Msg_Sloc :=
17064 Interrupt_States.Table (IST_Num).Pragma_Loc;
17065 Error_Pragma_Arg
17066 ("state conflicts with that given #", Arg2);
17067 exit;
17068 end if;
17070 IST_Num := IST_Num + 1;
17071 end loop;
17072 end Interrupt_State;
17074 ---------------
17075 -- Invariant --
17076 ---------------
17078 -- pragma Invariant
17079 -- ([Entity =>] type_LOCAL_NAME,
17080 -- [Check =>] EXPRESSION
17081 -- [,[Message =>] String_Expression]);
17083 when Pragma_Invariant => Invariant : declare
17084 Discard : Boolean;
17085 Typ : Entity_Id;
17086 Typ_Arg : Node_Id;
17088 begin
17089 GNAT_Pragma;
17090 Check_At_Least_N_Arguments (2);
17091 Check_At_Most_N_Arguments (3);
17092 Check_Optional_Identifier (Arg1, Name_Entity);
17093 Check_Optional_Identifier (Arg2, Name_Check);
17095 if Arg_Count = 3 then
17096 Check_Optional_Identifier (Arg3, Name_Message);
17097 Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
17098 end if;
17100 Check_Arg_Is_Local_Name (Arg1);
17102 Typ_Arg := Get_Pragma_Arg (Arg1);
17103 Find_Type (Typ_Arg);
17104 Typ := Entity (Typ_Arg);
17106 -- Nothing to do of the related type is erroneous in some way
17108 if Typ = Any_Type then
17109 return;
17111 -- AI12-0041: Invariants are allowed in interface types
17113 elsif Is_Interface (Typ) then
17114 null;
17116 -- An invariant must apply to a private type, or appear in the
17117 -- private part of a package spec and apply to a completion.
17118 -- a class-wide invariant can only appear on a private declaration
17119 -- or private extension, not a completion.
17121 -- A [class-wide] invariant may be associated a [limited] private
17122 -- type or a private extension.
17124 elsif Ekind_In (Typ, E_Limited_Private_Type,
17125 E_Private_Type,
17126 E_Record_Type_With_Private)
17127 then
17128 null;
17130 -- A non-class-wide invariant may be associated with the full view
17131 -- of a [limited] private type or a private extension.
17133 elsif Has_Private_Declaration (Typ)
17134 and then not Class_Present (N)
17135 then
17136 null;
17138 -- A class-wide invariant may appear on the partial view only
17140 elsif Class_Present (N) then
17141 Error_Pragma_Arg
17142 ("pragma % only allowed for private type", Arg1);
17143 return;
17145 -- A regular invariant may appear on both views
17147 else
17148 Error_Pragma_Arg
17149 ("pragma % only allowed for private type or corresponding "
17150 & "full view", Arg1);
17151 return;
17152 end if;
17154 -- An invariant associated with an abstract type (this includes
17155 -- interfaces) must be class-wide.
17157 if Is_Abstract_Type (Typ) and then not Class_Present (N) then
17158 Error_Pragma_Arg
17159 ("pragma % not allowed for abstract type", Arg1);
17160 return;
17161 end if;
17163 -- A pragma that applies to a Ghost entity becomes Ghost for the
17164 -- purposes of legality checks and removal of ignored Ghost code.
17166 Mark_Ghost_Pragma (N, Typ);
17168 -- The pragma defines a type-specific invariant, the type is said
17169 -- to have invariants of its "own".
17171 Set_Has_Own_Invariants (Typ);
17173 -- If the invariant is class-wide, then it can be inherited by
17174 -- derived or interface implementing types. The type is said to
17175 -- have "inheritable" invariants.
17177 if Class_Present (N) then
17178 Set_Has_Inheritable_Invariants (Typ);
17179 end if;
17181 -- Chain the pragma on to the rep item chain, for processing when
17182 -- the type is frozen.
17184 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
17186 -- Create the declaration of the invariant procedure that will
17187 -- verify the invariant at run time. Interfaces are treated as the
17188 -- partial view of a private type in order to achieve uniformity
17189 -- with the general case. As a result, an interface receives only
17190 -- a "partial" invariant procedure, which is never called.
17192 Build_Invariant_Procedure_Declaration
17193 (Typ => Typ,
17194 Partial_Invariant => Is_Interface (Typ));
17195 end Invariant;
17197 ----------------
17198 -- Keep_Names --
17199 ----------------
17201 -- pragma Keep_Names ([On => ] LOCAL_NAME);
17203 when Pragma_Keep_Names => Keep_Names : declare
17204 Arg : Node_Id;
17206 begin
17207 GNAT_Pragma;
17208 Check_Arg_Count (1);
17209 Check_Optional_Identifier (Arg1, Name_On);
17210 Check_Arg_Is_Local_Name (Arg1);
17212 Arg := Get_Pragma_Arg (Arg1);
17213 Analyze (Arg);
17215 if Etype (Arg) = Any_Type then
17216 return;
17217 end if;
17219 if not Is_Entity_Name (Arg)
17220 or else Ekind (Entity (Arg)) /= E_Enumeration_Type
17221 then
17222 Error_Pragma_Arg
17223 ("pragma% requires a local enumeration type", Arg1);
17224 end if;
17226 Set_Discard_Names (Entity (Arg), False);
17227 end Keep_Names;
17229 -------------
17230 -- License --
17231 -------------
17233 -- pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
17235 when Pragma_License =>
17236 GNAT_Pragma;
17238 -- Do not analyze pragma any further in CodePeer mode, to avoid
17239 -- extraneous errors in this implementation-dependent pragma,
17240 -- which has a different profile on other compilers.
17242 if CodePeer_Mode then
17243 return;
17244 end if;
17246 Check_Arg_Count (1);
17247 Check_No_Identifiers;
17248 Check_Valid_Configuration_Pragma;
17249 Check_Arg_Is_Identifier (Arg1);
17251 declare
17252 Sind : constant Source_File_Index :=
17253 Source_Index (Current_Sem_Unit);
17255 begin
17256 case Chars (Get_Pragma_Arg (Arg1)) is
17257 when Name_GPL =>
17258 Set_License (Sind, GPL);
17260 when Name_Modified_GPL =>
17261 Set_License (Sind, Modified_GPL);
17263 when Name_Restricted =>
17264 Set_License (Sind, Restricted);
17266 when Name_Unrestricted =>
17267 Set_License (Sind, Unrestricted);
17269 when others =>
17270 Error_Pragma_Arg ("invalid license name", Arg1);
17271 end case;
17272 end;
17274 ---------------
17275 -- Link_With --
17276 ---------------
17278 -- pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
17280 when Pragma_Link_With => Link_With : declare
17281 Arg : Node_Id;
17283 begin
17284 GNAT_Pragma;
17286 if Operating_Mode = Generate_Code
17287 and then In_Extended_Main_Source_Unit (N)
17288 then
17289 Check_At_Least_N_Arguments (1);
17290 Check_No_Identifiers;
17291 Check_Is_In_Decl_Part_Or_Package_Spec;
17292 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
17293 Start_String;
17295 Arg := Arg1;
17296 while Present (Arg) loop
17297 Check_Arg_Is_OK_Static_Expression (Arg, Standard_String);
17299 -- Store argument, converting sequences of spaces to a
17300 -- single null character (this is one of the differences
17301 -- in processing between Link_With and Linker_Options).
17303 Arg_Store : declare
17304 C : constant Char_Code := Get_Char_Code (' ');
17305 S : constant String_Id :=
17306 Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
17307 L : constant Nat := String_Length (S);
17308 F : Nat := 1;
17310 procedure Skip_Spaces;
17311 -- Advance F past any spaces
17313 -----------------
17314 -- Skip_Spaces --
17315 -----------------
17317 procedure Skip_Spaces is
17318 begin
17319 while F <= L and then Get_String_Char (S, F) = C loop
17320 F := F + 1;
17321 end loop;
17322 end Skip_Spaces;
17324 -- Start of processing for Arg_Store
17326 begin
17327 Skip_Spaces; -- skip leading spaces
17329 -- Loop through characters, changing any embedded
17330 -- sequence of spaces to a single null character (this
17331 -- is how Link_With/Linker_Options differ)
17333 while F <= L loop
17334 if Get_String_Char (S, F) = C then
17335 Skip_Spaces;
17336 exit when F > L;
17337 Store_String_Char (ASCII.NUL);
17339 else
17340 Store_String_Char (Get_String_Char (S, F));
17341 F := F + 1;
17342 end if;
17343 end loop;
17344 end Arg_Store;
17346 Arg := Next (Arg);
17348 if Present (Arg) then
17349 Store_String_Char (ASCII.NUL);
17350 end if;
17351 end loop;
17353 Store_Linker_Option_String (End_String);
17354 end if;
17355 end Link_With;
17357 ------------------
17358 -- Linker_Alias --
17359 ------------------
17361 -- pragma Linker_Alias (
17362 -- [Entity =>] LOCAL_NAME
17363 -- [Target =>] static_string_EXPRESSION);
17365 when Pragma_Linker_Alias =>
17366 GNAT_Pragma;
17367 Check_Arg_Order ((Name_Entity, Name_Target));
17368 Check_Arg_Count (2);
17369 Check_Optional_Identifier (Arg1, Name_Entity);
17370 Check_Optional_Identifier (Arg2, Name_Target);
17371 Check_Arg_Is_Library_Level_Local_Name (Arg1);
17372 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
17374 -- The only processing required is to link this item on to the
17375 -- list of rep items for the given entity. This is accomplished
17376 -- by the call to Rep_Item_Too_Late (when no error is detected
17377 -- and False is returned).
17379 if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
17380 return;
17381 else
17382 Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
17383 end if;
17385 ------------------------
17386 -- Linker_Constructor --
17387 ------------------------
17389 -- pragma Linker_Constructor (procedure_LOCAL_NAME);
17391 -- Code is shared with Linker_Destructor
17393 -----------------------
17394 -- Linker_Destructor --
17395 -----------------------
17397 -- pragma Linker_Destructor (procedure_LOCAL_NAME);
17399 when Pragma_Linker_Constructor
17400 | Pragma_Linker_Destructor
17402 Linker_Constructor : declare
17403 Arg1_X : Node_Id;
17404 Proc : Entity_Id;
17406 begin
17407 GNAT_Pragma;
17408 Check_Arg_Count (1);
17409 Check_No_Identifiers;
17410 Check_Arg_Is_Local_Name (Arg1);
17411 Arg1_X := Get_Pragma_Arg (Arg1);
17412 Analyze (Arg1_X);
17413 Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
17415 if not Is_Library_Level_Entity (Proc) then
17416 Error_Pragma_Arg
17417 ("argument for pragma% must be library level entity", Arg1);
17418 end if;
17420 -- The only processing required is to link this item on to the
17421 -- list of rep items for the given entity. This is accomplished
17422 -- by the call to Rep_Item_Too_Late (when no error is detected
17423 -- and False is returned).
17425 if Rep_Item_Too_Late (Proc, N) then
17426 return;
17427 else
17428 Set_Has_Gigi_Rep_Item (Proc);
17429 end if;
17430 end Linker_Constructor;
17432 --------------------
17433 -- Linker_Options --
17434 --------------------
17436 -- pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
17438 when Pragma_Linker_Options => Linker_Options : declare
17439 Arg : Node_Id;
17441 begin
17442 Check_Ada_83_Warning;
17443 Check_No_Identifiers;
17444 Check_Arg_Count (1);
17445 Check_Is_In_Decl_Part_Or_Package_Spec;
17446 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
17447 Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
17449 Arg := Arg2;
17450 while Present (Arg) loop
17451 Check_Arg_Is_OK_Static_Expression (Arg, Standard_String);
17452 Store_String_Char (ASCII.NUL);
17453 Store_String_Chars
17454 (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
17455 Arg := Next (Arg);
17456 end loop;
17458 if Operating_Mode = Generate_Code
17459 and then In_Extended_Main_Source_Unit (N)
17460 then
17461 Store_Linker_Option_String (End_String);
17462 end if;
17463 end Linker_Options;
17465 --------------------
17466 -- Linker_Section --
17467 --------------------
17469 -- pragma Linker_Section (
17470 -- [Entity =>] LOCAL_NAME
17471 -- [Section =>] static_string_EXPRESSION);
17473 when Pragma_Linker_Section => Linker_Section : declare
17474 Arg : Node_Id;
17475 Ent : Entity_Id;
17476 LPE : Node_Id;
17478 Ghost_Error_Posted : Boolean := False;
17479 -- Flag set when an error concerning the illegal mix of Ghost and
17480 -- non-Ghost subprograms is emitted.
17482 Ghost_Id : Entity_Id := Empty;
17483 -- The entity of the first Ghost subprogram encountered while
17484 -- processing the arguments of the pragma.
17486 begin
17487 GNAT_Pragma;
17488 Check_Arg_Order ((Name_Entity, Name_Section));
17489 Check_Arg_Count (2);
17490 Check_Optional_Identifier (Arg1, Name_Entity);
17491 Check_Optional_Identifier (Arg2, Name_Section);
17492 Check_Arg_Is_Library_Level_Local_Name (Arg1);
17493 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
17495 -- Check kind of entity
17497 Arg := Get_Pragma_Arg (Arg1);
17498 Ent := Entity (Arg);
17500 case Ekind (Ent) is
17502 -- Objects (constants and variables) and types. For these cases
17503 -- all we need to do is to set the Linker_Section_pragma field,
17504 -- checking that we do not have a duplicate.
17506 when Type_Kind
17507 | E_Constant
17508 | E_Variable
17510 LPE := Linker_Section_Pragma (Ent);
17512 if Present (LPE) then
17513 Error_Msg_Sloc := Sloc (LPE);
17514 Error_Msg_NE
17515 ("Linker_Section already specified for &#", Arg1, Ent);
17516 end if;
17518 Set_Linker_Section_Pragma (Ent, N);
17520 -- A pragma that applies to a Ghost entity becomes Ghost for
17521 -- the purposes of legality checks and removal of ignored
17522 -- Ghost code.
17524 Mark_Ghost_Pragma (N, Ent);
17526 -- Subprograms
17528 when Subprogram_Kind =>
17530 -- Aspect case, entity already set
17532 if From_Aspect_Specification (N) then
17533 Set_Linker_Section_Pragma
17534 (Entity (Corresponding_Aspect (N)), N);
17536 -- Pragma case, we must climb the homonym chain, but skip
17537 -- any for which the linker section is already set.
17539 else
17540 loop
17541 if No (Linker_Section_Pragma (Ent)) then
17542 Set_Linker_Section_Pragma (Ent, N);
17544 -- A pragma that applies to a Ghost entity becomes
17545 -- Ghost for the purposes of legality checks and
17546 -- removal of ignored Ghost code.
17548 Mark_Ghost_Pragma (N, Ent);
17550 -- Capture the entity of the first Ghost subprogram
17551 -- being processed for error detection purposes.
17553 if Is_Ghost_Entity (Ent) then
17554 if No (Ghost_Id) then
17555 Ghost_Id := Ent;
17556 end if;
17558 -- Otherwise the subprogram is non-Ghost. It is
17559 -- illegal to mix references to Ghost and non-Ghost
17560 -- entities (SPARK RM 6.9).
17562 elsif Present (Ghost_Id)
17563 and then not Ghost_Error_Posted
17564 then
17565 Ghost_Error_Posted := True;
17567 Error_Msg_Name_1 := Pname;
17568 Error_Msg_N
17569 ("pragma % cannot mention ghost and "
17570 & "non-ghost subprograms", N);
17572 Error_Msg_Sloc := Sloc (Ghost_Id);
17573 Error_Msg_NE
17574 ("\& # declared as ghost", N, Ghost_Id);
17576 Error_Msg_Sloc := Sloc (Ent);
17577 Error_Msg_NE
17578 ("\& # declared as non-ghost", N, Ent);
17579 end if;
17580 end if;
17582 Ent := Homonym (Ent);
17583 exit when No (Ent)
17584 or else Scope (Ent) /= Current_Scope;
17585 end loop;
17586 end if;
17588 -- All other cases are illegal
17590 when others =>
17591 Error_Pragma_Arg
17592 ("pragma% applies only to objects, subprograms, and types",
17593 Arg1);
17594 end case;
17595 end Linker_Section;
17597 ----------
17598 -- List --
17599 ----------
17601 -- pragma List (On | Off)
17603 -- There is nothing to do here, since we did all the processing for
17604 -- this pragma in Par.Prag (so that it works properly even in syntax
17605 -- only mode).
17607 when Pragma_List =>
17608 null;
17610 ---------------
17611 -- Lock_Free --
17612 ---------------
17614 -- pragma Lock_Free [(Boolean_EXPRESSION)];
17616 when Pragma_Lock_Free => Lock_Free : declare
17617 P : constant Node_Id := Parent (N);
17618 Arg : Node_Id;
17619 Ent : Entity_Id;
17620 Val : Boolean;
17622 begin
17623 Check_No_Identifiers;
17624 Check_At_Most_N_Arguments (1);
17626 -- Protected definition case
17628 if Nkind (P) = N_Protected_Definition then
17629 Ent := Defining_Identifier (Parent (P));
17631 -- One argument
17633 if Arg_Count = 1 then
17634 Arg := Get_Pragma_Arg (Arg1);
17635 Val := Is_True (Static_Boolean (Arg));
17637 -- No arguments (expression is considered to be True)
17639 else
17640 Val := True;
17641 end if;
17643 -- Check duplicate pragma before we chain the pragma in the Rep
17644 -- Item chain of Ent.
17646 Check_Duplicate_Pragma (Ent);
17647 Record_Rep_Item (Ent, N);
17648 Set_Uses_Lock_Free (Ent, Val);
17650 -- Anything else is incorrect placement
17652 else
17653 Pragma_Misplaced;
17654 end if;
17655 end Lock_Free;
17657 --------------------
17658 -- Locking_Policy --
17659 --------------------
17661 -- pragma Locking_Policy (policy_IDENTIFIER);
17663 when Pragma_Locking_Policy => declare
17664 subtype LP_Range is Name_Id
17665 range First_Locking_Policy_Name .. Last_Locking_Policy_Name;
17666 LP_Val : LP_Range;
17667 LP : Character;
17669 begin
17670 Check_Ada_83_Warning;
17671 Check_Arg_Count (1);
17672 Check_No_Identifiers;
17673 Check_Arg_Is_Locking_Policy (Arg1);
17674 Check_Valid_Configuration_Pragma;
17675 LP_Val := Chars (Get_Pragma_Arg (Arg1));
17677 case LP_Val is
17678 when Name_Ceiling_Locking => LP := 'C';
17679 when Name_Concurrent_Readers_Locking => LP := 'R';
17680 when Name_Inheritance_Locking => LP := 'I';
17681 end case;
17683 if Locking_Policy /= ' '
17684 and then Locking_Policy /= LP
17685 then
17686 Error_Msg_Sloc := Locking_Policy_Sloc;
17687 Error_Pragma ("locking policy incompatible with policy#");
17689 -- Set new policy, but always preserve System_Location since we
17690 -- like the error message with the run time name.
17692 else
17693 Locking_Policy := LP;
17695 if Locking_Policy_Sloc /= System_Location then
17696 Locking_Policy_Sloc := Loc;
17697 end if;
17698 end if;
17699 end;
17701 -------------------
17702 -- Loop_Optimize --
17703 -------------------
17705 -- pragma Loop_Optimize ( OPTIMIZATION_HINT {, OPTIMIZATION_HINT } );
17707 -- OPTIMIZATION_HINT ::=
17708 -- Ivdep | No_Unroll | Unroll | No_Vector | Vector
17710 when Pragma_Loop_Optimize => Loop_Optimize : declare
17711 Hint : Node_Id;
17713 begin
17714 GNAT_Pragma;
17715 Check_At_Least_N_Arguments (1);
17716 Check_No_Identifiers;
17718 Hint := First (Pragma_Argument_Associations (N));
17719 while Present (Hint) loop
17720 Check_Arg_Is_One_Of (Hint, Name_Ivdep,
17721 Name_No_Unroll,
17722 Name_Unroll,
17723 Name_No_Vector,
17724 Name_Vector);
17725 Next (Hint);
17726 end loop;
17728 Check_Loop_Pragma_Placement;
17729 end Loop_Optimize;
17731 ------------------
17732 -- Loop_Variant --
17733 ------------------
17735 -- pragma Loop_Variant
17736 -- ( LOOP_VARIANT_ITEM {, LOOP_VARIANT_ITEM } );
17738 -- LOOP_VARIANT_ITEM ::= CHANGE_DIRECTION => discrete_EXPRESSION
17740 -- CHANGE_DIRECTION ::= Increases | Decreases
17742 when Pragma_Loop_Variant => Loop_Variant : declare
17743 Variant : Node_Id;
17745 begin
17746 GNAT_Pragma;
17747 Check_At_Least_N_Arguments (1);
17748 Check_Loop_Pragma_Placement;
17750 -- Process all increasing / decreasing expressions
17752 Variant := First (Pragma_Argument_Associations (N));
17753 while Present (Variant) loop
17754 if not Nam_In (Chars (Variant), Name_Decreases,
17755 Name_Increases)
17756 then
17757 Error_Pragma_Arg ("wrong change modifier", Variant);
17758 end if;
17760 Preanalyze_Assert_Expression
17761 (Expression (Variant), Any_Discrete);
17763 Next (Variant);
17764 end loop;
17765 end Loop_Variant;
17767 -----------------------
17768 -- Machine_Attribute --
17769 -----------------------
17771 -- pragma Machine_Attribute (
17772 -- [Entity =>] LOCAL_NAME,
17773 -- [Attribute_Name =>] static_string_EXPRESSION
17774 -- [, [Info =>] static_EXPRESSION] );
17776 when Pragma_Machine_Attribute => Machine_Attribute : declare
17777 Def_Id : Entity_Id;
17779 begin
17780 GNAT_Pragma;
17781 Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
17783 if Arg_Count = 3 then
17784 Check_Optional_Identifier (Arg3, Name_Info);
17785 Check_Arg_Is_OK_Static_Expression (Arg3);
17786 else
17787 Check_Arg_Count (2);
17788 end if;
17790 Check_Optional_Identifier (Arg1, Name_Entity);
17791 Check_Optional_Identifier (Arg2, Name_Attribute_Name);
17792 Check_Arg_Is_Local_Name (Arg1);
17793 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
17794 Def_Id := Entity (Get_Pragma_Arg (Arg1));
17796 if Is_Access_Type (Def_Id) then
17797 Def_Id := Designated_Type (Def_Id);
17798 end if;
17800 if Rep_Item_Too_Early (Def_Id, N) then
17801 return;
17802 end if;
17804 Def_Id := Underlying_Type (Def_Id);
17806 -- The only processing required is to link this item on to the
17807 -- list of rep items for the given entity. This is accomplished
17808 -- by the call to Rep_Item_Too_Late (when no error is detected
17809 -- and False is returned).
17811 if Rep_Item_Too_Late (Def_Id, N) then
17812 return;
17813 else
17814 Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
17815 end if;
17816 end Machine_Attribute;
17818 ----------
17819 -- Main --
17820 ----------
17822 -- pragma Main
17823 -- (MAIN_OPTION [, MAIN_OPTION]);
17825 -- MAIN_OPTION ::=
17826 -- [STACK_SIZE =>] static_integer_EXPRESSION
17827 -- | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
17828 -- | [TIME_SLICING_ENABLED =>] static_boolean_EXPRESSION
17830 when Pragma_Main => Main : declare
17831 Args : Args_List (1 .. 3);
17832 Names : constant Name_List (1 .. 3) := (
17833 Name_Stack_Size,
17834 Name_Task_Stack_Size_Default,
17835 Name_Time_Slicing_Enabled);
17837 Nod : Node_Id;
17839 begin
17840 GNAT_Pragma;
17841 Gather_Associations (Names, Args);
17843 for J in 1 .. 2 loop
17844 if Present (Args (J)) then
17845 Check_Arg_Is_OK_Static_Expression (Args (J), Any_Integer);
17846 end if;
17847 end loop;
17849 if Present (Args (3)) then
17850 Check_Arg_Is_OK_Static_Expression (Args (3), Standard_Boolean);
17851 end if;
17853 Nod := Next (N);
17854 while Present (Nod) loop
17855 if Nkind (Nod) = N_Pragma
17856 and then Pragma_Name (Nod) = Name_Main
17857 then
17858 Error_Msg_Name_1 := Pname;
17859 Error_Msg_N ("duplicate pragma% not permitted", Nod);
17860 end if;
17862 Next (Nod);
17863 end loop;
17864 end Main;
17866 ------------------
17867 -- Main_Storage --
17868 ------------------
17870 -- pragma Main_Storage
17871 -- (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
17873 -- MAIN_STORAGE_OPTION ::=
17874 -- [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
17875 -- | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
17877 when Pragma_Main_Storage => Main_Storage : declare
17878 Args : Args_List (1 .. 2);
17879 Names : constant Name_List (1 .. 2) := (
17880 Name_Working_Storage,
17881 Name_Top_Guard);
17883 Nod : Node_Id;
17885 begin
17886 GNAT_Pragma;
17887 Gather_Associations (Names, Args);
17889 for J in 1 .. 2 loop
17890 if Present (Args (J)) then
17891 Check_Arg_Is_OK_Static_Expression (Args (J), Any_Integer);
17892 end if;
17893 end loop;
17895 Check_In_Main_Program;
17897 Nod := Next (N);
17898 while Present (Nod) loop
17899 if Nkind (Nod) = N_Pragma
17900 and then Pragma_Name (Nod) = Name_Main_Storage
17901 then
17902 Error_Msg_Name_1 := Pname;
17903 Error_Msg_N ("duplicate pragma% not permitted", Nod);
17904 end if;
17906 Next (Nod);
17907 end loop;
17908 end Main_Storage;
17910 ----------------------
17911 -- Max_Queue_Length --
17912 ----------------------
17914 -- pragma Max_Queue_Length (static_integer_EXPRESSION);
17916 when Pragma_Max_Queue_Length => Max_Queue_Length : declare
17917 Arg : Node_Id;
17918 Entry_Decl : Node_Id;
17919 Entry_Id : Entity_Id;
17920 Val : Uint;
17922 begin
17923 GNAT_Pragma;
17924 Check_Arg_Count (1);
17926 Entry_Decl :=
17927 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
17929 -- Entry declaration
17931 if Nkind (Entry_Decl) = N_Entry_Declaration then
17933 -- Entry illegally within a task
17935 if Nkind (Parent (N)) = N_Task_Definition then
17936 Error_Pragma ("pragma % cannot apply to task entries");
17937 return;
17938 end if;
17940 Entry_Id := Unique_Defining_Entity (Entry_Decl);
17942 -- Otherwise the pragma is associated with an illegal construct
17944 else
17945 Error_Pragma ("pragma % must apply to a protected entry");
17946 return;
17947 end if;
17949 -- Mark the pragma as Ghost if the related subprogram is also
17950 -- Ghost. This also ensures that any expansion performed further
17951 -- below will produce Ghost nodes.
17953 Mark_Ghost_Pragma (N, Entry_Id);
17955 -- Analyze the Integer expression
17957 Arg := Get_Pragma_Arg (Arg1);
17958 Check_Arg_Is_OK_Static_Expression (Arg, Any_Integer);
17960 Val := Expr_Value (Arg);
17962 if Val <= 0 then
17963 Error_Pragma_Arg
17964 ("argument for pragma% must be positive", Arg1);
17966 elsif not UI_Is_In_Int_Range (Val) then
17967 Error_Pragma_Arg
17968 ("argument for pragma% out of range of Integer", Arg1);
17970 end if;
17972 -- Manually substitute the expression value of the pragma argument
17973 -- if it's not an integer literal because this is not taken care
17974 -- of automatically elsewhere.
17976 if Nkind (Arg) /= N_Integer_Literal then
17977 Rewrite (Arg, Make_Integer_Literal (Sloc (Arg), Val));
17978 end if;
17980 Record_Rep_Item (Entry_Id, N);
17981 end Max_Queue_Length;
17983 -----------------
17984 -- Memory_Size --
17985 -----------------
17987 -- pragma Memory_Size (NUMERIC_LITERAL)
17989 when Pragma_Memory_Size =>
17990 GNAT_Pragma;
17992 -- Memory size is simply ignored
17994 Check_No_Identifiers;
17995 Check_Arg_Count (1);
17996 Check_Arg_Is_Integer_Literal (Arg1);
17998 -------------
17999 -- No_Body --
18000 -------------
18002 -- pragma No_Body;
18004 -- The only correct use of this pragma is on its own in a file, in
18005 -- which case it is specially processed (see Gnat1drv.Check_Bad_Body
18006 -- and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
18007 -- check for a file containing nothing but a No_Body pragma). If we
18008 -- attempt to process it during normal semantics processing, it means
18009 -- it was misplaced.
18011 when Pragma_No_Body =>
18012 GNAT_Pragma;
18013 Pragma_Misplaced;
18015 -----------------------------
18016 -- No_Elaboration_Code_All --
18017 -----------------------------
18019 -- pragma No_Elaboration_Code_All;
18021 when Pragma_No_Elaboration_Code_All =>
18022 GNAT_Pragma;
18023 Check_Valid_Library_Unit_Pragma;
18025 if Nkind (N) = N_Null_Statement then
18026 return;
18027 end if;
18029 -- Must appear for a spec or generic spec
18031 if not Nkind_In (Unit (Cunit (Current_Sem_Unit)),
18032 N_Generic_Package_Declaration,
18033 N_Generic_Subprogram_Declaration,
18034 N_Package_Declaration,
18035 N_Subprogram_Declaration)
18036 then
18037 Error_Pragma
18038 (Fix_Error
18039 ("pragma% can only occur for package "
18040 & "or subprogram spec"));
18041 end if;
18043 -- Set flag in unit table
18045 Set_No_Elab_Code_All (Current_Sem_Unit);
18047 -- Set restriction No_Elaboration_Code if this is the main unit
18049 if Current_Sem_Unit = Main_Unit then
18050 Set_Restriction (No_Elaboration_Code, N);
18051 end if;
18053 -- If we are in the main unit or in an extended main source unit,
18054 -- then we also add it to the configuration restrictions so that
18055 -- it will apply to all units in the extended main source.
18057 if Current_Sem_Unit = Main_Unit
18058 or else In_Extended_Main_Source_Unit (N)
18059 then
18060 Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
18061 end if;
18063 -- If in main extended unit, activate transitive with test
18065 if In_Extended_Main_Source_Unit (N) then
18066 Opt.No_Elab_Code_All_Pragma := N;
18067 end if;
18069 --------------------------
18070 -- No_Heap_Finalization --
18071 --------------------------
18073 -- pragma No_Heap_Finalization [ (first_subtype_LOCAL_NAME) ];
18075 when Pragma_No_Heap_Finalization => No_Heap_Finalization : declare
18076 Context : constant Node_Id := Parent (N);
18077 Typ_Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
18078 Prev : Node_Id;
18079 Typ : Entity_Id;
18081 begin
18082 GNAT_Pragma;
18083 Check_No_Identifiers;
18085 -- The pragma appears in a configuration file
18087 if No (Context) then
18088 Check_Arg_Count (0);
18089 Check_Valid_Configuration_Pragma;
18091 -- Detect a duplicate pragma
18093 if Present (No_Heap_Finalization_Pragma) then
18094 Duplication_Error
18095 (Prag => N,
18096 Prev => No_Heap_Finalization_Pragma);
18097 raise Pragma_Exit;
18098 end if;
18100 No_Heap_Finalization_Pragma := N;
18102 -- Otherwise the pragma should be associated with a library-level
18103 -- named access-to-object type.
18105 else
18106 Check_Arg_Count (1);
18107 Check_Arg_Is_Local_Name (Arg1);
18109 Find_Type (Typ_Arg);
18110 Typ := Entity (Typ_Arg);
18112 -- The type being subjected to the pragma is erroneous
18114 if Typ = Any_Type then
18115 Error_Pragma ("cannot find type referenced by pragma %");
18117 -- The pragma is applied to an incomplete or generic formal
18118 -- type way too early.
18120 elsif Rep_Item_Too_Early (Typ, N) then
18121 return;
18123 else
18124 Typ := Underlying_Type (Typ);
18125 end if;
18127 -- The pragma must apply to an access-to-object type
18129 if Ekind_In (Typ, E_Access_Type, E_General_Access_Type) then
18130 null;
18132 -- Give a detailed error message on all other access type kinds
18134 elsif Ekind (Typ) = E_Access_Protected_Subprogram_Type then
18135 Error_Pragma
18136 ("pragma % cannot apply to access protected subprogram "
18137 & "type");
18139 elsif Ekind (Typ) = E_Access_Subprogram_Type then
18140 Error_Pragma
18141 ("pragma % cannot apply to access subprogram type");
18143 elsif Is_Anonymous_Access_Type (Typ) then
18144 Error_Pragma
18145 ("pragma % cannot apply to anonymous access type");
18147 -- Give a general error message in case the pragma applies to a
18148 -- non-access type.
18150 else
18151 Error_Pragma
18152 ("pragma % must apply to library level access type");
18153 end if;
18155 -- At this point the argument denotes an access-to-object type.
18156 -- Ensure that the type is declared at the library level.
18158 if Is_Library_Level_Entity (Typ) then
18159 null;
18161 -- Quietly ignore an access-to-object type originally declared
18162 -- at the library level within a generic, but instantiated at
18163 -- a non-library level. As a result the access-to-object type
18164 -- "loses" its No_Heap_Finalization property.
18166 elsif In_Instance then
18167 raise Pragma_Exit;
18169 else
18170 Error_Pragma
18171 ("pragma % must apply to library level access type");
18172 end if;
18174 -- Detect a duplicate pragma
18176 if Present (No_Heap_Finalization_Pragma) then
18177 Duplication_Error
18178 (Prag => N,
18179 Prev => No_Heap_Finalization_Pragma);
18180 raise Pragma_Exit;
18182 else
18183 Prev := Get_Pragma (Typ, Pragma_No_Heap_Finalization);
18185 if Present (Prev) then
18186 Duplication_Error
18187 (Prag => N,
18188 Prev => Prev);
18189 raise Pragma_Exit;
18190 end if;
18191 end if;
18193 Record_Rep_Item (Typ, N);
18194 end if;
18195 end No_Heap_Finalization;
18197 ---------------
18198 -- No_Inline --
18199 ---------------
18201 -- pragma No_Inline ( NAME {, NAME} );
18203 when Pragma_No_Inline =>
18204 GNAT_Pragma;
18205 Process_Inline (Suppressed);
18207 ---------------
18208 -- No_Return --
18209 ---------------
18211 -- pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
18213 when Pragma_No_Return => No_Return : declare
18214 Arg : Node_Id;
18215 E : Entity_Id;
18216 Found : Boolean;
18217 Id : Node_Id;
18219 Ghost_Error_Posted : Boolean := False;
18220 -- Flag set when an error concerning the illegal mix of Ghost and
18221 -- non-Ghost subprograms is emitted.
18223 Ghost_Id : Entity_Id := Empty;
18224 -- The entity of the first Ghost procedure encountered while
18225 -- processing the arguments of the pragma.
18227 begin
18228 Ada_2005_Pragma;
18229 Check_At_Least_N_Arguments (1);
18231 -- Loop through arguments of pragma
18233 Arg := Arg1;
18234 while Present (Arg) loop
18235 Check_Arg_Is_Local_Name (Arg);
18236 Id := Get_Pragma_Arg (Arg);
18237 Analyze (Id);
18239 if not Is_Entity_Name (Id) then
18240 Error_Pragma_Arg ("entity name required", Arg);
18241 end if;
18243 if Etype (Id) = Any_Type then
18244 raise Pragma_Exit;
18245 end if;
18247 -- Loop to find matching procedures
18249 E := Entity (Id);
18251 Found := False;
18252 while Present (E)
18253 and then Scope (E) = Current_Scope
18254 loop
18255 if Ekind_In (E, E_Generic_Procedure, E_Procedure) then
18257 -- Check that the pragma is not applied to a body.
18258 -- First check the specless body case, to give a
18259 -- different error message. These checks do not apply
18260 -- if Relaxed_RM_Semantics, to accommodate other Ada
18261 -- compilers. Disable these checks under -gnatd.J.
18263 if not Debug_Flag_Dot_JJ then
18264 if Nkind (Parent (Declaration_Node (E))) =
18265 N_Subprogram_Body
18266 and then not Relaxed_RM_Semantics
18267 then
18268 Error_Pragma
18269 ("pragma% requires separate spec and must come "
18270 & "before body");
18271 end if;
18273 -- Now the "specful" body case
18275 if Rep_Item_Too_Late (E, N) then
18276 raise Pragma_Exit;
18277 end if;
18278 end if;
18280 Set_No_Return (E);
18282 -- A pragma that applies to a Ghost entity becomes Ghost
18283 -- for the purposes of legality checks and removal of
18284 -- ignored Ghost code.
18286 Mark_Ghost_Pragma (N, E);
18288 -- Capture the entity of the first Ghost procedure being
18289 -- processed for error detection purposes.
18291 if Is_Ghost_Entity (E) then
18292 if No (Ghost_Id) then
18293 Ghost_Id := E;
18294 end if;
18296 -- Otherwise the subprogram is non-Ghost. It is illegal
18297 -- to mix references to Ghost and non-Ghost entities
18298 -- (SPARK RM 6.9).
18300 elsif Present (Ghost_Id)
18301 and then not Ghost_Error_Posted
18302 then
18303 Ghost_Error_Posted := True;
18305 Error_Msg_Name_1 := Pname;
18306 Error_Msg_N
18307 ("pragma % cannot mention ghost and non-ghost "
18308 & "procedures", N);
18310 Error_Msg_Sloc := Sloc (Ghost_Id);
18311 Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
18313 Error_Msg_Sloc := Sloc (E);
18314 Error_Msg_NE ("\& # declared as non-ghost", N, E);
18315 end if;
18317 -- Set flag on any alias as well
18319 if Is_Overloadable (E) and then Present (Alias (E)) then
18320 Set_No_Return (Alias (E));
18321 end if;
18323 Found := True;
18324 end if;
18326 exit when From_Aspect_Specification (N);
18327 E := Homonym (E);
18328 end loop;
18330 -- If entity in not in current scope it may be the enclosing
18331 -- suprogram body to which the aspect applies.
18333 if not Found then
18334 if Entity (Id) = Current_Scope
18335 and then From_Aspect_Specification (N)
18336 then
18337 Set_No_Return (Entity (Id));
18338 else
18339 Error_Pragma_Arg ("no procedure& found for pragma%", Arg);
18340 end if;
18341 end if;
18343 Next (Arg);
18344 end loop;
18345 end No_Return;
18347 -----------------
18348 -- No_Run_Time --
18349 -----------------
18351 -- pragma No_Run_Time;
18353 -- Note: this pragma is retained for backwards compatibility. See
18354 -- body of Rtsfind for full details on its handling.
18356 when Pragma_No_Run_Time =>
18357 GNAT_Pragma;
18358 Check_Valid_Configuration_Pragma;
18359 Check_Arg_Count (0);
18361 -- Remove backward compatibility if Build_Type is FSF or GPL and
18362 -- generate a warning.
18364 declare
18365 Ignore : constant Boolean := Build_Type in FSF .. GPL;
18366 begin
18367 if Ignore then
18368 Error_Pragma ("pragma% is ignored, has no effect??");
18369 else
18370 No_Run_Time_Mode := True;
18371 Configurable_Run_Time_Mode := True;
18373 -- Set Duration to 32 bits if word size is 32
18375 if Ttypes.System_Word_Size = 32 then
18376 Duration_32_Bits_On_Target := True;
18377 end if;
18379 -- Set appropriate restrictions
18381 Set_Restriction (No_Finalization, N);
18382 Set_Restriction (No_Exception_Handlers, N);
18383 Set_Restriction (Max_Tasks, N, 0);
18384 Set_Restriction (No_Tasking, N);
18385 end if;
18386 end;
18388 -----------------------
18389 -- No_Tagged_Streams --
18390 -----------------------
18392 -- pragma No_Tagged_Streams [([Entity => ]tagged_type_local_NAME)];
18394 when Pragma_No_Tagged_Streams => No_Tagged_Strms : declare
18395 E : Entity_Id;
18396 E_Id : Node_Id;
18398 begin
18399 GNAT_Pragma;
18400 Check_At_Most_N_Arguments (1);
18402 -- One argument case
18404 if Arg_Count = 1 then
18405 Check_Optional_Identifier (Arg1, Name_Entity);
18406 Check_Arg_Is_Local_Name (Arg1);
18407 E_Id := Get_Pragma_Arg (Arg1);
18409 if Etype (E_Id) = Any_Type then
18410 return;
18411 end if;
18413 E := Entity (E_Id);
18415 Check_Duplicate_Pragma (E);
18417 if not Is_Tagged_Type (E) or else Is_Derived_Type (E) then
18418 Error_Pragma_Arg
18419 ("argument for pragma% must be root tagged type", Arg1);
18420 end if;
18422 if Rep_Item_Too_Early (E, N)
18423 or else
18424 Rep_Item_Too_Late (E, N)
18425 then
18426 return;
18427 else
18428 Set_No_Tagged_Streams_Pragma (E, N);
18429 end if;
18431 -- Zero argument case
18433 else
18434 Check_Is_In_Decl_Part_Or_Package_Spec;
18435 No_Tagged_Streams := N;
18436 end if;
18437 end No_Tagged_Strms;
18439 ------------------------
18440 -- No_Strict_Aliasing --
18441 ------------------------
18443 -- pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
18445 when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
18446 E_Id : Entity_Id;
18448 begin
18449 GNAT_Pragma;
18450 Check_At_Most_N_Arguments (1);
18452 if Arg_Count = 0 then
18453 Check_Valid_Configuration_Pragma;
18454 Opt.No_Strict_Aliasing := True;
18456 else
18457 Check_Optional_Identifier (Arg2, Name_Entity);
18458 Check_Arg_Is_Local_Name (Arg1);
18459 E_Id := Entity (Get_Pragma_Arg (Arg1));
18461 if E_Id = Any_Type then
18462 return;
18463 elsif No (E_Id) or else not Is_Access_Type (E_Id) then
18464 Error_Pragma_Arg ("pragma% requires access type", Arg1);
18465 end if;
18467 Set_No_Strict_Aliasing (Implementation_Base_Type (E_Id));
18468 end if;
18469 end No_Strict_Aliasing;
18471 -----------------------
18472 -- Normalize_Scalars --
18473 -----------------------
18475 -- pragma Normalize_Scalars;
18477 when Pragma_Normalize_Scalars =>
18478 Check_Ada_83_Warning;
18479 Check_Arg_Count (0);
18480 Check_Valid_Configuration_Pragma;
18482 -- Normalize_Scalars creates false positives in CodePeer, and
18483 -- incorrect negative results in GNATprove mode, so ignore this
18484 -- pragma in these modes.
18486 if not (CodePeer_Mode or GNATprove_Mode) then
18487 Normalize_Scalars := True;
18488 Init_Or_Norm_Scalars := True;
18489 end if;
18491 -----------------
18492 -- Obsolescent --
18493 -----------------
18495 -- pragma Obsolescent;
18497 -- pragma Obsolescent (
18498 -- [Message =>] static_string_EXPRESSION
18499 -- [,[Version =>] Ada_05]]);
18501 -- pragma Obsolescent (
18502 -- [Entity =>] NAME
18503 -- [,[Message =>] static_string_EXPRESSION
18504 -- [,[Version =>] Ada_05]] );
18506 when Pragma_Obsolescent => Obsolescent : declare
18507 Decl : Node_Id;
18508 Ename : Node_Id;
18510 procedure Set_Obsolescent (E : Entity_Id);
18511 -- Given an entity Ent, mark it as obsolescent if appropriate
18513 ---------------------
18514 -- Set_Obsolescent --
18515 ---------------------
18517 procedure Set_Obsolescent (E : Entity_Id) is
18518 Active : Boolean;
18519 Ent : Entity_Id;
18520 S : String_Id;
18522 begin
18523 Active := True;
18524 Ent := E;
18526 -- A pragma that applies to a Ghost entity becomes Ghost for
18527 -- the purposes of legality checks and removal of ignored Ghost
18528 -- code.
18530 Mark_Ghost_Pragma (N, E);
18532 -- Entity name was given
18534 if Present (Ename) then
18536 -- If entity name matches, we are fine. Save entity in
18537 -- pragma argument, for ASIS use.
18539 if Chars (Ename) = Chars (Ent) then
18540 Set_Entity (Ename, Ent);
18541 Generate_Reference (Ent, Ename);
18543 -- If entity name does not match, only possibility is an
18544 -- enumeration literal from an enumeration type declaration.
18546 elsif Ekind (Ent) /= E_Enumeration_Type then
18547 Error_Pragma
18548 ("pragma % entity name does not match declaration");
18550 else
18551 Ent := First_Literal (E);
18552 loop
18553 if No (Ent) then
18554 Error_Pragma
18555 ("pragma % entity name does not match any "
18556 & "enumeration literal");
18558 elsif Chars (Ent) = Chars (Ename) then
18559 Set_Entity (Ename, Ent);
18560 Generate_Reference (Ent, Ename);
18561 exit;
18563 else
18564 Ent := Next_Literal (Ent);
18565 end if;
18566 end loop;
18567 end if;
18568 end if;
18570 -- Ent points to entity to be marked
18572 if Arg_Count >= 1 then
18574 -- Deal with static string argument
18576 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
18577 S := Strval (Get_Pragma_Arg (Arg1));
18579 for J in 1 .. String_Length (S) loop
18580 if not In_Character_Range (Get_String_Char (S, J)) then
18581 Error_Pragma_Arg
18582 ("pragma% argument does not allow wide characters",
18583 Arg1);
18584 end if;
18585 end loop;
18587 Obsolescent_Warnings.Append
18588 ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
18590 -- Check for Ada_05 parameter
18592 if Arg_Count /= 1 then
18593 Check_Arg_Count (2);
18595 declare
18596 Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
18598 begin
18599 Check_Arg_Is_Identifier (Argx);
18601 if Chars (Argx) /= Name_Ada_05 then
18602 Error_Msg_Name_2 := Name_Ada_05;
18603 Error_Pragma_Arg
18604 ("only allowed argument for pragma% is %", Argx);
18605 end if;
18607 if Ada_Version_Explicit < Ada_2005
18608 or else not Warn_On_Ada_2005_Compatibility
18609 then
18610 Active := False;
18611 end if;
18612 end;
18613 end if;
18614 end if;
18616 -- Set flag if pragma active
18618 if Active then
18619 Set_Is_Obsolescent (Ent);
18620 end if;
18622 return;
18623 end Set_Obsolescent;
18625 -- Start of processing for pragma Obsolescent
18627 begin
18628 GNAT_Pragma;
18630 Check_At_Most_N_Arguments (3);
18632 -- See if first argument specifies an entity name
18634 if Arg_Count >= 1
18635 and then
18636 (Chars (Arg1) = Name_Entity
18637 or else
18638 Nkind_In (Get_Pragma_Arg (Arg1), N_Character_Literal,
18639 N_Identifier,
18640 N_Operator_Symbol))
18641 then
18642 Ename := Get_Pragma_Arg (Arg1);
18644 -- Eliminate first argument, so we can share processing
18646 Arg1 := Arg2;
18647 Arg2 := Arg3;
18648 Arg_Count := Arg_Count - 1;
18650 -- No Entity name argument given
18652 else
18653 Ename := Empty;
18654 end if;
18656 if Arg_Count >= 1 then
18657 Check_Optional_Identifier (Arg1, Name_Message);
18659 if Arg_Count = 2 then
18660 Check_Optional_Identifier (Arg2, Name_Version);
18661 end if;
18662 end if;
18664 -- Get immediately preceding declaration
18666 Decl := Prev (N);
18667 while Present (Decl) and then Nkind (Decl) = N_Pragma loop
18668 Prev (Decl);
18669 end loop;
18671 -- Cases where we do not follow anything other than another pragma
18673 if No (Decl) then
18675 -- First case: library level compilation unit declaration with
18676 -- the pragma immediately following the declaration.
18678 if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
18679 Set_Obsolescent
18680 (Defining_Entity (Unit (Parent (Parent (N)))));
18681 return;
18683 -- Case 2: library unit placement for package
18685 else
18686 declare
18687 Ent : constant Entity_Id := Find_Lib_Unit_Name;
18688 begin
18689 if Is_Package_Or_Generic_Package (Ent) then
18690 Set_Obsolescent (Ent);
18691 return;
18692 end if;
18693 end;
18694 end if;
18696 -- Cases where we must follow a declaration, including an
18697 -- abstract subprogram declaration, which is not in the
18698 -- other node subtypes.
18700 else
18701 if Nkind (Decl) not in N_Declaration
18702 and then Nkind (Decl) not in N_Later_Decl_Item
18703 and then Nkind (Decl) not in N_Generic_Declaration
18704 and then Nkind (Decl) not in N_Renaming_Declaration
18705 and then Nkind (Decl) /= N_Abstract_Subprogram_Declaration
18706 then
18707 Error_Pragma
18708 ("pragma% misplaced, "
18709 & "must immediately follow a declaration");
18711 else
18712 Set_Obsolescent (Defining_Entity (Decl));
18713 return;
18714 end if;
18715 end if;
18716 end Obsolescent;
18718 --------------
18719 -- Optimize --
18720 --------------
18722 -- pragma Optimize (Time | Space | Off);
18724 -- The actual check for optimize is done in Gigi. Note that this
18725 -- pragma does not actually change the optimization setting, it
18726 -- simply checks that it is consistent with the pragma.
18728 when Pragma_Optimize =>
18729 Check_No_Identifiers;
18730 Check_Arg_Count (1);
18731 Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
18733 ------------------------
18734 -- Optimize_Alignment --
18735 ------------------------
18737 -- pragma Optimize_Alignment (Time | Space | Off);
18739 when Pragma_Optimize_Alignment => Optimize_Alignment : begin
18740 GNAT_Pragma;
18741 Check_No_Identifiers;
18742 Check_Arg_Count (1);
18743 Check_Valid_Configuration_Pragma;
18745 declare
18746 Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
18747 begin
18748 case Nam is
18749 when Name_Off => Opt.Optimize_Alignment := 'O';
18750 when Name_Space => Opt.Optimize_Alignment := 'S';
18751 when Name_Time => Opt.Optimize_Alignment := 'T';
18753 when others =>
18754 Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
18755 end case;
18756 end;
18758 -- Set indication that mode is set locally. If we are in fact in a
18759 -- configuration pragma file, this setting is harmless since the
18760 -- switch will get reset anyway at the start of each unit.
18762 Optimize_Alignment_Local := True;
18763 end Optimize_Alignment;
18765 -------------
18766 -- Ordered --
18767 -------------
18769 -- pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
18771 when Pragma_Ordered => Ordered : declare
18772 Assoc : constant Node_Id := Arg1;
18773 Type_Id : Node_Id;
18774 Typ : Entity_Id;
18776 begin
18777 GNAT_Pragma;
18778 Check_No_Identifiers;
18779 Check_Arg_Count (1);
18780 Check_Arg_Is_Local_Name (Arg1);
18782 Type_Id := Get_Pragma_Arg (Assoc);
18783 Find_Type (Type_Id);
18784 Typ := Entity (Type_Id);
18786 if Typ = Any_Type then
18787 return;
18788 else
18789 Typ := Underlying_Type (Typ);
18790 end if;
18792 if not Is_Enumeration_Type (Typ) then
18793 Error_Pragma ("pragma% must specify enumeration type");
18794 end if;
18796 Check_First_Subtype (Arg1);
18797 Set_Has_Pragma_Ordered (Base_Type (Typ));
18798 end Ordered;
18800 -------------------
18801 -- Overflow_Mode --
18802 -------------------
18804 -- pragma Overflow_Mode
18805 -- ([General => ] MODE [, [Assertions => ] MODE]);
18807 -- MODE := STRICT | MINIMIZED | ELIMINATED
18809 -- Note: ELIMINATED is allowed only if Long_Long_Integer'Size is 64
18810 -- since System.Bignums makes this assumption. This is true of nearly
18811 -- all (all?) targets.
18813 when Pragma_Overflow_Mode => Overflow_Mode : declare
18814 function Get_Overflow_Mode
18815 (Name : Name_Id;
18816 Arg : Node_Id) return Overflow_Mode_Type;
18817 -- Function to process one pragma argument, Arg. If an identifier
18818 -- is present, it must be Name. Mode type is returned if a valid
18819 -- argument exists, otherwise an error is signalled.
18821 -----------------------
18822 -- Get_Overflow_Mode --
18823 -----------------------
18825 function Get_Overflow_Mode
18826 (Name : Name_Id;
18827 Arg : Node_Id) return Overflow_Mode_Type
18829 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
18831 begin
18832 Check_Optional_Identifier (Arg, Name);
18833 Check_Arg_Is_Identifier (Argx);
18835 if Chars (Argx) = Name_Strict then
18836 return Strict;
18838 elsif Chars (Argx) = Name_Minimized then
18839 return Minimized;
18841 elsif Chars (Argx) = Name_Eliminated then
18842 if Ttypes.Standard_Long_Long_Integer_Size /= 64 then
18843 Error_Pragma_Arg
18844 ("Eliminated not implemented on this target", Argx);
18845 else
18846 return Eliminated;
18847 end if;
18849 else
18850 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
18851 end if;
18852 end Get_Overflow_Mode;
18854 -- Start of processing for Overflow_Mode
18856 begin
18857 GNAT_Pragma;
18858 Check_At_Least_N_Arguments (1);
18859 Check_At_Most_N_Arguments (2);
18861 -- Process first argument
18863 Scope_Suppress.Overflow_Mode_General :=
18864 Get_Overflow_Mode (Name_General, Arg1);
18866 -- Case of only one argument
18868 if Arg_Count = 1 then
18869 Scope_Suppress.Overflow_Mode_Assertions :=
18870 Scope_Suppress.Overflow_Mode_General;
18872 -- Case of two arguments present
18874 else
18875 Scope_Suppress.Overflow_Mode_Assertions :=
18876 Get_Overflow_Mode (Name_Assertions, Arg2);
18877 end if;
18878 end Overflow_Mode;
18880 --------------------------
18881 -- Overriding Renamings --
18882 --------------------------
18884 -- pragma Overriding_Renamings;
18886 when Pragma_Overriding_Renamings =>
18887 GNAT_Pragma;
18888 Check_Arg_Count (0);
18889 Check_Valid_Configuration_Pragma;
18890 Overriding_Renamings := True;
18892 ----------
18893 -- Pack --
18894 ----------
18896 -- pragma Pack (first_subtype_LOCAL_NAME);
18898 when Pragma_Pack => Pack : declare
18899 Assoc : constant Node_Id := Arg1;
18900 Ctyp : Entity_Id;
18901 Ignore : Boolean := False;
18902 Typ : Entity_Id;
18903 Type_Id : Node_Id;
18905 begin
18906 Check_No_Identifiers;
18907 Check_Arg_Count (1);
18908 Check_Arg_Is_Local_Name (Arg1);
18909 Type_Id := Get_Pragma_Arg (Assoc);
18911 if not Is_Entity_Name (Type_Id)
18912 or else not Is_Type (Entity (Type_Id))
18913 then
18914 Error_Pragma_Arg
18915 ("argument for pragma% must be type or subtype", Arg1);
18916 end if;
18918 Find_Type (Type_Id);
18919 Typ := Entity (Type_Id);
18921 if Typ = Any_Type
18922 or else Rep_Item_Too_Early (Typ, N)
18923 then
18924 return;
18925 else
18926 Typ := Underlying_Type (Typ);
18927 end if;
18929 -- A pragma that applies to a Ghost entity becomes Ghost for the
18930 -- purposes of legality checks and removal of ignored Ghost code.
18932 Mark_Ghost_Pragma (N, Typ);
18934 if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
18935 Error_Pragma ("pragma% must specify array or record type");
18936 end if;
18938 Check_First_Subtype (Arg1);
18939 Check_Duplicate_Pragma (Typ);
18941 -- Array type
18943 if Is_Array_Type (Typ) then
18944 Ctyp := Component_Type (Typ);
18946 -- Ignore pack that does nothing
18948 if Known_Static_Esize (Ctyp)
18949 and then Known_Static_RM_Size (Ctyp)
18950 and then Esize (Ctyp) = RM_Size (Ctyp)
18951 and then Addressable (Esize (Ctyp))
18952 then
18953 Ignore := True;
18954 end if;
18956 -- Process OK pragma Pack. Note that if there is a separate
18957 -- component clause present, the Pack will be cancelled. This
18958 -- processing is in Freeze.
18960 if not Rep_Item_Too_Late (Typ, N) then
18962 -- In CodePeer mode, we do not need complex front-end
18963 -- expansions related to pragma Pack, so disable handling
18964 -- of pragma Pack.
18966 if CodePeer_Mode then
18967 null;
18969 -- Normal case where we do the pack action
18971 else
18972 if not Ignore then
18973 Set_Is_Packed (Base_Type (Typ));
18974 Set_Has_Non_Standard_Rep (Base_Type (Typ));
18975 end if;
18977 Set_Has_Pragma_Pack (Base_Type (Typ));
18978 end if;
18979 end if;
18981 -- For record types, the pack is always effective
18983 else pragma Assert (Is_Record_Type (Typ));
18984 if not Rep_Item_Too_Late (Typ, N) then
18985 Set_Is_Packed (Base_Type (Typ));
18986 Set_Has_Pragma_Pack (Base_Type (Typ));
18987 Set_Has_Non_Standard_Rep (Base_Type (Typ));
18988 end if;
18989 end if;
18990 end Pack;
18992 ----------
18993 -- Page --
18994 ----------
18996 -- pragma Page;
18998 -- There is nothing to do here, since we did all the processing for
18999 -- this pragma in Par.Prag (so that it works properly even in syntax
19000 -- only mode).
19002 when Pragma_Page =>
19003 null;
19005 -------------
19006 -- Part_Of --
19007 -------------
19009 -- pragma Part_Of (ABSTRACT_STATE);
19011 -- ABSTRACT_STATE ::= NAME
19013 when Pragma_Part_Of => Part_Of : declare
19014 procedure Propagate_Part_Of
19015 (Pack_Id : Entity_Id;
19016 State_Id : Entity_Id;
19017 Instance : Node_Id);
19018 -- Propagate the Part_Of indicator to all abstract states and
19019 -- objects declared in the visible state space of a package
19020 -- denoted by Pack_Id. State_Id is the encapsulating state.
19021 -- Instance is the package instantiation node.
19023 -----------------------
19024 -- Propagate_Part_Of --
19025 -----------------------
19027 procedure Propagate_Part_Of
19028 (Pack_Id : Entity_Id;
19029 State_Id : Entity_Id;
19030 Instance : Node_Id)
19032 Has_Item : Boolean := False;
19033 -- Flag set when the visible state space contains at least one
19034 -- abstract state or variable.
19036 procedure Propagate_Part_Of (Pack_Id : Entity_Id);
19037 -- Propagate the Part_Of indicator to all abstract states and
19038 -- objects declared in the visible state space of a package
19039 -- denoted by Pack_Id.
19041 -----------------------
19042 -- Propagate_Part_Of --
19043 -----------------------
19045 procedure Propagate_Part_Of (Pack_Id : Entity_Id) is
19046 Constits : Elist_Id;
19047 Item_Id : Entity_Id;
19049 begin
19050 -- Traverse the entity chain of the package and set relevant
19051 -- attributes of abstract states and objects declared in the
19052 -- visible state space of the package.
19054 Item_Id := First_Entity (Pack_Id);
19055 while Present (Item_Id)
19056 and then not In_Private_Part (Item_Id)
19057 loop
19058 -- Do not consider internally generated items
19060 if not Comes_From_Source (Item_Id) then
19061 null;
19063 -- The Part_Of indicator turns an abstract state or an
19064 -- object into a constituent of the encapsulating state.
19066 elsif Ekind_In (Item_Id, E_Abstract_State,
19067 E_Constant,
19068 E_Variable)
19069 then
19070 Has_Item := True;
19071 Constits := Part_Of_Constituents (State_Id);
19073 if No (Constits) then
19074 Constits := New_Elmt_List;
19075 Set_Part_Of_Constituents (State_Id, Constits);
19076 end if;
19078 Append_Elmt (Item_Id, Constits);
19079 Set_Encapsulating_State (Item_Id, State_Id);
19081 -- Recursively handle nested packages and instantiations
19083 elsif Ekind (Item_Id) = E_Package then
19084 Propagate_Part_Of (Item_Id);
19085 end if;
19087 Next_Entity (Item_Id);
19088 end loop;
19089 end Propagate_Part_Of;
19091 -- Start of processing for Propagate_Part_Of
19093 begin
19094 Propagate_Part_Of (Pack_Id);
19096 -- Detect a package instantiation that is subject to a Part_Of
19097 -- indicator, but has no visible state.
19099 if not Has_Item then
19100 SPARK_Msg_NE
19101 ("package instantiation & has Part_Of indicator but "
19102 & "lacks visible state", Instance, Pack_Id);
19103 end if;
19104 end Propagate_Part_Of;
19106 -- Local variables
19108 Constits : Elist_Id;
19109 Encap : Node_Id;
19110 Encap_Id : Entity_Id;
19111 Item_Id : Entity_Id;
19112 Legal : Boolean;
19113 Stmt : Node_Id;
19115 -- Start of processing for Part_Of
19117 begin
19118 GNAT_Pragma;
19119 Check_No_Identifiers;
19120 Check_Arg_Count (1);
19122 Stmt := Find_Related_Context (N, Do_Checks => True);
19124 -- Object declaration
19126 if Nkind (Stmt) = N_Object_Declaration then
19127 null;
19129 -- Package instantiation
19131 elsif Nkind (Stmt) = N_Package_Instantiation then
19132 null;
19134 -- Single concurrent type declaration
19136 elsif Is_Single_Concurrent_Type_Declaration (Stmt) then
19137 null;
19139 -- Otherwise the pragma is associated with an illegal construct
19141 else
19142 Pragma_Misplaced;
19143 return;
19144 end if;
19146 -- Extract the entity of the related object declaration or package
19147 -- instantiation. In the case of the instantiation, use the entity
19148 -- of the instance spec.
19150 if Nkind (Stmt) = N_Package_Instantiation then
19151 Stmt := Instance_Spec (Stmt);
19152 end if;
19154 Item_Id := Defining_Entity (Stmt);
19156 -- A pragma that applies to a Ghost entity becomes Ghost for the
19157 -- purposes of legality checks and removal of ignored Ghost code.
19159 Mark_Ghost_Pragma (N, Item_Id);
19161 -- Chain the pragma on the contract for further processing by
19162 -- Analyze_Part_Of_In_Decl_Part or for completeness.
19164 Add_Contract_Item (N, Item_Id);
19166 -- A variable may act as constituent of a single concurrent type
19167 -- which in turn could be declared after the variable. Due to this
19168 -- discrepancy, the full analysis of indicator Part_Of is delayed
19169 -- until the end of the enclosing declarative region (see routine
19170 -- Analyze_Part_Of_In_Decl_Part).
19172 if Ekind (Item_Id) = E_Variable then
19173 null;
19175 -- Otherwise indicator Part_Of applies to a constant or a package
19176 -- instantiation.
19178 else
19179 Encap := Get_Pragma_Arg (Arg1);
19181 -- Detect any discrepancies between the placement of the
19182 -- constant or package instantiation with respect to state
19183 -- space and the encapsulating state.
19185 Analyze_Part_Of
19186 (Indic => N,
19187 Item_Id => Item_Id,
19188 Encap => Encap,
19189 Encap_Id => Encap_Id,
19190 Legal => Legal);
19192 if Legal then
19193 pragma Assert (Present (Encap_Id));
19195 if Ekind (Item_Id) = E_Constant then
19196 Constits := Part_Of_Constituents (Encap_Id);
19198 if No (Constits) then
19199 Constits := New_Elmt_List;
19200 Set_Part_Of_Constituents (Encap_Id, Constits);
19201 end if;
19203 Append_Elmt (Item_Id, Constits);
19204 Set_Encapsulating_State (Item_Id, Encap_Id);
19206 -- Propagate the Part_Of indicator to the visible state
19207 -- space of the package instantiation.
19209 else
19210 Propagate_Part_Of
19211 (Pack_Id => Item_Id,
19212 State_Id => Encap_Id,
19213 Instance => Stmt);
19214 end if;
19215 end if;
19216 end if;
19217 end Part_Of;
19219 ----------------------------------
19220 -- Partition_Elaboration_Policy --
19221 ----------------------------------
19223 -- pragma Partition_Elaboration_Policy (policy_IDENTIFIER);
19225 when Pragma_Partition_Elaboration_Policy => PEP : declare
19226 subtype PEP_Range is Name_Id
19227 range First_Partition_Elaboration_Policy_Name
19228 .. Last_Partition_Elaboration_Policy_Name;
19229 PEP_Val : PEP_Range;
19230 PEP : Character;
19232 begin
19233 Ada_2005_Pragma;
19234 Check_Arg_Count (1);
19235 Check_No_Identifiers;
19236 Check_Arg_Is_Partition_Elaboration_Policy (Arg1);
19237 Check_Valid_Configuration_Pragma;
19238 PEP_Val := Chars (Get_Pragma_Arg (Arg1));
19240 case PEP_Val is
19241 when Name_Concurrent => PEP := 'C';
19242 when Name_Sequential => PEP := 'S';
19243 end case;
19245 if Partition_Elaboration_Policy /= ' '
19246 and then Partition_Elaboration_Policy /= PEP
19247 then
19248 Error_Msg_Sloc := Partition_Elaboration_Policy_Sloc;
19249 Error_Pragma
19250 ("partition elaboration policy incompatible with policy#");
19252 -- Set new policy, but always preserve System_Location since we
19253 -- like the error message with the run time name.
19255 else
19256 Partition_Elaboration_Policy := PEP;
19258 if Partition_Elaboration_Policy_Sloc /= System_Location then
19259 Partition_Elaboration_Policy_Sloc := Loc;
19260 end if;
19261 end if;
19262 end PEP;
19264 -------------
19265 -- Passive --
19266 -------------
19268 -- pragma Passive [(PASSIVE_FORM)];
19270 -- PASSIVE_FORM ::= Semaphore | No
19272 when Pragma_Passive =>
19273 GNAT_Pragma;
19275 if Nkind (Parent (N)) /= N_Task_Definition then
19276 Error_Pragma ("pragma% must be within task definition");
19277 end if;
19279 if Arg_Count /= 0 then
19280 Check_Arg_Count (1);
19281 Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
19282 end if;
19284 ----------------------------------
19285 -- Preelaborable_Initialization --
19286 ----------------------------------
19288 -- pragma Preelaborable_Initialization (DIRECT_NAME);
19290 when Pragma_Preelaborable_Initialization => Preelab_Init : declare
19291 Ent : Entity_Id;
19293 begin
19294 Ada_2005_Pragma;
19295 Check_Arg_Count (1);
19296 Check_No_Identifiers;
19297 Check_Arg_Is_Identifier (Arg1);
19298 Check_Arg_Is_Local_Name (Arg1);
19299 Check_First_Subtype (Arg1);
19300 Ent := Entity (Get_Pragma_Arg (Arg1));
19302 -- A pragma that applies to a Ghost entity becomes Ghost for the
19303 -- purposes of legality checks and removal of ignored Ghost code.
19305 Mark_Ghost_Pragma (N, Ent);
19307 -- The pragma may come from an aspect on a private declaration,
19308 -- even if the freeze point at which this is analyzed in the
19309 -- private part after the full view.
19311 if Has_Private_Declaration (Ent)
19312 and then From_Aspect_Specification (N)
19313 then
19314 null;
19316 -- Check appropriate type argument
19318 elsif Is_Private_Type (Ent)
19319 or else Is_Protected_Type (Ent)
19320 or else (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent))
19322 -- AI05-0028: The pragma applies to all composite types. Note
19323 -- that we apply this binding interpretation to earlier versions
19324 -- of Ada, so there is no Ada 2012 guard. Seems a reasonable
19325 -- choice since there are other compilers that do the same.
19327 or else Is_Composite_Type (Ent)
19328 then
19329 null;
19331 else
19332 Error_Pragma_Arg
19333 ("pragma % can only be applied to private, formal derived, "
19334 & "protected, or composite type", Arg1);
19335 end if;
19337 -- Give an error if the pragma is applied to a protected type that
19338 -- does not qualify (due to having entries, or due to components
19339 -- that do not qualify).
19341 if Is_Protected_Type (Ent)
19342 and then not Has_Preelaborable_Initialization (Ent)
19343 then
19344 Error_Msg_N
19345 ("protected type & does not have preelaborable "
19346 & "initialization", Ent);
19348 -- Otherwise mark the type as definitely having preelaborable
19349 -- initialization.
19351 else
19352 Set_Known_To_Have_Preelab_Init (Ent);
19353 end if;
19355 if Has_Pragma_Preelab_Init (Ent)
19356 and then Warn_On_Redundant_Constructs
19357 then
19358 Error_Pragma ("?r?duplicate pragma%!");
19359 else
19360 Set_Has_Pragma_Preelab_Init (Ent);
19361 end if;
19362 end Preelab_Init;
19364 --------------------
19365 -- Persistent_BSS --
19366 --------------------
19368 -- pragma Persistent_BSS [(object_NAME)];
19370 when Pragma_Persistent_BSS => Persistent_BSS : declare
19371 Decl : Node_Id;
19372 Ent : Entity_Id;
19373 Prag : Node_Id;
19375 begin
19376 GNAT_Pragma;
19377 Check_At_Most_N_Arguments (1);
19379 -- Case of application to specific object (one argument)
19381 if Arg_Count = 1 then
19382 Check_Arg_Is_Library_Level_Local_Name (Arg1);
19384 if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
19385 or else not
19386 Ekind_In (Entity (Get_Pragma_Arg (Arg1)), E_Variable,
19387 E_Constant)
19388 then
19389 Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
19390 end if;
19392 Ent := Entity (Get_Pragma_Arg (Arg1));
19394 -- A pragma that applies to a Ghost entity becomes Ghost for
19395 -- the purposes of legality checks and removal of ignored Ghost
19396 -- code.
19398 Mark_Ghost_Pragma (N, Ent);
19400 -- Check for duplication before inserting in list of
19401 -- representation items.
19403 Check_Duplicate_Pragma (Ent);
19405 if Rep_Item_Too_Late (Ent, N) then
19406 return;
19407 end if;
19409 Decl := Parent (Ent);
19411 if Present (Expression (Decl)) then
19412 Error_Pragma_Arg
19413 ("object for pragma% cannot have initialization", Arg1);
19414 end if;
19416 if not Is_Potentially_Persistent_Type (Etype (Ent)) then
19417 Error_Pragma_Arg
19418 ("object type for pragma% is not potentially persistent",
19419 Arg1);
19420 end if;
19422 Prag :=
19423 Make_Linker_Section_Pragma
19424 (Ent, Sloc (N), ".persistent.bss");
19425 Insert_After (N, Prag);
19426 Analyze (Prag);
19428 -- Case of use as configuration pragma with no arguments
19430 else
19431 Check_Valid_Configuration_Pragma;
19432 Persistent_BSS_Mode := True;
19433 end if;
19434 end Persistent_BSS;
19436 --------------------
19437 -- Rename_Pragma --
19438 --------------------
19440 -- pragma Rename_Pragma (
19441 -- [New_Name =>] IDENTIFIER,
19442 -- [Renamed =>] pragma_IDENTIFIER);
19444 when Pragma_Rename_Pragma => Rename_Pragma : declare
19445 New_Name : constant Node_Id := Get_Pragma_Arg (Arg1);
19446 Old_Name : constant Node_Id := Get_Pragma_Arg (Arg2);
19448 begin
19449 GNAT_Pragma;
19450 Check_Valid_Configuration_Pragma;
19451 Check_Arg_Count (2);
19452 Check_Optional_Identifier (Arg1, Name_New_Name);
19453 Check_Optional_Identifier (Arg2, Name_Renamed);
19455 if Nkind (New_Name) /= N_Identifier then
19456 Error_Pragma_Arg ("identifier expected", Arg1);
19457 end if;
19459 if Nkind (Old_Name) /= N_Identifier then
19460 Error_Pragma_Arg ("identifier expected", Arg2);
19461 end if;
19463 -- The New_Name arg should not be an existing pragma (but we allow
19464 -- it; it's just a warning). The Old_Name arg must be an existing
19465 -- pragma.
19467 if Is_Pragma_Name (Chars (New_Name)) then
19468 Error_Pragma_Arg ("??pragma is already defined", Arg1);
19469 end if;
19471 if not Is_Pragma_Name (Chars (Old_Name)) then
19472 Error_Pragma_Arg ("existing pragma name expected", Arg1);
19473 end if;
19475 Map_Pragma_Name (From => Chars (New_Name), To => Chars (Old_Name));
19476 end Rename_Pragma;
19478 -------------
19479 -- Polling --
19480 -------------
19482 -- pragma Polling (ON | OFF);
19484 when Pragma_Polling =>
19485 GNAT_Pragma;
19486 Check_Arg_Count (1);
19487 Check_No_Identifiers;
19488 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
19489 Polling_Required := (Chars (Get_Pragma_Arg (Arg1)) = Name_On);
19491 -----------------------------------
19492 -- Post/Post_Class/Postcondition --
19493 -----------------------------------
19495 -- pragma Post (Boolean_EXPRESSION);
19496 -- pragma Post_Class (Boolean_EXPRESSION);
19497 -- pragma Postcondition ([Check =>] Boolean_EXPRESSION
19498 -- [,[Message =>] String_EXPRESSION]);
19500 -- Characteristics:
19502 -- * Analysis - The annotation undergoes initial checks to verify
19503 -- the legal placement and context. Secondary checks preanalyze the
19504 -- expression in:
19506 -- Analyze_Pre_Post_Condition_In_Decl_Part
19508 -- * Expansion - The annotation is expanded during the expansion of
19509 -- the related subprogram [body] contract as performed in:
19511 -- Expand_Subprogram_Contract
19513 -- * Template - The annotation utilizes the generic template of the
19514 -- related subprogram [body] when it is:
19516 -- aspect on subprogram declaration
19517 -- aspect on stand alone subprogram body
19518 -- pragma on stand alone subprogram body
19520 -- The annotation must prepare its own template when it is:
19522 -- pragma on subprogram declaration
19524 -- * Globals - Capture of global references must occur after full
19525 -- analysis.
19527 -- * Instance - The annotation is instantiated automatically when
19528 -- the related generic subprogram [body] is instantiated except for
19529 -- the "pragma on subprogram declaration" case. In that scenario
19530 -- the annotation must instantiate itself.
19532 when Pragma_Post
19533 | Pragma_Post_Class
19534 | Pragma_Postcondition
19536 Analyze_Pre_Post_Condition;
19538 --------------------------------
19539 -- Pre/Pre_Class/Precondition --
19540 --------------------------------
19542 -- pragma Pre (Boolean_EXPRESSION);
19543 -- pragma Pre_Class (Boolean_EXPRESSION);
19544 -- pragma Precondition ([Check =>] Boolean_EXPRESSION
19545 -- [,[Message =>] String_EXPRESSION]);
19547 -- Characteristics:
19549 -- * Analysis - The annotation undergoes initial checks to verify
19550 -- the legal placement and context. Secondary checks preanalyze the
19551 -- expression in:
19553 -- Analyze_Pre_Post_Condition_In_Decl_Part
19555 -- * Expansion - The annotation is expanded during the expansion of
19556 -- the related subprogram [body] contract as performed in:
19558 -- Expand_Subprogram_Contract
19560 -- * Template - The annotation utilizes the generic template of the
19561 -- related subprogram [body] when it is:
19563 -- aspect on subprogram declaration
19564 -- aspect on stand alone subprogram body
19565 -- pragma on stand alone subprogram body
19567 -- The annotation must prepare its own template when it is:
19569 -- pragma on subprogram declaration
19571 -- * Globals - Capture of global references must occur after full
19572 -- analysis.
19574 -- * Instance - The annotation is instantiated automatically when
19575 -- the related generic subprogram [body] is instantiated except for
19576 -- the "pragma on subprogram declaration" case. In that scenario
19577 -- the annotation must instantiate itself.
19579 when Pragma_Pre
19580 | Pragma_Pre_Class
19581 | Pragma_Precondition
19583 Analyze_Pre_Post_Condition;
19585 ---------------
19586 -- Predicate --
19587 ---------------
19589 -- pragma Predicate
19590 -- ([Entity =>] type_LOCAL_NAME,
19591 -- [Check =>] boolean_EXPRESSION);
19593 when Pragma_Predicate => Predicate : declare
19594 Discard : Boolean;
19595 Typ : Entity_Id;
19596 Type_Id : Node_Id;
19598 begin
19599 GNAT_Pragma;
19600 Check_Arg_Count (2);
19601 Check_Optional_Identifier (Arg1, Name_Entity);
19602 Check_Optional_Identifier (Arg2, Name_Check);
19604 Check_Arg_Is_Local_Name (Arg1);
19606 Type_Id := Get_Pragma_Arg (Arg1);
19607 Find_Type (Type_Id);
19608 Typ := Entity (Type_Id);
19610 if Typ = Any_Type then
19611 return;
19612 end if;
19614 -- A pragma that applies to a Ghost entity becomes Ghost for the
19615 -- purposes of legality checks and removal of ignored Ghost code.
19617 Mark_Ghost_Pragma (N, Typ);
19619 -- The remaining processing is simply to link the pragma on to
19620 -- the rep item chain, for processing when the type is frozen.
19621 -- This is accomplished by a call to Rep_Item_Too_Late. We also
19622 -- mark the type as having predicates.
19624 -- If the current policy for predicate checking is Ignore mark the
19625 -- subtype accordingly. In the case of predicates we consider them
19626 -- enabled unless Ignore is specified (either directly or with a
19627 -- general Assertion_Policy pragma) to preserve existing warnings.
19629 Set_Has_Predicates (Typ);
19630 Set_Predicates_Ignored (Typ,
19631 Present (Check_Policy_List)
19632 and then
19633 Policy_In_Effect (Name_Dynamic_Predicate) = Name_Ignore);
19634 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
19635 end Predicate;
19637 -----------------------
19638 -- Predicate_Failure --
19639 -----------------------
19641 -- pragma Predicate_Failure
19642 -- ([Entity =>] type_LOCAL_NAME,
19643 -- [Message =>] string_EXPRESSION);
19645 when Pragma_Predicate_Failure => Predicate_Failure : declare
19646 Discard : Boolean;
19647 Typ : Entity_Id;
19648 Type_Id : Node_Id;
19650 begin
19651 GNAT_Pragma;
19652 Check_Arg_Count (2);
19653 Check_Optional_Identifier (Arg1, Name_Entity);
19654 Check_Optional_Identifier (Arg2, Name_Message);
19656 Check_Arg_Is_Local_Name (Arg1);
19658 Type_Id := Get_Pragma_Arg (Arg1);
19659 Find_Type (Type_Id);
19660 Typ := Entity (Type_Id);
19662 if Typ = Any_Type then
19663 return;
19664 end if;
19666 -- A pragma that applies to a Ghost entity becomes Ghost for the
19667 -- purposes of legality checks and removal of ignored Ghost code.
19669 Mark_Ghost_Pragma (N, Typ);
19671 -- The remaining processing is simply to link the pragma on to
19672 -- the rep item chain, for processing when the type is frozen.
19673 -- This is accomplished by a call to Rep_Item_Too_Late.
19675 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
19676 end Predicate_Failure;
19678 ------------------
19679 -- Preelaborate --
19680 ------------------
19682 -- pragma Preelaborate [(library_unit_NAME)];
19684 -- Set the flag Is_Preelaborated of program unit name entity
19686 when Pragma_Preelaborate => Preelaborate : declare
19687 Pa : constant Node_Id := Parent (N);
19688 Pk : constant Node_Kind := Nkind (Pa);
19689 Ent : Entity_Id;
19691 begin
19692 Check_Ada_83_Warning;
19693 Check_Valid_Library_Unit_Pragma;
19695 if Nkind (N) = N_Null_Statement then
19696 return;
19697 end if;
19699 Ent := Find_Lib_Unit_Name;
19701 -- A pragma that applies to a Ghost entity becomes Ghost for the
19702 -- purposes of legality checks and removal of ignored Ghost code.
19704 Mark_Ghost_Pragma (N, Ent);
19705 Check_Duplicate_Pragma (Ent);
19707 -- This filters out pragmas inside generic parents that show up
19708 -- inside instantiations. Pragmas that come from aspects in the
19709 -- unit are not ignored.
19711 if Present (Ent) then
19712 if Pk = N_Package_Specification
19713 and then Present (Generic_Parent (Pa))
19714 and then not From_Aspect_Specification (N)
19715 then
19716 null;
19718 else
19719 if not Debug_Flag_U then
19720 Set_Is_Preelaborated (Ent);
19721 Set_Suppress_Elaboration_Warnings (Ent);
19722 end if;
19723 end if;
19724 end if;
19725 end Preelaborate;
19727 -------------------------------
19728 -- Prefix_Exception_Messages --
19729 -------------------------------
19731 -- pragma Prefix_Exception_Messages;
19733 when Pragma_Prefix_Exception_Messages =>
19734 GNAT_Pragma;
19735 Check_Valid_Configuration_Pragma;
19736 Check_Arg_Count (0);
19737 Prefix_Exception_Messages := True;
19739 --------------
19740 -- Priority --
19741 --------------
19743 -- pragma Priority (EXPRESSION);
19745 when Pragma_Priority => Priority : declare
19746 P : constant Node_Id := Parent (N);
19747 Arg : Node_Id;
19748 Ent : Entity_Id;
19750 begin
19751 Check_No_Identifiers;
19752 Check_Arg_Count (1);
19754 -- Subprogram case
19756 if Nkind (P) = N_Subprogram_Body then
19757 Check_In_Main_Program;
19759 Ent := Defining_Unit_Name (Specification (P));
19761 if Nkind (Ent) = N_Defining_Program_Unit_Name then
19762 Ent := Defining_Identifier (Ent);
19763 end if;
19765 Arg := Get_Pragma_Arg (Arg1);
19766 Analyze_And_Resolve (Arg, Standard_Integer);
19768 -- Must be static
19770 if not Is_OK_Static_Expression (Arg) then
19771 Flag_Non_Static_Expr
19772 ("main subprogram priority is not static!", Arg);
19773 raise Pragma_Exit;
19775 -- If constraint error, then we already signalled an error
19777 elsif Raises_Constraint_Error (Arg) then
19778 null;
19780 -- Otherwise check in range except if Relaxed_RM_Semantics
19781 -- where we ignore the value if out of range.
19783 else
19784 if not Relaxed_RM_Semantics
19785 and then not Is_In_Range (Arg, RTE (RE_Priority))
19786 then
19787 Error_Pragma_Arg
19788 ("main subprogram priority is out of range", Arg1);
19789 else
19790 Set_Main_Priority
19791 (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
19792 end if;
19793 end if;
19795 -- Load an arbitrary entity from System.Tasking.Stages or
19796 -- System.Tasking.Restricted.Stages (depending on the
19797 -- supported profile) to make sure that one of these packages
19798 -- is implicitly with'ed, since we need to have the tasking
19799 -- run time active for the pragma Priority to have any effect.
19800 -- Previously we with'ed the package System.Tasking, but this
19801 -- package does not trigger the required initialization of the
19802 -- run-time library.
19804 declare
19805 Discard : Entity_Id;
19806 pragma Warnings (Off, Discard);
19807 begin
19808 if Restricted_Profile then
19809 Discard := RTE (RE_Activate_Restricted_Tasks);
19810 else
19811 Discard := RTE (RE_Activate_Tasks);
19812 end if;
19813 end;
19815 -- Task or Protected, must be of type Integer
19817 elsif Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
19818 Arg := Get_Pragma_Arg (Arg1);
19819 Ent := Defining_Identifier (Parent (P));
19821 -- The expression must be analyzed in the special manner
19822 -- described in "Handling of Default and Per-Object
19823 -- Expressions" in sem.ads.
19825 Preanalyze_Spec_Expression (Arg, RTE (RE_Any_Priority));
19827 if not Is_OK_Static_Expression (Arg) then
19828 Check_Restriction (Static_Priorities, Arg);
19829 end if;
19831 -- Anything else is incorrect
19833 else
19834 Pragma_Misplaced;
19835 end if;
19837 -- Check duplicate pragma before we chain the pragma in the Rep
19838 -- Item chain of Ent.
19840 Check_Duplicate_Pragma (Ent);
19841 Record_Rep_Item (Ent, N);
19842 end Priority;
19844 -----------------------------------
19845 -- Priority_Specific_Dispatching --
19846 -----------------------------------
19848 -- pragma Priority_Specific_Dispatching (
19849 -- policy_IDENTIFIER,
19850 -- first_priority_EXPRESSION,
19851 -- last_priority_EXPRESSION);
19853 when Pragma_Priority_Specific_Dispatching =>
19854 Priority_Specific_Dispatching : declare
19855 Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
19856 -- This is the entity System.Any_Priority;
19858 DP : Character;
19859 Lower_Bound : Node_Id;
19860 Upper_Bound : Node_Id;
19861 Lower_Val : Uint;
19862 Upper_Val : Uint;
19864 begin
19865 Ada_2005_Pragma;
19866 Check_Arg_Count (3);
19867 Check_No_Identifiers;
19868 Check_Arg_Is_Task_Dispatching_Policy (Arg1);
19869 Check_Valid_Configuration_Pragma;
19870 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
19871 DP := Fold_Upper (Name_Buffer (1));
19873 Lower_Bound := Get_Pragma_Arg (Arg2);
19874 Check_Arg_Is_OK_Static_Expression (Lower_Bound, Standard_Integer);
19875 Lower_Val := Expr_Value (Lower_Bound);
19877 Upper_Bound := Get_Pragma_Arg (Arg3);
19878 Check_Arg_Is_OK_Static_Expression (Upper_Bound, Standard_Integer);
19879 Upper_Val := Expr_Value (Upper_Bound);
19881 -- It is not allowed to use Task_Dispatching_Policy and
19882 -- Priority_Specific_Dispatching in the same partition.
19884 if Task_Dispatching_Policy /= ' ' then
19885 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
19886 Error_Pragma
19887 ("pragma% incompatible with Task_Dispatching_Policy#");
19889 -- Check lower bound in range
19891 elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
19892 or else
19893 Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
19894 then
19895 Error_Pragma_Arg
19896 ("first_priority is out of range", Arg2);
19898 -- Check upper bound in range
19900 elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
19901 or else
19902 Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
19903 then
19904 Error_Pragma_Arg
19905 ("last_priority is out of range", Arg3);
19907 -- Check that the priority range is valid
19909 elsif Lower_Val > Upper_Val then
19910 Error_Pragma
19911 ("last_priority_expression must be greater than or equal to "
19912 & "first_priority_expression");
19914 -- Store the new policy, but always preserve System_Location since
19915 -- we like the error message with the run-time name.
19917 else
19918 -- Check overlapping in the priority ranges specified in other
19919 -- Priority_Specific_Dispatching pragmas within the same
19920 -- partition. We can only check those we know about.
19922 for J in
19923 Specific_Dispatching.First .. Specific_Dispatching.Last
19924 loop
19925 if Specific_Dispatching.Table (J).First_Priority in
19926 UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
19927 or else Specific_Dispatching.Table (J).Last_Priority in
19928 UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
19929 then
19930 Error_Msg_Sloc :=
19931 Specific_Dispatching.Table (J).Pragma_Loc;
19932 Error_Pragma
19933 ("priority range overlaps with "
19934 & "Priority_Specific_Dispatching#");
19935 end if;
19936 end loop;
19938 -- The use of Priority_Specific_Dispatching is incompatible
19939 -- with Task_Dispatching_Policy.
19941 if Task_Dispatching_Policy /= ' ' then
19942 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
19943 Error_Pragma
19944 ("Priority_Specific_Dispatching incompatible "
19945 & "with Task_Dispatching_Policy#");
19946 end if;
19948 -- The use of Priority_Specific_Dispatching forces ceiling
19949 -- locking policy.
19951 if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
19952 Error_Msg_Sloc := Locking_Policy_Sloc;
19953 Error_Pragma
19954 ("Priority_Specific_Dispatching incompatible "
19955 & "with Locking_Policy#");
19957 -- Set the Ceiling_Locking policy, but preserve System_Location
19958 -- since we like the error message with the run time name.
19960 else
19961 Locking_Policy := 'C';
19963 if Locking_Policy_Sloc /= System_Location then
19964 Locking_Policy_Sloc := Loc;
19965 end if;
19966 end if;
19968 -- Add entry in the table
19970 Specific_Dispatching.Append
19971 ((Dispatching_Policy => DP,
19972 First_Priority => UI_To_Int (Lower_Val),
19973 Last_Priority => UI_To_Int (Upper_Val),
19974 Pragma_Loc => Loc));
19975 end if;
19976 end Priority_Specific_Dispatching;
19978 -------------
19979 -- Profile --
19980 -------------
19982 -- pragma Profile (profile_IDENTIFIER);
19984 -- profile_IDENTIFIER => Restricted | Ravenscar | Rational
19986 when Pragma_Profile =>
19987 Ada_2005_Pragma;
19988 Check_Arg_Count (1);
19989 Check_Valid_Configuration_Pragma;
19990 Check_No_Identifiers;
19992 declare
19993 Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
19995 begin
19996 if Chars (Argx) = Name_Ravenscar then
19997 Set_Ravenscar_Profile (Ravenscar, N);
19999 elsif Chars (Argx) = Name_Gnat_Extended_Ravenscar then
20000 Set_Ravenscar_Profile (GNAT_Extended_Ravenscar, N);
20002 elsif Chars (Argx) = Name_Gnat_Ravenscar_EDF then
20003 Set_Ravenscar_Profile (GNAT_Ravenscar_EDF, N);
20005 elsif Chars (Argx) = Name_Restricted then
20006 Set_Profile_Restrictions
20007 (Restricted,
20008 N, Warn => Treat_Restrictions_As_Warnings);
20010 elsif Chars (Argx) = Name_Rational then
20011 Set_Rational_Profile;
20013 elsif Chars (Argx) = Name_No_Implementation_Extensions then
20014 Set_Profile_Restrictions
20015 (No_Implementation_Extensions,
20016 N, Warn => Treat_Restrictions_As_Warnings);
20018 else
20019 Error_Pragma_Arg ("& is not a valid profile", Argx);
20020 end if;
20021 end;
20023 ----------------------
20024 -- Profile_Warnings --
20025 ----------------------
20027 -- pragma Profile_Warnings (profile_IDENTIFIER);
20029 -- profile_IDENTIFIER => Restricted | Ravenscar
20031 when Pragma_Profile_Warnings =>
20032 GNAT_Pragma;
20033 Check_Arg_Count (1);
20034 Check_Valid_Configuration_Pragma;
20035 Check_No_Identifiers;
20037 declare
20038 Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
20040 begin
20041 if Chars (Argx) = Name_Ravenscar then
20042 Set_Profile_Restrictions (Ravenscar, N, Warn => True);
20044 elsif Chars (Argx) = Name_Restricted then
20045 Set_Profile_Restrictions (Restricted, N, Warn => True);
20047 elsif Chars (Argx) = Name_No_Implementation_Extensions then
20048 Set_Profile_Restrictions
20049 (No_Implementation_Extensions, N, Warn => True);
20051 else
20052 Error_Pragma_Arg ("& is not a valid profile", Argx);
20053 end if;
20054 end;
20056 --------------------------
20057 -- Propagate_Exceptions --
20058 --------------------------
20060 -- pragma Propagate_Exceptions;
20062 -- Note: this pragma is obsolete and has no effect
20064 when Pragma_Propagate_Exceptions =>
20065 GNAT_Pragma;
20066 Check_Arg_Count (0);
20068 if Warn_On_Obsolescent_Feature then
20069 Error_Msg_N
20070 ("'G'N'A'T pragma Propagate'_Exceptions is now obsolete " &
20071 "and has no effect?j?", N);
20072 end if;
20074 -----------------------------
20075 -- Provide_Shift_Operators --
20076 -----------------------------
20078 -- pragma Provide_Shift_Operators (integer_subtype_LOCAL_NAME);
20080 when Pragma_Provide_Shift_Operators =>
20081 Provide_Shift_Operators : declare
20082 Ent : Entity_Id;
20084 procedure Declare_Shift_Operator (Nam : Name_Id);
20085 -- Insert declaration and pragma Instrinsic for named shift op
20087 ----------------------------
20088 -- Declare_Shift_Operator --
20089 ----------------------------
20091 procedure Declare_Shift_Operator (Nam : Name_Id) is
20092 Func : Node_Id;
20093 Import : Node_Id;
20095 begin
20096 Func :=
20097 Make_Subprogram_Declaration (Loc,
20098 Make_Function_Specification (Loc,
20099 Defining_Unit_Name =>
20100 Make_Defining_Identifier (Loc, Chars => Nam),
20102 Result_Definition =>
20103 Make_Identifier (Loc, Chars => Chars (Ent)),
20105 Parameter_Specifications => New_List (
20106 Make_Parameter_Specification (Loc,
20107 Defining_Identifier =>
20108 Make_Defining_Identifier (Loc, Name_Value),
20109 Parameter_Type =>
20110 Make_Identifier (Loc, Chars => Chars (Ent))),
20112 Make_Parameter_Specification (Loc,
20113 Defining_Identifier =>
20114 Make_Defining_Identifier (Loc, Name_Amount),
20115 Parameter_Type =>
20116 New_Occurrence_Of (Standard_Natural, Loc)))));
20118 Import :=
20119 Make_Pragma (Loc,
20120 Chars => Name_Import,
20121 Pragma_Argument_Associations => New_List (
20122 Make_Pragma_Argument_Association (Loc,
20123 Expression => Make_Identifier (Loc, Name_Intrinsic)),
20124 Make_Pragma_Argument_Association (Loc,
20125 Expression => Make_Identifier (Loc, Nam))));
20127 Insert_After (N, Import);
20128 Insert_After (N, Func);
20129 end Declare_Shift_Operator;
20131 -- Start of processing for Provide_Shift_Operators
20133 begin
20134 GNAT_Pragma;
20135 Check_Arg_Count (1);
20136 Check_Arg_Is_Local_Name (Arg1);
20138 Arg1 := Get_Pragma_Arg (Arg1);
20140 -- We must have an entity name
20142 if not Is_Entity_Name (Arg1) then
20143 Error_Pragma_Arg
20144 ("pragma % must apply to integer first subtype", Arg1);
20145 end if;
20147 -- If no Entity, means there was a prior error so ignore
20149 if Present (Entity (Arg1)) then
20150 Ent := Entity (Arg1);
20152 -- Apply error checks
20154 if not Is_First_Subtype (Ent) then
20155 Error_Pragma_Arg
20156 ("cannot apply pragma %",
20157 "\& is not a first subtype",
20158 Arg1);
20160 elsif not Is_Integer_Type (Ent) then
20161 Error_Pragma_Arg
20162 ("cannot apply pragma %",
20163 "\& is not an integer type",
20164 Arg1);
20166 elsif Has_Shift_Operator (Ent) then
20167 Error_Pragma_Arg
20168 ("cannot apply pragma %",
20169 "\& already has declared shift operators",
20170 Arg1);
20172 elsif Is_Frozen (Ent) then
20173 Error_Pragma_Arg
20174 ("pragma % appears too late",
20175 "\& is already frozen",
20176 Arg1);
20177 end if;
20179 -- Now declare the operators. We do this during analysis rather
20180 -- than expansion, since we want the operators available if we
20181 -- are operating in -gnatc or ASIS mode.
20183 Declare_Shift_Operator (Name_Rotate_Left);
20184 Declare_Shift_Operator (Name_Rotate_Right);
20185 Declare_Shift_Operator (Name_Shift_Left);
20186 Declare_Shift_Operator (Name_Shift_Right);
20187 Declare_Shift_Operator (Name_Shift_Right_Arithmetic);
20188 end if;
20189 end Provide_Shift_Operators;
20191 ------------------
20192 -- Psect_Object --
20193 ------------------
20195 -- pragma Psect_Object (
20196 -- [Internal =>] LOCAL_NAME,
20197 -- [, [External =>] EXTERNAL_SYMBOL]
20198 -- [, [Size =>] EXTERNAL_SYMBOL]);
20200 when Pragma_Common_Object
20201 | Pragma_Psect_Object
20203 Psect_Object : declare
20204 Args : Args_List (1 .. 3);
20205 Names : constant Name_List (1 .. 3) := (
20206 Name_Internal,
20207 Name_External,
20208 Name_Size);
20210 Internal : Node_Id renames Args (1);
20211 External : Node_Id renames Args (2);
20212 Size : Node_Id renames Args (3);
20214 Def_Id : Entity_Id;
20216 procedure Check_Arg (Arg : Node_Id);
20217 -- Checks that argument is either a string literal or an
20218 -- identifier, and posts error message if not.
20220 ---------------
20221 -- Check_Arg --
20222 ---------------
20224 procedure Check_Arg (Arg : Node_Id) is
20225 begin
20226 if not Nkind_In (Original_Node (Arg),
20227 N_String_Literal,
20228 N_Identifier)
20229 then
20230 Error_Pragma_Arg
20231 ("inappropriate argument for pragma %", Arg);
20232 end if;
20233 end Check_Arg;
20235 -- Start of processing for Common_Object/Psect_Object
20237 begin
20238 GNAT_Pragma;
20239 Gather_Associations (Names, Args);
20240 Process_Extended_Import_Export_Internal_Arg (Internal);
20242 Def_Id := Entity (Internal);
20244 if not Ekind_In (Def_Id, E_Constant, E_Variable) then
20245 Error_Pragma_Arg
20246 ("pragma% must designate an object", Internal);
20247 end if;
20249 Check_Arg (Internal);
20251 if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
20252 Error_Pragma_Arg
20253 ("cannot use pragma% for imported/exported object",
20254 Internal);
20255 end if;
20257 if Is_Concurrent_Type (Etype (Internal)) then
20258 Error_Pragma_Arg
20259 ("cannot specify pragma % for task/protected object",
20260 Internal);
20261 end if;
20263 if Has_Rep_Pragma (Def_Id, Name_Common_Object)
20264 or else
20265 Has_Rep_Pragma (Def_Id, Name_Psect_Object)
20266 then
20267 Error_Msg_N ("??duplicate Common/Psect_Object pragma", N);
20268 end if;
20270 if Ekind (Def_Id) = E_Constant then
20271 Error_Pragma_Arg
20272 ("cannot specify pragma % for a constant", Internal);
20273 end if;
20275 if Is_Record_Type (Etype (Internal)) then
20276 declare
20277 Ent : Entity_Id;
20278 Decl : Entity_Id;
20280 begin
20281 Ent := First_Entity (Etype (Internal));
20282 while Present (Ent) loop
20283 Decl := Declaration_Node (Ent);
20285 if Ekind (Ent) = E_Component
20286 and then Nkind (Decl) = N_Component_Declaration
20287 and then Present (Expression (Decl))
20288 and then Warn_On_Export_Import
20289 then
20290 Error_Msg_N
20291 ("?x?object for pragma % has defaults", Internal);
20292 exit;
20294 else
20295 Next_Entity (Ent);
20296 end if;
20297 end loop;
20298 end;
20299 end if;
20301 if Present (Size) then
20302 Check_Arg (Size);
20303 end if;
20305 if Present (External) then
20306 Check_Arg_Is_External_Name (External);
20307 end if;
20309 -- If all error tests pass, link pragma on to the rep item chain
20311 Record_Rep_Item (Def_Id, N);
20312 end Psect_Object;
20314 ----------
20315 -- Pure --
20316 ----------
20318 -- pragma Pure [(library_unit_NAME)];
20320 when Pragma_Pure => Pure : declare
20321 Ent : Entity_Id;
20323 begin
20324 Check_Ada_83_Warning;
20326 -- If the pragma comes from a subprogram instantiation, nothing to
20327 -- check, this can happen at any level of nesting.
20329 if Is_Wrapper_Package (Current_Scope) then
20330 return;
20331 else
20332 Check_Valid_Library_Unit_Pragma;
20333 end if;
20335 if Nkind (N) = N_Null_Statement then
20336 return;
20337 end if;
20339 Ent := Find_Lib_Unit_Name;
20341 -- A pragma that applies to a Ghost entity becomes Ghost for the
20342 -- purposes of legality checks and removal of ignored Ghost code.
20344 Mark_Ghost_Pragma (N, Ent);
20346 if not Debug_Flag_U then
20347 Set_Is_Pure (Ent);
20348 Set_Has_Pragma_Pure (Ent);
20349 Set_Suppress_Elaboration_Warnings (Ent);
20350 end if;
20351 end Pure;
20353 -------------------
20354 -- Pure_Function --
20355 -------------------
20357 -- pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
20359 when Pragma_Pure_Function => Pure_Function : declare
20360 Def_Id : Entity_Id;
20361 E : Entity_Id;
20362 E_Id : Node_Id;
20363 Effective : Boolean := False;
20365 begin
20366 GNAT_Pragma;
20367 Check_Arg_Count (1);
20368 Check_Optional_Identifier (Arg1, Name_Entity);
20369 Check_Arg_Is_Local_Name (Arg1);
20370 E_Id := Get_Pragma_Arg (Arg1);
20372 if Error_Posted (E_Id) then
20373 return;
20374 end if;
20376 -- Loop through homonyms (overloadings) of referenced entity
20378 E := Entity (E_Id);
20380 -- A pragma that applies to a Ghost entity becomes Ghost for the
20381 -- purposes of legality checks and removal of ignored Ghost code.
20383 Mark_Ghost_Pragma (N, E);
20385 if Present (E) then
20386 loop
20387 Def_Id := Get_Base_Subprogram (E);
20389 if not Ekind_In (Def_Id, E_Function,
20390 E_Generic_Function,
20391 E_Operator)
20392 then
20393 Error_Pragma_Arg
20394 ("pragma% requires a function name", Arg1);
20395 end if;
20397 Set_Is_Pure (Def_Id);
20399 if not Has_Pragma_Pure_Function (Def_Id) then
20400 Set_Has_Pragma_Pure_Function (Def_Id);
20401 Effective := True;
20402 end if;
20404 exit when From_Aspect_Specification (N);
20405 E := Homonym (E);
20406 exit when No (E) or else Scope (E) /= Current_Scope;
20407 end loop;
20409 if not Effective
20410 and then Warn_On_Redundant_Constructs
20411 then
20412 Error_Msg_NE
20413 ("pragma Pure_Function on& is redundant?r?",
20414 N, Entity (E_Id));
20415 end if;
20416 end if;
20417 end Pure_Function;
20419 --------------------
20420 -- Queuing_Policy --
20421 --------------------
20423 -- pragma Queuing_Policy (policy_IDENTIFIER);
20425 when Pragma_Queuing_Policy => declare
20426 QP : Character;
20428 begin
20429 Check_Ada_83_Warning;
20430 Check_Arg_Count (1);
20431 Check_No_Identifiers;
20432 Check_Arg_Is_Queuing_Policy (Arg1);
20433 Check_Valid_Configuration_Pragma;
20434 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
20435 QP := Fold_Upper (Name_Buffer (1));
20437 if Queuing_Policy /= ' '
20438 and then Queuing_Policy /= QP
20439 then
20440 Error_Msg_Sloc := Queuing_Policy_Sloc;
20441 Error_Pragma ("queuing policy incompatible with policy#");
20443 -- Set new policy, but always preserve System_Location since we
20444 -- like the error message with the run time name.
20446 else
20447 Queuing_Policy := QP;
20449 if Queuing_Policy_Sloc /= System_Location then
20450 Queuing_Policy_Sloc := Loc;
20451 end if;
20452 end if;
20453 end;
20455 --------------
20456 -- Rational --
20457 --------------
20459 -- pragma Rational, for compatibility with foreign compiler
20461 when Pragma_Rational =>
20462 Set_Rational_Profile;
20464 ---------------------
20465 -- Refined_Depends --
20466 ---------------------
20468 -- pragma Refined_Depends (DEPENDENCY_RELATION);
20470 -- DEPENDENCY_RELATION ::=
20471 -- null
20472 -- | (DEPENDENCY_CLAUSE {, DEPENDENCY_CLAUSE})
20474 -- DEPENDENCY_CLAUSE ::=
20475 -- OUTPUT_LIST =>[+] INPUT_LIST
20476 -- | NULL_DEPENDENCY_CLAUSE
20478 -- NULL_DEPENDENCY_CLAUSE ::= null => INPUT_LIST
20480 -- OUTPUT_LIST ::= OUTPUT | (OUTPUT {, OUTPUT})
20482 -- INPUT_LIST ::= null | INPUT | (INPUT {, INPUT})
20484 -- OUTPUT ::= NAME | FUNCTION_RESULT
20485 -- INPUT ::= NAME
20487 -- where FUNCTION_RESULT is a function Result attribute_reference
20489 -- Characteristics:
20491 -- * Analysis - The annotation undergoes initial checks to verify
20492 -- the legal placement and context. Secondary checks fully analyze
20493 -- the dependency clauses/global list in:
20495 -- Analyze_Refined_Depends_In_Decl_Part
20497 -- * Expansion - None.
20499 -- * Template - The annotation utilizes the generic template of the
20500 -- related subprogram body.
20502 -- * Globals - Capture of global references must occur after full
20503 -- analysis.
20505 -- * Instance - The annotation is instantiated automatically when
20506 -- the related generic subprogram body is instantiated.
20508 when Pragma_Refined_Depends => Refined_Depends : declare
20509 Body_Id : Entity_Id;
20510 Legal : Boolean;
20511 Spec_Id : Entity_Id;
20513 begin
20514 Analyze_Refined_Depends_Global_Post (Spec_Id, Body_Id, Legal);
20516 if Legal then
20518 -- Chain the pragma on the contract for further processing by
20519 -- Analyze_Refined_Depends_In_Decl_Part.
20521 Add_Contract_Item (N, Body_Id);
20523 -- The legality checks of pragmas Refined_Depends and
20524 -- Refined_Global are affected by the SPARK mode in effect and
20525 -- the volatility of the context. In addition these two pragmas
20526 -- are subject to an inherent order:
20528 -- 1) Refined_Global
20529 -- 2) Refined_Depends
20531 -- Analyze all these pragmas in the order outlined above
20533 Analyze_If_Present (Pragma_SPARK_Mode);
20534 Analyze_If_Present (Pragma_Volatile_Function);
20535 Analyze_If_Present (Pragma_Refined_Global);
20536 Analyze_Refined_Depends_In_Decl_Part (N);
20537 end if;
20538 end Refined_Depends;
20540 --------------------
20541 -- Refined_Global --
20542 --------------------
20544 -- pragma Refined_Global (GLOBAL_SPECIFICATION);
20546 -- GLOBAL_SPECIFICATION ::=
20547 -- null
20548 -- | (GLOBAL_LIST)
20549 -- | (MODED_GLOBAL_LIST {, MODED_GLOBAL_LIST})
20551 -- MODED_GLOBAL_LIST ::= MODE_SELECTOR => GLOBAL_LIST
20553 -- MODE_SELECTOR ::= In_Out | Input | Output | Proof_In
20554 -- GLOBAL_LIST ::= GLOBAL_ITEM | (GLOBAL_ITEM {, GLOBAL_ITEM})
20555 -- GLOBAL_ITEM ::= NAME
20557 -- Characteristics:
20559 -- * Analysis - The annotation undergoes initial checks to verify
20560 -- the legal placement and context. Secondary checks fully analyze
20561 -- the dependency clauses/global list in:
20563 -- Analyze_Refined_Global_In_Decl_Part
20565 -- * Expansion - None.
20567 -- * Template - The annotation utilizes the generic template of the
20568 -- related subprogram body.
20570 -- * Globals - Capture of global references must occur after full
20571 -- analysis.
20573 -- * Instance - The annotation is instantiated automatically when
20574 -- the related generic subprogram body is instantiated.
20576 when Pragma_Refined_Global => Refined_Global : declare
20577 Body_Id : Entity_Id;
20578 Legal : Boolean;
20579 Spec_Id : Entity_Id;
20581 begin
20582 Analyze_Refined_Depends_Global_Post (Spec_Id, Body_Id, Legal);
20584 if Legal then
20586 -- Chain the pragma on the contract for further processing by
20587 -- Analyze_Refined_Global_In_Decl_Part.
20589 Add_Contract_Item (N, Body_Id);
20591 -- The legality checks of pragmas Refined_Depends and
20592 -- Refined_Global are affected by the SPARK mode in effect and
20593 -- the volatility of the context. In addition these two pragmas
20594 -- are subject to an inherent order:
20596 -- 1) Refined_Global
20597 -- 2) Refined_Depends
20599 -- Analyze all these pragmas in the order outlined above
20601 Analyze_If_Present (Pragma_SPARK_Mode);
20602 Analyze_If_Present (Pragma_Volatile_Function);
20603 Analyze_Refined_Global_In_Decl_Part (N);
20604 Analyze_If_Present (Pragma_Refined_Depends);
20605 end if;
20606 end Refined_Global;
20608 ------------------
20609 -- Refined_Post --
20610 ------------------
20612 -- pragma Refined_Post (boolean_EXPRESSION);
20614 -- Characteristics:
20616 -- * Analysis - The annotation is fully analyzed immediately upon
20617 -- elaboration as it cannot forward reference entities.
20619 -- * Expansion - The annotation is expanded during the expansion of
20620 -- the related subprogram body contract as performed in:
20622 -- Expand_Subprogram_Contract
20624 -- * Template - The annotation utilizes the generic template of the
20625 -- related subprogram body.
20627 -- * Globals - Capture of global references must occur after full
20628 -- analysis.
20630 -- * Instance - The annotation is instantiated automatically when
20631 -- the related generic subprogram body is instantiated.
20633 when Pragma_Refined_Post => Refined_Post : declare
20634 Body_Id : Entity_Id;
20635 Legal : Boolean;
20636 Spec_Id : Entity_Id;
20638 begin
20639 Analyze_Refined_Depends_Global_Post (Spec_Id, Body_Id, Legal);
20641 -- Fully analyze the pragma when it appears inside a subprogram
20642 -- body because it cannot benefit from forward references.
20644 if Legal then
20646 -- Chain the pragma on the contract for completeness
20648 Add_Contract_Item (N, Body_Id);
20650 -- The legality checks of pragma Refined_Post are affected by
20651 -- the SPARK mode in effect and the volatility of the context.
20652 -- Analyze all pragmas in a specific order.
20654 Analyze_If_Present (Pragma_SPARK_Mode);
20655 Analyze_If_Present (Pragma_Volatile_Function);
20656 Analyze_Pre_Post_Condition_In_Decl_Part (N);
20658 -- Currently it is not possible to inline pre/postconditions on
20659 -- a subprogram subject to pragma Inline_Always.
20661 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
20662 end if;
20663 end Refined_Post;
20665 -------------------
20666 -- Refined_State --
20667 -------------------
20669 -- pragma Refined_State (REFINEMENT_LIST);
20671 -- REFINEMENT_LIST ::=
20672 -- (REFINEMENT_CLAUSE {, REFINEMENT_CLAUSE})
20674 -- REFINEMENT_CLAUSE ::= state_NAME => CONSTITUENT_LIST
20676 -- CONSTITUENT_LIST ::=
20677 -- null
20678 -- | CONSTITUENT
20679 -- | (CONSTITUENT {, CONSTITUENT})
20681 -- CONSTITUENT ::= object_NAME | state_NAME
20683 -- Characteristics:
20685 -- * Analysis - The annotation undergoes initial checks to verify
20686 -- the legal placement and context. Secondary checks preanalyze the
20687 -- refinement clauses in:
20689 -- Analyze_Refined_State_In_Decl_Part
20691 -- * Expansion - None.
20693 -- * Template - The annotation utilizes the template of the related
20694 -- package body.
20696 -- * Globals - Capture of global references must occur after full
20697 -- analysis.
20699 -- * Instance - The annotation is instantiated automatically when
20700 -- the related generic package body is instantiated.
20702 when Pragma_Refined_State => Refined_State : declare
20703 Pack_Decl : Node_Id;
20704 Spec_Id : Entity_Id;
20706 begin
20707 GNAT_Pragma;
20708 Check_No_Identifiers;
20709 Check_Arg_Count (1);
20711 Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
20713 -- Ensure the proper placement of the pragma. Refined states must
20714 -- be associated with a package body.
20716 if Nkind (Pack_Decl) = N_Package_Body then
20717 null;
20719 -- Otherwise the pragma is associated with an illegal construct
20721 else
20722 Pragma_Misplaced;
20723 return;
20724 end if;
20726 Spec_Id := Corresponding_Spec (Pack_Decl);
20728 -- A pragma that applies to a Ghost entity becomes Ghost for the
20729 -- purposes of legality checks and removal of ignored Ghost code.
20731 Mark_Ghost_Pragma (N, Spec_Id);
20733 -- Chain the pragma on the contract for further processing by
20734 -- Analyze_Refined_State_In_Decl_Part.
20736 Add_Contract_Item (N, Defining_Entity (Pack_Decl));
20738 -- The legality checks of pragma Refined_State are affected by the
20739 -- SPARK mode in effect. Analyze all pragmas in a specific order.
20741 Analyze_If_Present (Pragma_SPARK_Mode);
20743 -- State refinement is allowed only when the corresponding package
20744 -- declaration has non-null pragma Abstract_State. Refinement not
20745 -- enforced when SPARK checks are suppressed (SPARK RM 7.2.2(3)).
20747 if SPARK_Mode /= Off
20748 and then
20749 (No (Abstract_States (Spec_Id))
20750 or else Has_Null_Abstract_State (Spec_Id))
20751 then
20752 Error_Msg_NE
20753 ("useless refinement, package & does not define abstract "
20754 & "states", N, Spec_Id);
20755 return;
20756 end if;
20757 end Refined_State;
20759 -----------------------
20760 -- Relative_Deadline --
20761 -----------------------
20763 -- pragma Relative_Deadline (time_span_EXPRESSION);
20765 when Pragma_Relative_Deadline => Relative_Deadline : declare
20766 P : constant Node_Id := Parent (N);
20767 Arg : Node_Id;
20769 begin
20770 Ada_2005_Pragma;
20771 Check_No_Identifiers;
20772 Check_Arg_Count (1);
20774 Arg := Get_Pragma_Arg (Arg1);
20776 -- The expression must be analyzed in the special manner described
20777 -- in "Handling of Default and Per-Object Expressions" in sem.ads.
20779 Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
20781 -- Subprogram case
20783 if Nkind (P) = N_Subprogram_Body then
20784 Check_In_Main_Program;
20786 -- Only Task and subprogram cases allowed
20788 elsif Nkind (P) /= N_Task_Definition then
20789 Pragma_Misplaced;
20790 end if;
20792 -- Check duplicate pragma before we set the corresponding flag
20794 if Has_Relative_Deadline_Pragma (P) then
20795 Error_Pragma ("duplicate pragma% not allowed");
20796 end if;
20798 -- Set Has_Relative_Deadline_Pragma only for tasks. Note that
20799 -- Relative_Deadline pragma node cannot be inserted in the Rep
20800 -- Item chain of Ent since it is rewritten by the expander as a
20801 -- procedure call statement that will break the chain.
20803 Set_Has_Relative_Deadline_Pragma (P);
20804 end Relative_Deadline;
20806 ------------------------
20807 -- Remote_Access_Type --
20808 ------------------------
20810 -- pragma Remote_Access_Type ([Entity =>] formal_type_LOCAL_NAME);
20812 when Pragma_Remote_Access_Type => Remote_Access_Type : declare
20813 E : Entity_Id;
20815 begin
20816 GNAT_Pragma;
20817 Check_Arg_Count (1);
20818 Check_Optional_Identifier (Arg1, Name_Entity);
20819 Check_Arg_Is_Local_Name (Arg1);
20821 E := Entity (Get_Pragma_Arg (Arg1));
20823 -- A pragma that applies to a Ghost entity becomes Ghost for the
20824 -- purposes of legality checks and removal of ignored Ghost code.
20826 Mark_Ghost_Pragma (N, E);
20828 if Nkind (Parent (E)) = N_Formal_Type_Declaration
20829 and then Ekind (E) = E_General_Access_Type
20830 and then Is_Class_Wide_Type (Directly_Designated_Type (E))
20831 and then Scope (Root_Type (Directly_Designated_Type (E)))
20832 = Scope (E)
20833 and then Is_Valid_Remote_Object_Type
20834 (Root_Type (Directly_Designated_Type (E)))
20835 then
20836 Set_Is_Remote_Types (E);
20838 else
20839 Error_Pragma_Arg
20840 ("pragma% applies only to formal access-to-class-wide types",
20841 Arg1);
20842 end if;
20843 end Remote_Access_Type;
20845 ---------------------------
20846 -- Remote_Call_Interface --
20847 ---------------------------
20849 -- pragma Remote_Call_Interface [(library_unit_NAME)];
20851 when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
20852 Cunit_Node : Node_Id;
20853 Cunit_Ent : Entity_Id;
20854 K : Node_Kind;
20856 begin
20857 Check_Ada_83_Warning;
20858 Check_Valid_Library_Unit_Pragma;
20860 if Nkind (N) = N_Null_Statement then
20861 return;
20862 end if;
20864 Cunit_Node := Cunit (Current_Sem_Unit);
20865 K := Nkind (Unit (Cunit_Node));
20866 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
20868 -- A pragma that applies to a Ghost entity becomes Ghost for the
20869 -- purposes of legality checks and removal of ignored Ghost code.
20871 Mark_Ghost_Pragma (N, Cunit_Ent);
20873 if K = N_Package_Declaration
20874 or else K = N_Generic_Package_Declaration
20875 or else K = N_Subprogram_Declaration
20876 or else K = N_Generic_Subprogram_Declaration
20877 or else (K = N_Subprogram_Body
20878 and then Acts_As_Spec (Unit (Cunit_Node)))
20879 then
20880 null;
20881 else
20882 Error_Pragma (
20883 "pragma% must apply to package or subprogram declaration");
20884 end if;
20886 Set_Is_Remote_Call_Interface (Cunit_Ent);
20887 end Remote_Call_Interface;
20889 ------------------
20890 -- Remote_Types --
20891 ------------------
20893 -- pragma Remote_Types [(library_unit_NAME)];
20895 when Pragma_Remote_Types => Remote_Types : declare
20896 Cunit_Node : Node_Id;
20897 Cunit_Ent : Entity_Id;
20899 begin
20900 Check_Ada_83_Warning;
20901 Check_Valid_Library_Unit_Pragma;
20903 if Nkind (N) = N_Null_Statement then
20904 return;
20905 end if;
20907 Cunit_Node := Cunit (Current_Sem_Unit);
20908 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
20910 -- A pragma that applies to a Ghost entity becomes Ghost for the
20911 -- purposes of legality checks and removal of ignored Ghost code.
20913 Mark_Ghost_Pragma (N, Cunit_Ent);
20915 if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
20916 N_Generic_Package_Declaration)
20917 then
20918 Error_Pragma
20919 ("pragma% can only apply to a package declaration");
20920 end if;
20922 Set_Is_Remote_Types (Cunit_Ent);
20923 end Remote_Types;
20925 ---------------
20926 -- Ravenscar --
20927 ---------------
20929 -- pragma Ravenscar;
20931 when Pragma_Ravenscar =>
20932 GNAT_Pragma;
20933 Check_Arg_Count (0);
20934 Check_Valid_Configuration_Pragma;
20935 Set_Ravenscar_Profile (Ravenscar, N);
20937 if Warn_On_Obsolescent_Feature then
20938 Error_Msg_N
20939 ("pragma Ravenscar is an obsolescent feature?j?", N);
20940 Error_Msg_N
20941 ("|use pragma Profile (Ravenscar) instead?j?", N);
20942 end if;
20944 -------------------------
20945 -- Restricted_Run_Time --
20946 -------------------------
20948 -- pragma Restricted_Run_Time;
20950 when Pragma_Restricted_Run_Time =>
20951 GNAT_Pragma;
20952 Check_Arg_Count (0);
20953 Check_Valid_Configuration_Pragma;
20954 Set_Profile_Restrictions
20955 (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
20957 if Warn_On_Obsolescent_Feature then
20958 Error_Msg_N
20959 ("pragma Restricted_Run_Time is an obsolescent feature?j?",
20961 Error_Msg_N
20962 ("|use pragma Profile (Restricted) instead?j?", N);
20963 end if;
20965 ------------------
20966 -- Restrictions --
20967 ------------------
20969 -- pragma Restrictions (RESTRICTION {, RESTRICTION});
20971 -- RESTRICTION ::=
20972 -- restriction_IDENTIFIER
20973 -- | restriction_parameter_IDENTIFIER => EXPRESSION
20975 when Pragma_Restrictions =>
20976 Process_Restrictions_Or_Restriction_Warnings
20977 (Warn => Treat_Restrictions_As_Warnings);
20979 --------------------------
20980 -- Restriction_Warnings --
20981 --------------------------
20983 -- pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
20985 -- RESTRICTION ::=
20986 -- restriction_IDENTIFIER
20987 -- | restriction_parameter_IDENTIFIER => EXPRESSION
20989 when Pragma_Restriction_Warnings =>
20990 GNAT_Pragma;
20991 Process_Restrictions_Or_Restriction_Warnings (Warn => True);
20993 ----------------
20994 -- Reviewable --
20995 ----------------
20997 -- pragma Reviewable;
20999 when Pragma_Reviewable =>
21000 Check_Ada_83_Warning;
21001 Check_Arg_Count (0);
21003 -- Call dummy debugging function rv. This is done to assist front
21004 -- end debugging. By placing a Reviewable pragma in the source
21005 -- program, a breakpoint on rv catches this place in the source,
21006 -- allowing convenient stepping to the point of interest.
21010 --------------------------
21011 -- Secondary_Stack_Size --
21012 --------------------------
21014 -- pragma Secondary_Stack_Size (EXPRESSION);
21016 when Pragma_Secondary_Stack_Size => Secondary_Stack_Size : declare
21017 P : constant Node_Id := Parent (N);
21018 Arg : Node_Id;
21019 Ent : Entity_Id;
21021 begin
21022 GNAT_Pragma;
21023 Check_No_Identifiers;
21024 Check_Arg_Count (1);
21026 if Nkind (P) = N_Task_Definition then
21027 Arg := Get_Pragma_Arg (Arg1);
21028 Ent := Defining_Identifier (Parent (P));
21030 -- The expression must be analyzed in the special manner
21031 -- described in "Handling of Default Expressions" in sem.ads.
21033 Preanalyze_Spec_Expression (Arg, Any_Integer);
21035 -- The pragma cannot appear if the No_Secondary_Stack
21036 -- restriction is in effect.
21038 Check_Restriction (No_Secondary_Stack, Arg);
21040 -- Anything else is incorrect
21042 else
21043 Pragma_Misplaced;
21044 end if;
21046 -- Check duplicate pragma before we chain the pragma in the Rep
21047 -- Item chain of Ent.
21049 Check_Duplicate_Pragma (Ent);
21050 Record_Rep_Item (Ent, N);
21051 end Secondary_Stack_Size;
21053 --------------------------
21054 -- Short_Circuit_And_Or --
21055 --------------------------
21057 -- pragma Short_Circuit_And_Or;
21059 when Pragma_Short_Circuit_And_Or =>
21060 GNAT_Pragma;
21061 Check_Arg_Count (0);
21062 Check_Valid_Configuration_Pragma;
21063 Short_Circuit_And_Or := True;
21065 -------------------
21066 -- Share_Generic --
21067 -------------------
21069 -- pragma Share_Generic (GNAME {, GNAME});
21071 -- GNAME ::= generic_unit_NAME | generic_instance_NAME
21073 when Pragma_Share_Generic =>
21074 GNAT_Pragma;
21075 Process_Generic_List;
21077 ------------
21078 -- Shared --
21079 ------------
21081 -- pragma Shared (LOCAL_NAME);
21083 when Pragma_Shared =>
21084 GNAT_Pragma;
21085 Process_Atomic_Independent_Shared_Volatile;
21087 --------------------
21088 -- Shared_Passive --
21089 --------------------
21091 -- pragma Shared_Passive [(library_unit_NAME)];
21093 -- Set the flag Is_Shared_Passive of program unit name entity
21095 when Pragma_Shared_Passive => Shared_Passive : declare
21096 Cunit_Node : Node_Id;
21097 Cunit_Ent : Entity_Id;
21099 begin
21100 Check_Ada_83_Warning;
21101 Check_Valid_Library_Unit_Pragma;
21103 if Nkind (N) = N_Null_Statement then
21104 return;
21105 end if;
21107 Cunit_Node := Cunit (Current_Sem_Unit);
21108 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
21110 -- A pragma that applies to a Ghost entity becomes Ghost for the
21111 -- purposes of legality checks and removal of ignored Ghost code.
21113 Mark_Ghost_Pragma (N, Cunit_Ent);
21115 if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
21116 N_Generic_Package_Declaration)
21117 then
21118 Error_Pragma
21119 ("pragma% can only apply to a package declaration");
21120 end if;
21122 Set_Is_Shared_Passive (Cunit_Ent);
21123 end Shared_Passive;
21125 -----------------------
21126 -- Short_Descriptors --
21127 -----------------------
21129 -- pragma Short_Descriptors;
21131 -- Recognize and validate, but otherwise ignore
21133 when Pragma_Short_Descriptors =>
21134 GNAT_Pragma;
21135 Check_Arg_Count (0);
21136 Check_Valid_Configuration_Pragma;
21138 ------------------------------
21139 -- Simple_Storage_Pool_Type --
21140 ------------------------------
21142 -- pragma Simple_Storage_Pool_Type (type_LOCAL_NAME);
21144 when Pragma_Simple_Storage_Pool_Type =>
21145 Simple_Storage_Pool_Type : declare
21146 Typ : Entity_Id;
21147 Type_Id : Node_Id;
21149 begin
21150 GNAT_Pragma;
21151 Check_Arg_Count (1);
21152 Check_Arg_Is_Library_Level_Local_Name (Arg1);
21154 Type_Id := Get_Pragma_Arg (Arg1);
21155 Find_Type (Type_Id);
21156 Typ := Entity (Type_Id);
21158 if Typ = Any_Type then
21159 return;
21160 end if;
21162 -- A pragma that applies to a Ghost entity becomes Ghost for the
21163 -- purposes of legality checks and removal of ignored Ghost code.
21165 Mark_Ghost_Pragma (N, Typ);
21167 -- We require the pragma to apply to a type declared in a package
21168 -- declaration, but not (immediately) within a package body.
21170 if Ekind (Current_Scope) /= E_Package
21171 or else In_Package_Body (Current_Scope)
21172 then
21173 Error_Pragma
21174 ("pragma% can only apply to type declared immediately "
21175 & "within a package declaration");
21176 end if;
21178 -- A simple storage pool type must be an immutably limited record
21179 -- or private type. If the pragma is given for a private type,
21180 -- the full type is similarly restricted (which is checked later
21181 -- in Freeze_Entity).
21183 if Is_Record_Type (Typ)
21184 and then not Is_Limited_View (Typ)
21185 then
21186 Error_Pragma
21187 ("pragma% can only apply to explicitly limited record type");
21189 elsif Is_Private_Type (Typ) and then not Is_Limited_Type (Typ) then
21190 Error_Pragma
21191 ("pragma% can only apply to a private type that is limited");
21193 elsif not Is_Record_Type (Typ)
21194 and then not Is_Private_Type (Typ)
21195 then
21196 Error_Pragma
21197 ("pragma% can only apply to limited record or private type");
21198 end if;
21200 Record_Rep_Item (Typ, N);
21201 end Simple_Storage_Pool_Type;
21203 ----------------------
21204 -- Source_File_Name --
21205 ----------------------
21207 -- There are five forms for this pragma:
21209 -- pragma Source_File_Name (
21210 -- [UNIT_NAME =>] unit_NAME,
21211 -- BODY_FILE_NAME => STRING_LITERAL
21212 -- [, [INDEX =>] INTEGER_LITERAL]);
21214 -- pragma Source_File_Name (
21215 -- [UNIT_NAME =>] unit_NAME,
21216 -- SPEC_FILE_NAME => STRING_LITERAL
21217 -- [, [INDEX =>] INTEGER_LITERAL]);
21219 -- pragma Source_File_Name (
21220 -- BODY_FILE_NAME => STRING_LITERAL
21221 -- [, DOT_REPLACEMENT => STRING_LITERAL]
21222 -- [, CASING => CASING_SPEC]);
21224 -- pragma Source_File_Name (
21225 -- SPEC_FILE_NAME => STRING_LITERAL
21226 -- [, DOT_REPLACEMENT => STRING_LITERAL]
21227 -- [, CASING => CASING_SPEC]);
21229 -- pragma Source_File_Name (
21230 -- SUBUNIT_FILE_NAME => STRING_LITERAL
21231 -- [, DOT_REPLACEMENT => STRING_LITERAL]
21232 -- [, CASING => CASING_SPEC]);
21234 -- CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
21236 -- Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
21237 -- Source_File_Name (SFN), however their usage is exclusive: SFN can
21238 -- only be used when no project file is used, while SFNP can only be
21239 -- used when a project file is used.
21241 -- No processing here. Processing was completed during parsing, since
21242 -- we need to have file names set as early as possible. Units are
21243 -- loaded well before semantic processing starts.
21245 -- The only processing we defer to this point is the check for
21246 -- correct placement.
21248 when Pragma_Source_File_Name =>
21249 GNAT_Pragma;
21250 Check_Valid_Configuration_Pragma;
21252 ------------------------------
21253 -- Source_File_Name_Project --
21254 ------------------------------
21256 -- See Source_File_Name for syntax
21258 -- No processing here. Processing was completed during parsing, since
21259 -- we need to have file names set as early as possible. Units are
21260 -- loaded well before semantic processing starts.
21262 -- The only processing we defer to this point is the check for
21263 -- correct placement.
21265 when Pragma_Source_File_Name_Project =>
21266 GNAT_Pragma;
21267 Check_Valid_Configuration_Pragma;
21269 -- Check that a pragma Source_File_Name_Project is used only in a
21270 -- configuration pragmas file.
21272 -- Pragmas Source_File_Name_Project should only be generated by
21273 -- the Project Manager in configuration pragmas files.
21275 -- This is really an ugly test. It seems to depend on some
21276 -- accidental and undocumented property. At the very least it
21277 -- needs to be documented, but it would be better to have a
21278 -- clean way of testing if we are in a configuration file???
21280 if Present (Parent (N)) then
21281 Error_Pragma
21282 ("pragma% can only appear in a configuration pragmas file");
21283 end if;
21285 ----------------------
21286 -- Source_Reference --
21287 ----------------------
21289 -- pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
21291 -- Nothing to do, all processing completed in Par.Prag, since we need
21292 -- the information for possible parser messages that are output.
21294 when Pragma_Source_Reference =>
21295 GNAT_Pragma;
21297 ----------------
21298 -- SPARK_Mode --
21299 ----------------
21301 -- pragma SPARK_Mode [(On | Off)];
21303 when Pragma_SPARK_Mode => Do_SPARK_Mode : declare
21304 Mode_Id : SPARK_Mode_Type;
21306 procedure Check_Pragma_Conformance
21307 (Context_Pragma : Node_Id;
21308 Entity : Entity_Id;
21309 Entity_Pragma : Node_Id);
21310 -- Subsidiary to routines Process_xxx. Verify the SPARK_Mode
21311 -- conformance of pragma N depending the following scenarios:
21313 -- If pragma Context_Pragma is not Empty, verify that pragma N is
21314 -- compatible with the pragma Context_Pragma that was inherited
21315 -- from the context:
21316 -- * If the mode of Context_Pragma is ON, then the new mode can
21317 -- be anything.
21318 -- * If the mode of Context_Pragma is OFF, then the only allowed
21319 -- new mode is also OFF. Emit error if this is not the case.
21321 -- If Entity is not Empty, verify that pragma N is compatible with
21322 -- pragma Entity_Pragma that belongs to Entity.
21323 -- * If Entity_Pragma is Empty, always issue an error as this
21324 -- corresponds to the case where a previous section of Entity
21325 -- has no SPARK_Mode set.
21326 -- * If the mode of Entity_Pragma is ON, then the new mode can
21327 -- be anything.
21328 -- * If the mode of Entity_Pragma is OFF, then the only allowed
21329 -- new mode is also OFF. Emit error if this is not the case.
21331 procedure Check_Library_Level_Entity (E : Entity_Id);
21332 -- Subsidiary to routines Process_xxx. Verify that the related
21333 -- entity E subject to pragma SPARK_Mode is library-level.
21335 procedure Process_Body (Decl : Node_Id);
21336 -- Verify the legality of pragma SPARK_Mode when it appears as the
21337 -- top of the body declarations of entry, package, protected unit,
21338 -- subprogram or task unit body denoted by Decl.
21340 procedure Process_Overloadable (Decl : Node_Id);
21341 -- Verify the legality of pragma SPARK_Mode when it applies to an
21342 -- entry or [generic] subprogram declaration denoted by Decl.
21344 procedure Process_Private_Part (Decl : Node_Id);
21345 -- Verify the legality of pragma SPARK_Mode when it appears at the
21346 -- top of the private declarations of a package spec, protected or
21347 -- task unit declaration denoted by Decl.
21349 procedure Process_Statement_Part (Decl : Node_Id);
21350 -- Verify the legality of pragma SPARK_Mode when it appears at the
21351 -- top of the statement sequence of a package body denoted by node
21352 -- Decl.
21354 procedure Process_Visible_Part (Decl : Node_Id);
21355 -- Verify the legality of pragma SPARK_Mode when it appears at the
21356 -- top of the visible declarations of a package spec, protected or
21357 -- task unit declaration denoted by Decl. The routine is also used
21358 -- on protected or task units declared without a definition.
21360 procedure Set_SPARK_Context;
21361 -- Subsidiary to routines Process_xxx. Set the global variables
21362 -- which represent the mode of the context from pragma N. Ensure
21363 -- that Dynamic_Elaboration_Checks are off if the new mode is On.
21365 ------------------------------
21366 -- Check_Pragma_Conformance --
21367 ------------------------------
21369 procedure Check_Pragma_Conformance
21370 (Context_Pragma : Node_Id;
21371 Entity : Entity_Id;
21372 Entity_Pragma : Node_Id)
21374 Err_Id : Entity_Id;
21375 Err_N : Node_Id;
21377 begin
21378 -- The current pragma may appear without an argument. If this
21379 -- is the case, associate all error messages with the pragma
21380 -- itself.
21382 if Present (Arg1) then
21383 Err_N := Arg1;
21384 else
21385 Err_N := N;
21386 end if;
21388 -- The mode of the current pragma is compared against that of
21389 -- an enclosing context.
21391 if Present (Context_Pragma) then
21392 pragma Assert (Nkind (Context_Pragma) = N_Pragma);
21394 -- Issue an error if the new mode is less restrictive than
21395 -- that of the context.
21397 if Get_SPARK_Mode_From_Annotation (Context_Pragma) = Off
21398 and then Get_SPARK_Mode_From_Annotation (N) = On
21399 then
21400 Error_Msg_N
21401 ("cannot change SPARK_Mode from Off to On", Err_N);
21402 Error_Msg_Sloc := Sloc (SPARK_Mode_Pragma);
21403 Error_Msg_N ("\SPARK_Mode was set to Off#", Err_N);
21404 raise Pragma_Exit;
21405 end if;
21406 end if;
21408 -- The mode of the current pragma is compared against that of
21409 -- an initial package, protected type, subprogram or task type
21410 -- declaration.
21412 if Present (Entity) then
21414 -- A simple protected or task type is transformed into an
21415 -- anonymous type whose name cannot be used to issue error
21416 -- messages. Recover the original entity of the type.
21418 if Ekind_In (Entity, E_Protected_Type, E_Task_Type) then
21419 Err_Id :=
21420 Defining_Entity
21421 (Original_Node (Unit_Declaration_Node (Entity)));
21422 else
21423 Err_Id := Entity;
21424 end if;
21426 -- Both the initial declaration and the completion carry
21427 -- SPARK_Mode pragmas.
21429 if Present (Entity_Pragma) then
21430 pragma Assert (Nkind (Entity_Pragma) = N_Pragma);
21432 -- Issue an error if the new mode is less restrictive
21433 -- than that of the initial declaration.
21435 if Get_SPARK_Mode_From_Annotation (Entity_Pragma) = Off
21436 and then Get_SPARK_Mode_From_Annotation (N) = On
21437 then
21438 Error_Msg_N ("incorrect use of SPARK_Mode", Err_N);
21439 Error_Msg_Sloc := Sloc (Entity_Pragma);
21440 Error_Msg_NE
21441 ("\value Off was set for SPARK_Mode on&#",
21442 Err_N, Err_Id);
21443 raise Pragma_Exit;
21444 end if;
21446 -- Otherwise the initial declaration lacks a SPARK_Mode
21447 -- pragma in which case the current pragma is illegal as
21448 -- it cannot "complete".
21450 else
21451 Error_Msg_N ("incorrect use of SPARK_Mode", Err_N);
21452 Error_Msg_Sloc := Sloc (Err_Id);
21453 Error_Msg_NE
21454 ("\no value was set for SPARK_Mode on&#",
21455 Err_N, Err_Id);
21456 raise Pragma_Exit;
21457 end if;
21458 end if;
21459 end Check_Pragma_Conformance;
21461 --------------------------------
21462 -- Check_Library_Level_Entity --
21463 --------------------------------
21465 procedure Check_Library_Level_Entity (E : Entity_Id) is
21466 procedure Add_Entity_To_Name_Buffer;
21467 -- Add the E_Kind of entity E to the name buffer
21469 -------------------------------
21470 -- Add_Entity_To_Name_Buffer --
21471 -------------------------------
21473 procedure Add_Entity_To_Name_Buffer is
21474 begin
21475 if Ekind_In (E, E_Entry, E_Entry_Family) then
21476 Add_Str_To_Name_Buffer ("entry");
21478 elsif Ekind_In (E, E_Generic_Package,
21479 E_Package,
21480 E_Package_Body)
21481 then
21482 Add_Str_To_Name_Buffer ("package");
21484 elsif Ekind_In (E, E_Protected_Body, E_Protected_Type) then
21485 Add_Str_To_Name_Buffer ("protected type");
21487 elsif Ekind_In (E, E_Function,
21488 E_Generic_Function,
21489 E_Generic_Procedure,
21490 E_Procedure,
21491 E_Subprogram_Body)
21492 then
21493 Add_Str_To_Name_Buffer ("subprogram");
21495 else
21496 pragma Assert (Ekind_In (E, E_Task_Body, E_Task_Type));
21497 Add_Str_To_Name_Buffer ("task type");
21498 end if;
21499 end Add_Entity_To_Name_Buffer;
21501 -- Local variables
21503 Msg_1 : constant String := "incorrect placement of pragma%";
21504 Msg_2 : Name_Id;
21506 -- Start of processing for Check_Library_Level_Entity
21508 begin
21509 if not Is_Library_Level_Entity (E) then
21510 Error_Msg_Name_1 := Pname;
21511 Error_Msg_N (Fix_Error (Msg_1), N);
21513 Name_Len := 0;
21514 Add_Str_To_Name_Buffer ("\& is not a library-level ");
21515 Add_Entity_To_Name_Buffer;
21517 Msg_2 := Name_Find;
21518 Error_Msg_NE (Get_Name_String (Msg_2), N, E);
21520 raise Pragma_Exit;
21521 end if;
21522 end Check_Library_Level_Entity;
21524 ------------------
21525 -- Process_Body --
21526 ------------------
21528 procedure Process_Body (Decl : Node_Id) is
21529 Body_Id : constant Entity_Id := Defining_Entity (Decl);
21530 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Decl);
21532 begin
21533 -- Ignore pragma when applied to the special body created for
21534 -- inlining, recognized by its internal name _Parent.
21536 if Chars (Body_Id) = Name_uParent then
21537 return;
21538 end if;
21540 Check_Library_Level_Entity (Body_Id);
21542 -- For entry bodies, verify the legality against:
21543 -- * The mode of the context
21544 -- * The mode of the spec (if any)
21546 if Nkind_In (Decl, N_Entry_Body, N_Subprogram_Body) then
21548 -- A stand alone subprogram body
21550 if Body_Id = Spec_Id then
21551 Check_Pragma_Conformance
21552 (Context_Pragma => SPARK_Pragma (Body_Id),
21553 Entity => Empty,
21554 Entity_Pragma => Empty);
21556 -- An entry or subprogram body that completes a previous
21557 -- declaration.
21559 else
21560 Check_Pragma_Conformance
21561 (Context_Pragma => SPARK_Pragma (Body_Id),
21562 Entity => Spec_Id,
21563 Entity_Pragma => SPARK_Pragma (Spec_Id));
21564 end if;
21566 Set_SPARK_Context;
21567 Set_SPARK_Pragma (Body_Id, N);
21568 Set_SPARK_Pragma_Inherited (Body_Id, False);
21570 -- For package bodies, verify the legality against:
21571 -- * The mode of the context
21572 -- * The mode of the private part
21574 -- This case is separated from protected and task bodies
21575 -- because the statement part of the package body inherits
21576 -- the mode of the body declarations.
21578 elsif Nkind (Decl) = N_Package_Body then
21579 Check_Pragma_Conformance
21580 (Context_Pragma => SPARK_Pragma (Body_Id),
21581 Entity => Spec_Id,
21582 Entity_Pragma => SPARK_Aux_Pragma (Spec_Id));
21584 Set_SPARK_Context;
21585 Set_SPARK_Pragma (Body_Id, N);
21586 Set_SPARK_Pragma_Inherited (Body_Id, False);
21587 Set_SPARK_Aux_Pragma (Body_Id, N);
21588 Set_SPARK_Aux_Pragma_Inherited (Body_Id, True);
21590 -- For protected and task bodies, verify the legality against:
21591 -- * The mode of the context
21592 -- * The mode of the private part
21594 else
21595 pragma Assert
21596 (Nkind_In (Decl, N_Protected_Body, N_Task_Body));
21598 Check_Pragma_Conformance
21599 (Context_Pragma => SPARK_Pragma (Body_Id),
21600 Entity => Spec_Id,
21601 Entity_Pragma => SPARK_Aux_Pragma (Spec_Id));
21603 Set_SPARK_Context;
21604 Set_SPARK_Pragma (Body_Id, N);
21605 Set_SPARK_Pragma_Inherited (Body_Id, False);
21606 end if;
21607 end Process_Body;
21609 --------------------------
21610 -- Process_Overloadable --
21611 --------------------------
21613 procedure Process_Overloadable (Decl : Node_Id) is
21614 Spec_Id : constant Entity_Id := Defining_Entity (Decl);
21615 Spec_Typ : constant Entity_Id := Etype (Spec_Id);
21617 begin
21618 Check_Library_Level_Entity (Spec_Id);
21620 -- Verify the legality against:
21621 -- * The mode of the context
21623 Check_Pragma_Conformance
21624 (Context_Pragma => SPARK_Pragma (Spec_Id),
21625 Entity => Empty,
21626 Entity_Pragma => Empty);
21628 Set_SPARK_Pragma (Spec_Id, N);
21629 Set_SPARK_Pragma_Inherited (Spec_Id, False);
21631 -- When the pragma applies to the anonymous object created for
21632 -- a single task type, decorate the type as well. This scenario
21633 -- arises when the single task type lacks a task definition,
21634 -- therefore there is no issue with respect to a potential
21635 -- pragma SPARK_Mode in the private part.
21637 -- task type Anon_Task_Typ;
21638 -- Obj : Anon_Task_Typ;
21639 -- pragma SPARK_Mode ...;
21641 if Is_Single_Task_Object (Spec_Id) then
21642 Set_SPARK_Pragma (Spec_Typ, N);
21643 Set_SPARK_Pragma_Inherited (Spec_Typ, False);
21644 Set_SPARK_Aux_Pragma (Spec_Typ, N);
21645 Set_SPARK_Aux_Pragma_Inherited (Spec_Typ, True);
21646 end if;
21647 end Process_Overloadable;
21649 --------------------------
21650 -- Process_Private_Part --
21651 --------------------------
21653 procedure Process_Private_Part (Decl : Node_Id) is
21654 Spec_Id : constant Entity_Id := Defining_Entity (Decl);
21656 begin
21657 Check_Library_Level_Entity (Spec_Id);
21659 -- Verify the legality against:
21660 -- * The mode of the visible declarations
21662 Check_Pragma_Conformance
21663 (Context_Pragma => Empty,
21664 Entity => Spec_Id,
21665 Entity_Pragma => SPARK_Pragma (Spec_Id));
21667 Set_SPARK_Context;
21668 Set_SPARK_Aux_Pragma (Spec_Id, N);
21669 Set_SPARK_Aux_Pragma_Inherited (Spec_Id, False);
21670 end Process_Private_Part;
21672 ----------------------------
21673 -- Process_Statement_Part --
21674 ----------------------------
21676 procedure Process_Statement_Part (Decl : Node_Id) is
21677 Body_Id : constant Entity_Id := Defining_Entity (Decl);
21679 begin
21680 Check_Library_Level_Entity (Body_Id);
21682 -- Verify the legality against:
21683 -- * The mode of the body declarations
21685 Check_Pragma_Conformance
21686 (Context_Pragma => Empty,
21687 Entity => Body_Id,
21688 Entity_Pragma => SPARK_Pragma (Body_Id));
21690 Set_SPARK_Context;
21691 Set_SPARK_Aux_Pragma (Body_Id, N);
21692 Set_SPARK_Aux_Pragma_Inherited (Body_Id, False);
21693 end Process_Statement_Part;
21695 --------------------------
21696 -- Process_Visible_Part --
21697 --------------------------
21699 procedure Process_Visible_Part (Decl : Node_Id) is
21700 Spec_Id : constant Entity_Id := Defining_Entity (Decl);
21701 Obj_Id : Entity_Id;
21703 begin
21704 Check_Library_Level_Entity (Spec_Id);
21706 -- Verify the legality against:
21707 -- * The mode of the context
21709 Check_Pragma_Conformance
21710 (Context_Pragma => SPARK_Pragma (Spec_Id),
21711 Entity => Empty,
21712 Entity_Pragma => Empty);
21714 -- A task unit declared without a definition does not set the
21715 -- SPARK_Mode of the context because the task does not have any
21716 -- entries that could inherit the mode.
21718 if not Nkind_In (Decl, N_Single_Task_Declaration,
21719 N_Task_Type_Declaration)
21720 then
21721 Set_SPARK_Context;
21722 end if;
21724 Set_SPARK_Pragma (Spec_Id, N);
21725 Set_SPARK_Pragma_Inherited (Spec_Id, False);
21726 Set_SPARK_Aux_Pragma (Spec_Id, N);
21727 Set_SPARK_Aux_Pragma_Inherited (Spec_Id, True);
21729 -- When the pragma applies to a single protected or task type,
21730 -- decorate the corresponding anonymous object as well.
21732 -- protected Anon_Prot_Typ is
21733 -- pragma SPARK_Mode ...;
21734 -- ...
21735 -- end Anon_Prot_Typ;
21737 -- Obj : Anon_Prot_Typ;
21739 if Is_Single_Concurrent_Type (Spec_Id) then
21740 Obj_Id := Anonymous_Object (Spec_Id);
21742 Set_SPARK_Pragma (Obj_Id, N);
21743 Set_SPARK_Pragma_Inherited (Obj_Id, False);
21744 end if;
21745 end Process_Visible_Part;
21747 -----------------------
21748 -- Set_SPARK_Context --
21749 -----------------------
21751 procedure Set_SPARK_Context is
21752 begin
21753 SPARK_Mode := Mode_Id;
21754 SPARK_Mode_Pragma := N;
21755 end Set_SPARK_Context;
21757 -- Local variables
21759 Context : Node_Id;
21760 Mode : Name_Id;
21761 Stmt : Node_Id;
21763 -- Start of processing for Do_SPARK_Mode
21765 begin
21766 -- When a SPARK_Mode pragma appears inside an instantiation whose
21767 -- enclosing context has SPARK_Mode set to "off", the pragma has
21768 -- no semantic effect.
21770 if Ignore_SPARK_Mode_Pragmas_In_Instance then
21771 Rewrite (N, Make_Null_Statement (Loc));
21772 Analyze (N);
21773 return;
21774 end if;
21776 GNAT_Pragma;
21777 Check_No_Identifiers;
21778 Check_At_Most_N_Arguments (1);
21780 -- Check the legality of the mode (no argument = ON)
21782 if Arg_Count = 1 then
21783 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
21784 Mode := Chars (Get_Pragma_Arg (Arg1));
21785 else
21786 Mode := Name_On;
21787 end if;
21789 Mode_Id := Get_SPARK_Mode_Type (Mode);
21790 Context := Parent (N);
21792 -- The pragma appears in a configuration file
21794 if No (Context) then
21795 Check_Valid_Configuration_Pragma;
21797 if Present (SPARK_Mode_Pragma) then
21798 Duplication_Error
21799 (Prag => N,
21800 Prev => SPARK_Mode_Pragma);
21801 raise Pragma_Exit;
21802 end if;
21804 Set_SPARK_Context;
21806 -- The pragma acts as a configuration pragma in a compilation unit
21808 -- pragma SPARK_Mode ...;
21809 -- package Pack is ...;
21811 elsif Nkind (Context) = N_Compilation_Unit
21812 and then List_Containing (N) = Context_Items (Context)
21813 then
21814 Check_Valid_Configuration_Pragma;
21815 Set_SPARK_Context;
21817 -- Otherwise the placement of the pragma within the tree dictates
21818 -- its associated construct. Inspect the declarative list where
21819 -- the pragma resides to find a potential construct.
21821 else
21822 Stmt := Prev (N);
21823 while Present (Stmt) loop
21825 -- Skip prior pragmas, but check for duplicates. Note that
21826 -- this also takes care of pragmas generated for aspects.
21828 if Nkind (Stmt) = N_Pragma then
21829 if Pragma_Name (Stmt) = Pname then
21830 Duplication_Error
21831 (Prag => N,
21832 Prev => Stmt);
21833 raise Pragma_Exit;
21834 end if;
21836 -- The pragma applies to an expression function that has
21837 -- already been rewritten into a subprogram declaration.
21839 -- function Expr_Func return ... is (...);
21840 -- pragma SPARK_Mode ...;
21842 elsif Nkind (Stmt) = N_Subprogram_Declaration
21843 and then Nkind (Original_Node (Stmt)) =
21844 N_Expression_Function
21845 then
21846 Process_Overloadable (Stmt);
21847 return;
21849 -- The pragma applies to the anonymous object created for a
21850 -- single concurrent type.
21852 -- protected type Anon_Prot_Typ ...;
21853 -- Obj : Anon_Prot_Typ;
21854 -- pragma SPARK_Mode ...;
21856 elsif Nkind (Stmt) = N_Object_Declaration
21857 and then Is_Single_Concurrent_Object
21858 (Defining_Entity (Stmt))
21859 then
21860 Process_Overloadable (Stmt);
21861 return;
21863 -- Skip internally generated code
21865 elsif not Comes_From_Source (Stmt) then
21866 null;
21868 -- The pragma applies to an entry or [generic] subprogram
21869 -- declaration.
21871 -- entry Ent ...;
21872 -- pragma SPARK_Mode ...;
21874 -- [generic]
21875 -- procedure Proc ...;
21876 -- pragma SPARK_Mode ...;
21878 elsif Nkind_In (Stmt, N_Generic_Subprogram_Declaration,
21879 N_Subprogram_Declaration)
21880 or else (Nkind (Stmt) = N_Entry_Declaration
21881 and then Is_Protected_Type
21882 (Scope (Defining_Entity (Stmt))))
21883 then
21884 Process_Overloadable (Stmt);
21885 return;
21887 -- Otherwise the pragma does not apply to a legal construct
21888 -- or it does not appear at the top of a declarative or a
21889 -- statement list. Issue an error and stop the analysis.
21891 else
21892 Pragma_Misplaced;
21893 exit;
21894 end if;
21896 Prev (Stmt);
21897 end loop;
21899 -- The pragma applies to a package or a subprogram that acts as
21900 -- a compilation unit.
21902 -- procedure Proc ...;
21903 -- pragma SPARK_Mode ...;
21905 if Nkind (Context) = N_Compilation_Unit_Aux then
21906 Context := Unit (Parent (Context));
21907 end if;
21909 -- The pragma appears at the top of entry, package, protected
21910 -- unit, subprogram or task unit body declarations.
21912 -- entry Ent when ... is
21913 -- pragma SPARK_Mode ...;
21915 -- package body Pack is
21916 -- pragma SPARK_Mode ...;
21918 -- procedure Proc ... is
21919 -- pragma SPARK_Mode;
21921 -- protected body Prot is
21922 -- pragma SPARK_Mode ...;
21924 if Nkind_In (Context, N_Entry_Body,
21925 N_Package_Body,
21926 N_Protected_Body,
21927 N_Subprogram_Body,
21928 N_Task_Body)
21929 then
21930 Process_Body (Context);
21932 -- The pragma appears at the top of the visible or private
21933 -- declaration of a package spec, protected or task unit.
21935 -- package Pack is
21936 -- pragma SPARK_Mode ...;
21937 -- private
21938 -- pragma SPARK_Mode ...;
21940 -- protected [type] Prot is
21941 -- pragma SPARK_Mode ...;
21942 -- private
21943 -- pragma SPARK_Mode ...;
21945 elsif Nkind_In (Context, N_Package_Specification,
21946 N_Protected_Definition,
21947 N_Task_Definition)
21948 then
21949 if List_Containing (N) = Visible_Declarations (Context) then
21950 Process_Visible_Part (Parent (Context));
21951 else
21952 Process_Private_Part (Parent (Context));
21953 end if;
21955 -- The pragma appears at the top of package body statements
21957 -- package body Pack is
21958 -- begin
21959 -- pragma SPARK_Mode;
21961 elsif Nkind (Context) = N_Handled_Sequence_Of_Statements
21962 and then Nkind (Parent (Context)) = N_Package_Body
21963 then
21964 Process_Statement_Part (Parent (Context));
21966 -- The pragma appeared as an aspect of a [generic] subprogram
21967 -- declaration that acts as a compilation unit.
21969 -- [generic]
21970 -- procedure Proc ...;
21971 -- pragma SPARK_Mode ...;
21973 elsif Nkind_In (Context, N_Generic_Subprogram_Declaration,
21974 N_Subprogram_Declaration)
21975 then
21976 Process_Overloadable (Context);
21978 -- The pragma does not apply to a legal construct, issue error
21980 else
21981 Pragma_Misplaced;
21982 end if;
21983 end if;
21984 end Do_SPARK_Mode;
21986 --------------------------------
21987 -- Static_Elaboration_Desired --
21988 --------------------------------
21990 -- pragma Static_Elaboration_Desired (DIRECT_NAME);
21992 when Pragma_Static_Elaboration_Desired =>
21993 GNAT_Pragma;
21994 Check_At_Most_N_Arguments (1);
21996 if Is_Compilation_Unit (Current_Scope)
21997 and then Ekind (Current_Scope) = E_Package
21998 then
21999 Set_Static_Elaboration_Desired (Current_Scope, True);
22000 else
22001 Error_Pragma ("pragma% must apply to a library-level package");
22002 end if;
22004 ------------------
22005 -- Storage_Size --
22006 ------------------
22008 -- pragma Storage_Size (EXPRESSION);
22010 when Pragma_Storage_Size => Storage_Size : declare
22011 P : constant Node_Id := Parent (N);
22012 Arg : Node_Id;
22014 begin
22015 Check_No_Identifiers;
22016 Check_Arg_Count (1);
22018 -- The expression must be analyzed in the special manner described
22019 -- in "Handling of Default Expressions" in sem.ads.
22021 Arg := Get_Pragma_Arg (Arg1);
22022 Preanalyze_Spec_Expression (Arg, Any_Integer);
22024 if not Is_OK_Static_Expression (Arg) then
22025 Check_Restriction (Static_Storage_Size, Arg);
22026 end if;
22028 if Nkind (P) /= N_Task_Definition then
22029 Pragma_Misplaced;
22030 return;
22032 else
22033 if Has_Storage_Size_Pragma (P) then
22034 Error_Pragma ("duplicate pragma% not allowed");
22035 else
22036 Set_Has_Storage_Size_Pragma (P, True);
22037 end if;
22039 Record_Rep_Item (Defining_Identifier (Parent (P)), N);
22040 end if;
22041 end Storage_Size;
22043 ------------------
22044 -- Storage_Unit --
22045 ------------------
22047 -- pragma Storage_Unit (NUMERIC_LITERAL);
22049 -- Only permitted argument is System'Storage_Unit value
22051 when Pragma_Storage_Unit =>
22052 Check_No_Identifiers;
22053 Check_Arg_Count (1);
22054 Check_Arg_Is_Integer_Literal (Arg1);
22056 if Intval (Get_Pragma_Arg (Arg1)) /=
22057 UI_From_Int (Ttypes.System_Storage_Unit)
22058 then
22059 Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
22060 Error_Pragma_Arg
22061 ("the only allowed argument for pragma% is ^", Arg1);
22062 end if;
22064 --------------------
22065 -- Stream_Convert --
22066 --------------------
22068 -- pragma Stream_Convert (
22069 -- [Entity =>] type_LOCAL_NAME,
22070 -- [Read =>] function_NAME,
22071 -- [Write =>] function NAME);
22073 when Pragma_Stream_Convert => Stream_Convert : declare
22074 procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
22075 -- Check that the given argument is the name of a local function
22076 -- of one argument that is not overloaded earlier in the current
22077 -- local scope. A check is also made that the argument is a
22078 -- function with one parameter.
22080 --------------------------------------
22081 -- Check_OK_Stream_Convert_Function --
22082 --------------------------------------
22084 procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
22085 Ent : Entity_Id;
22087 begin
22088 Check_Arg_Is_Local_Name (Arg);
22089 Ent := Entity (Get_Pragma_Arg (Arg));
22091 if Has_Homonym (Ent) then
22092 Error_Pragma_Arg
22093 ("argument for pragma% may not be overloaded", Arg);
22094 end if;
22096 if Ekind (Ent) /= E_Function
22097 or else No (First_Formal (Ent))
22098 or else Present (Next_Formal (First_Formal (Ent)))
22099 then
22100 Error_Pragma_Arg
22101 ("argument for pragma% must be function of one argument",
22102 Arg);
22103 end if;
22104 end Check_OK_Stream_Convert_Function;
22106 -- Start of processing for Stream_Convert
22108 begin
22109 GNAT_Pragma;
22110 Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
22111 Check_Arg_Count (3);
22112 Check_Optional_Identifier (Arg1, Name_Entity);
22113 Check_Optional_Identifier (Arg2, Name_Read);
22114 Check_Optional_Identifier (Arg3, Name_Write);
22115 Check_Arg_Is_Local_Name (Arg1);
22116 Check_OK_Stream_Convert_Function (Arg2);
22117 Check_OK_Stream_Convert_Function (Arg3);
22119 declare
22120 Typ : constant Entity_Id :=
22121 Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
22122 Read : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
22123 Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
22125 begin
22126 Check_First_Subtype (Arg1);
22128 -- Check for too early or too late. Note that we don't enforce
22129 -- the rule about primitive operations in this case, since, as
22130 -- is the case for explicit stream attributes themselves, these
22131 -- restrictions are not appropriate. Note that the chaining of
22132 -- the pragma by Rep_Item_Too_Late is actually the critical
22133 -- processing done for this pragma.
22135 if Rep_Item_Too_Early (Typ, N)
22136 or else
22137 Rep_Item_Too_Late (Typ, N, FOnly => True)
22138 then
22139 return;
22140 end if;
22142 -- Return if previous error
22144 if Etype (Typ) = Any_Type
22145 or else
22146 Etype (Read) = Any_Type
22147 or else
22148 Etype (Write) = Any_Type
22149 then
22150 return;
22151 end if;
22153 -- Error checks
22155 if Underlying_Type (Etype (Read)) /= Typ then
22156 Error_Pragma_Arg
22157 ("incorrect return type for function&", Arg2);
22158 end if;
22160 if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
22161 Error_Pragma_Arg
22162 ("incorrect parameter type for function&", Arg3);
22163 end if;
22165 if Underlying_Type (Etype (First_Formal (Read))) /=
22166 Underlying_Type (Etype (Write))
22167 then
22168 Error_Pragma_Arg
22169 ("result type of & does not match Read parameter type",
22170 Arg3);
22171 end if;
22172 end;
22173 end Stream_Convert;
22175 ------------------
22176 -- Style_Checks --
22177 ------------------
22179 -- pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
22181 -- This is processed by the parser since some of the style checks
22182 -- take place during source scanning and parsing. This means that
22183 -- we don't need to issue error messages here.
22185 when Pragma_Style_Checks => Style_Checks : declare
22186 A : constant Node_Id := Get_Pragma_Arg (Arg1);
22187 S : String_Id;
22188 C : Char_Code;
22190 begin
22191 GNAT_Pragma;
22192 Check_No_Identifiers;
22194 -- Two argument form
22196 if Arg_Count = 2 then
22197 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
22199 declare
22200 E_Id : Node_Id;
22201 E : Entity_Id;
22203 begin
22204 E_Id := Get_Pragma_Arg (Arg2);
22205 Analyze (E_Id);
22207 if not Is_Entity_Name (E_Id) then
22208 Error_Pragma_Arg
22209 ("second argument of pragma% must be entity name",
22210 Arg2);
22211 end if;
22213 E := Entity (E_Id);
22215 if not Ignore_Style_Checks_Pragmas then
22216 if E = Any_Id then
22217 return;
22218 else
22219 loop
22220 Set_Suppress_Style_Checks
22221 (E, Chars (Get_Pragma_Arg (Arg1)) = Name_Off);
22222 exit when No (Homonym (E));
22223 E := Homonym (E);
22224 end loop;
22225 end if;
22226 end if;
22227 end;
22229 -- One argument form
22231 else
22232 Check_Arg_Count (1);
22234 if Nkind (A) = N_String_Literal then
22235 S := Strval (A);
22237 declare
22238 Slen : constant Natural := Natural (String_Length (S));
22239 Options : String (1 .. Slen);
22240 J : Positive;
22242 begin
22243 J := 1;
22244 loop
22245 C := Get_String_Char (S, Pos (J));
22246 exit when not In_Character_Range (C);
22247 Options (J) := Get_Character (C);
22249 -- If at end of string, set options. As per discussion
22250 -- above, no need to check for errors, since we issued
22251 -- them in the parser.
22253 if J = Slen then
22254 if not Ignore_Style_Checks_Pragmas then
22255 Set_Style_Check_Options (Options);
22256 end if;
22258 exit;
22259 end if;
22261 J := J + 1;
22262 end loop;
22263 end;
22265 elsif Nkind (A) = N_Identifier then
22266 if Chars (A) = Name_All_Checks then
22267 if not Ignore_Style_Checks_Pragmas then
22268 if GNAT_Mode then
22269 Set_GNAT_Style_Check_Options;
22270 else
22271 Set_Default_Style_Check_Options;
22272 end if;
22273 end if;
22275 elsif Chars (A) = Name_On then
22276 if not Ignore_Style_Checks_Pragmas then
22277 Style_Check := True;
22278 end if;
22280 elsif Chars (A) = Name_Off then
22281 if not Ignore_Style_Checks_Pragmas then
22282 Style_Check := False;
22283 end if;
22284 end if;
22285 end if;
22286 end if;
22287 end Style_Checks;
22289 --------------
22290 -- Subtitle --
22291 --------------
22293 -- pragma Subtitle ([Subtitle =>] STRING_LITERAL);
22295 when Pragma_Subtitle =>
22296 GNAT_Pragma;
22297 Check_Arg_Count (1);
22298 Check_Optional_Identifier (Arg1, Name_Subtitle);
22299 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
22300 Store_Note (N);
22302 --------------
22303 -- Suppress --
22304 --------------
22306 -- pragma Suppress (IDENTIFIER [, [On =>] NAME]);
22308 when Pragma_Suppress =>
22309 Process_Suppress_Unsuppress (Suppress_Case => True);
22311 ------------------
22312 -- Suppress_All --
22313 ------------------
22315 -- pragma Suppress_All;
22317 -- The only check made here is that the pragma has no arguments.
22318 -- There are no placement rules, and the processing required (setting
22319 -- the Has_Pragma_Suppress_All flag in the compilation unit node was
22320 -- taken care of by the parser). Process_Compilation_Unit_Pragmas
22321 -- then creates and inserts a pragma Suppress (All_Checks).
22323 when Pragma_Suppress_All =>
22324 GNAT_Pragma;
22325 Check_Arg_Count (0);
22327 -------------------------
22328 -- Suppress_Debug_Info --
22329 -------------------------
22331 -- pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
22333 when Pragma_Suppress_Debug_Info => Suppress_Debug_Info : declare
22334 Nam_Id : Entity_Id;
22336 begin
22337 GNAT_Pragma;
22338 Check_Arg_Count (1);
22339 Check_Optional_Identifier (Arg1, Name_Entity);
22340 Check_Arg_Is_Local_Name (Arg1);
22342 Nam_Id := Entity (Get_Pragma_Arg (Arg1));
22344 -- A pragma that applies to a Ghost entity becomes Ghost for the
22345 -- purposes of legality checks and removal of ignored Ghost code.
22347 Mark_Ghost_Pragma (N, Nam_Id);
22348 Set_Debug_Info_Off (Nam_Id);
22349 end Suppress_Debug_Info;
22351 ----------------------------------
22352 -- Suppress_Exception_Locations --
22353 ----------------------------------
22355 -- pragma Suppress_Exception_Locations;
22357 when Pragma_Suppress_Exception_Locations =>
22358 GNAT_Pragma;
22359 Check_Arg_Count (0);
22360 Check_Valid_Configuration_Pragma;
22361 Exception_Locations_Suppressed := True;
22363 -----------------------------
22364 -- Suppress_Initialization --
22365 -----------------------------
22367 -- pragma Suppress_Initialization ([Entity =>] type_Name);
22369 when Pragma_Suppress_Initialization => Suppress_Init : declare
22370 E : Entity_Id;
22371 E_Id : Node_Id;
22373 begin
22374 GNAT_Pragma;
22375 Check_Arg_Count (1);
22376 Check_Optional_Identifier (Arg1, Name_Entity);
22377 Check_Arg_Is_Local_Name (Arg1);
22379 E_Id := Get_Pragma_Arg (Arg1);
22381 if Etype (E_Id) = Any_Type then
22382 return;
22383 end if;
22385 E := Entity (E_Id);
22387 -- A pragma that applies to a Ghost entity becomes Ghost for the
22388 -- purposes of legality checks and removal of ignored Ghost code.
22390 Mark_Ghost_Pragma (N, E);
22392 if not Is_Type (E) and then Ekind (E) /= E_Variable then
22393 Error_Pragma_Arg
22394 ("pragma% requires variable, type or subtype", Arg1);
22395 end if;
22397 if Rep_Item_Too_Early (E, N)
22398 or else
22399 Rep_Item_Too_Late (E, N, FOnly => True)
22400 then
22401 return;
22402 end if;
22404 -- For incomplete/private type, set flag on full view
22406 if Is_Incomplete_Or_Private_Type (E) then
22407 if No (Full_View (Base_Type (E))) then
22408 Error_Pragma_Arg
22409 ("argument of pragma% cannot be an incomplete type", Arg1);
22410 else
22411 Set_Suppress_Initialization (Full_View (Base_Type (E)));
22412 end if;
22414 -- For first subtype, set flag on base type
22416 elsif Is_First_Subtype (E) then
22417 Set_Suppress_Initialization (Base_Type (E));
22419 -- For other than first subtype, set flag on subtype or variable
22421 else
22422 Set_Suppress_Initialization (E);
22423 end if;
22424 end Suppress_Init;
22426 -----------------
22427 -- System_Name --
22428 -----------------
22430 -- pragma System_Name (DIRECT_NAME);
22432 -- Syntax check: one argument, which must be the identifier GNAT or
22433 -- the identifier GCC, no other identifiers are acceptable.
22435 when Pragma_System_Name =>
22436 GNAT_Pragma;
22437 Check_No_Identifiers;
22438 Check_Arg_Count (1);
22439 Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
22441 -----------------------------
22442 -- Task_Dispatching_Policy --
22443 -----------------------------
22445 -- pragma Task_Dispatching_Policy (policy_IDENTIFIER);
22447 when Pragma_Task_Dispatching_Policy => declare
22448 DP : Character;
22450 begin
22451 Check_Ada_83_Warning;
22452 Check_Arg_Count (1);
22453 Check_No_Identifiers;
22454 Check_Arg_Is_Task_Dispatching_Policy (Arg1);
22455 Check_Valid_Configuration_Pragma;
22456 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
22457 DP := Fold_Upper (Name_Buffer (1));
22459 if Task_Dispatching_Policy /= ' '
22460 and then Task_Dispatching_Policy /= DP
22461 then
22462 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
22463 Error_Pragma
22464 ("task dispatching policy incompatible with policy#");
22466 -- Set new policy, but always preserve System_Location since we
22467 -- like the error message with the run time name.
22469 else
22470 Task_Dispatching_Policy := DP;
22472 if Task_Dispatching_Policy_Sloc /= System_Location then
22473 Task_Dispatching_Policy_Sloc := Loc;
22474 end if;
22475 end if;
22476 end;
22478 ---------------
22479 -- Task_Info --
22480 ---------------
22482 -- pragma Task_Info (EXPRESSION);
22484 when Pragma_Task_Info => Task_Info : declare
22485 P : constant Node_Id := Parent (N);
22486 Ent : Entity_Id;
22488 begin
22489 GNAT_Pragma;
22491 if Warn_On_Obsolescent_Feature then
22492 Error_Msg_N
22493 ("'G'N'A'T pragma Task_Info is now obsolete, use 'C'P'U "
22494 & "instead?j?", N);
22495 end if;
22497 if Nkind (P) /= N_Task_Definition then
22498 Error_Pragma ("pragma% must appear in task definition");
22499 end if;
22501 Check_No_Identifiers;
22502 Check_Arg_Count (1);
22504 Analyze_And_Resolve
22505 (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
22507 if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
22508 return;
22509 end if;
22511 Ent := Defining_Identifier (Parent (P));
22513 -- Check duplicate pragma before we chain the pragma in the Rep
22514 -- Item chain of Ent.
22516 if Has_Rep_Pragma
22517 (Ent, Name_Task_Info, Check_Parents => False)
22518 then
22519 Error_Pragma ("duplicate pragma% not allowed");
22520 end if;
22522 Record_Rep_Item (Ent, N);
22523 end Task_Info;
22525 ---------------
22526 -- Task_Name --
22527 ---------------
22529 -- pragma Task_Name (string_EXPRESSION);
22531 when Pragma_Task_Name => Task_Name : declare
22532 P : constant Node_Id := Parent (N);
22533 Arg : Node_Id;
22534 Ent : Entity_Id;
22536 begin
22537 Check_No_Identifiers;
22538 Check_Arg_Count (1);
22540 Arg := Get_Pragma_Arg (Arg1);
22542 -- The expression is used in the call to Create_Task, and must be
22543 -- expanded there, not in the context of the current spec. It must
22544 -- however be analyzed to capture global references, in case it
22545 -- appears in a generic context.
22547 Preanalyze_And_Resolve (Arg, Standard_String);
22549 if Nkind (P) /= N_Task_Definition then
22550 Pragma_Misplaced;
22551 end if;
22553 Ent := Defining_Identifier (Parent (P));
22555 -- Check duplicate pragma before we chain the pragma in the Rep
22556 -- Item chain of Ent.
22558 if Has_Rep_Pragma
22559 (Ent, Name_Task_Name, Check_Parents => False)
22560 then
22561 Error_Pragma ("duplicate pragma% not allowed");
22562 end if;
22564 Record_Rep_Item (Ent, N);
22565 end Task_Name;
22567 ------------------
22568 -- Task_Storage --
22569 ------------------
22571 -- pragma Task_Storage (
22572 -- [Task_Type =>] LOCAL_NAME,
22573 -- [Top_Guard =>] static_integer_EXPRESSION);
22575 when Pragma_Task_Storage => Task_Storage : declare
22576 Args : Args_List (1 .. 2);
22577 Names : constant Name_List (1 .. 2) := (
22578 Name_Task_Type,
22579 Name_Top_Guard);
22581 Task_Type : Node_Id renames Args (1);
22582 Top_Guard : Node_Id renames Args (2);
22584 Ent : Entity_Id;
22586 begin
22587 GNAT_Pragma;
22588 Gather_Associations (Names, Args);
22590 if No (Task_Type) then
22591 Error_Pragma
22592 ("missing task_type argument for pragma%");
22593 end if;
22595 Check_Arg_Is_Local_Name (Task_Type);
22597 Ent := Entity (Task_Type);
22599 if not Is_Task_Type (Ent) then
22600 Error_Pragma_Arg
22601 ("argument for pragma% must be task type", Task_Type);
22602 end if;
22604 if No (Top_Guard) then
22605 Error_Pragma_Arg
22606 ("pragma% takes two arguments", Task_Type);
22607 else
22608 Check_Arg_Is_OK_Static_Expression (Top_Guard, Any_Integer);
22609 end if;
22611 Check_First_Subtype (Task_Type);
22613 if Rep_Item_Too_Late (Ent, N) then
22614 raise Pragma_Exit;
22615 end if;
22616 end Task_Storage;
22618 ---------------
22619 -- Test_Case --
22620 ---------------
22622 -- pragma Test_Case
22623 -- ([Name =>] Static_String_EXPRESSION
22624 -- ,[Mode =>] MODE_TYPE
22625 -- [, Requires => Boolean_EXPRESSION]
22626 -- [, Ensures => Boolean_EXPRESSION]);
22628 -- MODE_TYPE ::= Nominal | Robustness
22630 -- Characteristics:
22632 -- * Analysis - The annotation undergoes initial checks to verify
22633 -- the legal placement and context. Secondary checks preanalyze the
22634 -- expressions in:
22636 -- Analyze_Test_Case_In_Decl_Part
22638 -- * Expansion - None.
22640 -- * Template - The annotation utilizes the generic template of the
22641 -- related subprogram when it is:
22643 -- aspect on subprogram declaration
22645 -- The annotation must prepare its own template when it is:
22647 -- pragma on subprogram declaration
22649 -- * Globals - Capture of global references must occur after full
22650 -- analysis.
22652 -- * Instance - The annotation is instantiated automatically when
22653 -- the related generic subprogram is instantiated except for the
22654 -- "pragma on subprogram declaration" case. In that scenario the
22655 -- annotation must instantiate itself.
22657 when Pragma_Test_Case => Test_Case : declare
22658 procedure Check_Distinct_Name (Subp_Id : Entity_Id);
22659 -- Ensure that the contract of subprogram Subp_Id does not contain
22660 -- another Test_Case pragma with the same Name as the current one.
22662 -------------------------
22663 -- Check_Distinct_Name --
22664 -------------------------
22666 procedure Check_Distinct_Name (Subp_Id : Entity_Id) is
22667 Items : constant Node_Id := Contract (Subp_Id);
22668 Name : constant String_Id := Get_Name_From_CTC_Pragma (N);
22669 Prag : Node_Id;
22671 begin
22672 -- Inspect all Test_Case pragma of the related subprogram
22673 -- looking for one with a duplicate "Name" argument.
22675 if Present (Items) then
22676 Prag := Contract_Test_Cases (Items);
22677 while Present (Prag) loop
22678 if Pragma_Name (Prag) = Name_Test_Case
22679 and then Prag /= N
22680 and then String_Equal
22681 (Name, Get_Name_From_CTC_Pragma (Prag))
22682 then
22683 Error_Msg_Sloc := Sloc (Prag);
22684 Error_Pragma ("name for pragma % is already used #");
22685 end if;
22687 Prag := Next_Pragma (Prag);
22688 end loop;
22689 end if;
22690 end Check_Distinct_Name;
22692 -- Local variables
22694 Pack_Decl : constant Node_Id := Unit (Cunit (Current_Sem_Unit));
22695 Asp_Arg : Node_Id;
22696 Context : Node_Id;
22697 Subp_Decl : Node_Id;
22698 Subp_Id : Entity_Id;
22700 -- Start of processing for Test_Case
22702 begin
22703 GNAT_Pragma;
22704 Check_At_Least_N_Arguments (2);
22705 Check_At_Most_N_Arguments (4);
22706 Check_Arg_Order
22707 ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
22709 -- Argument "Name"
22711 Check_Optional_Identifier (Arg1, Name_Name);
22712 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
22714 -- Argument "Mode"
22716 Check_Optional_Identifier (Arg2, Name_Mode);
22717 Check_Arg_Is_One_Of (Arg2, Name_Nominal, Name_Robustness);
22719 -- Arguments "Requires" and "Ensures"
22721 if Present (Arg3) then
22722 if Present (Arg4) then
22723 Check_Identifier (Arg3, Name_Requires);
22724 Check_Identifier (Arg4, Name_Ensures);
22725 else
22726 Check_Identifier_Is_One_Of
22727 (Arg3, Name_Requires, Name_Ensures);
22728 end if;
22729 end if;
22731 -- Pragma Test_Case must be associated with a subprogram declared
22732 -- in a library-level package. First determine whether the current
22733 -- compilation unit is a legal context.
22735 if Nkind_In (Pack_Decl, N_Package_Declaration,
22736 N_Generic_Package_Declaration)
22737 then
22738 null;
22740 -- Otherwise the placement is illegal
22742 else
22743 Error_Pragma
22744 ("pragma % must be specified within a package declaration");
22745 return;
22746 end if;
22748 Subp_Decl := Find_Related_Declaration_Or_Body (N);
22750 -- Find the enclosing context
22752 Context := Parent (Subp_Decl);
22754 if Present (Context) then
22755 Context := Parent (Context);
22756 end if;
22758 -- Verify the placement of the pragma
22760 if Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
22761 Error_Pragma
22762 ("pragma % cannot be applied to abstract subprogram");
22763 return;
22765 elsif Nkind (Subp_Decl) = N_Entry_Declaration then
22766 Error_Pragma ("pragma % cannot be applied to entry");
22767 return;
22769 -- The context is a [generic] subprogram declared at the top level
22770 -- of the [generic] package unit.
22772 elsif Nkind_In (Subp_Decl, N_Generic_Subprogram_Declaration,
22773 N_Subprogram_Declaration)
22774 and then Present (Context)
22775 and then Nkind_In (Context, N_Generic_Package_Declaration,
22776 N_Package_Declaration)
22777 then
22778 null;
22780 -- Otherwise the placement is illegal
22782 else
22783 Error_Pragma
22784 ("pragma % must be applied to a library-level subprogram "
22785 & "declaration");
22786 return;
22787 end if;
22789 Subp_Id := Defining_Entity (Subp_Decl);
22791 -- A pragma that applies to a Ghost entity becomes Ghost for the
22792 -- purposes of legality checks and removal of ignored Ghost code.
22794 Mark_Ghost_Pragma (N, Subp_Id);
22796 -- Chain the pragma on the contract for further processing by
22797 -- Analyze_Test_Case_In_Decl_Part.
22799 Add_Contract_Item (N, Subp_Id);
22801 -- Preanalyze the original aspect argument "Name" for ASIS or for
22802 -- a generic subprogram to properly capture global references.
22804 if ASIS_Mode or else Is_Generic_Subprogram (Subp_Id) then
22805 Asp_Arg := Test_Case_Arg (N, Name_Name, From_Aspect => True);
22807 if Present (Asp_Arg) then
22809 -- The argument appears with an identifier in association
22810 -- form.
22812 if Nkind (Asp_Arg) = N_Component_Association then
22813 Asp_Arg := Expression (Asp_Arg);
22814 end if;
22816 Check_Expr_Is_OK_Static_Expression
22817 (Asp_Arg, Standard_String);
22818 end if;
22819 end if;
22821 -- Ensure that the all Test_Case pragmas of the related subprogram
22822 -- have distinct names.
22824 Check_Distinct_Name (Subp_Id);
22826 -- Fully analyze the pragma when it appears inside an entry
22827 -- or subprogram body because it cannot benefit from forward
22828 -- references.
22830 if Nkind_In (Subp_Decl, N_Entry_Body,
22831 N_Subprogram_Body,
22832 N_Subprogram_Body_Stub)
22833 then
22834 -- The legality checks of pragma Test_Case are affected by the
22835 -- SPARK mode in effect and the volatility of the context.
22836 -- Analyze all pragmas in a specific order.
22838 Analyze_If_Present (Pragma_SPARK_Mode);
22839 Analyze_If_Present (Pragma_Volatile_Function);
22840 Analyze_Test_Case_In_Decl_Part (N);
22841 end if;
22842 end Test_Case;
22844 --------------------------
22845 -- Thread_Local_Storage --
22846 --------------------------
22848 -- pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
22850 when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
22851 E : Entity_Id;
22852 Id : Node_Id;
22854 begin
22855 GNAT_Pragma;
22856 Check_Arg_Count (1);
22857 Check_Optional_Identifier (Arg1, Name_Entity);
22858 Check_Arg_Is_Library_Level_Local_Name (Arg1);
22860 Id := Get_Pragma_Arg (Arg1);
22861 Analyze (Id);
22863 if not Is_Entity_Name (Id)
22864 or else Ekind (Entity (Id)) /= E_Variable
22865 then
22866 Error_Pragma_Arg ("local variable name required", Arg1);
22867 end if;
22869 E := Entity (Id);
22871 -- A pragma that applies to a Ghost entity becomes Ghost for the
22872 -- purposes of legality checks and removal of ignored Ghost code.
22874 Mark_Ghost_Pragma (N, E);
22876 if Rep_Item_Too_Early (E, N)
22877 or else
22878 Rep_Item_Too_Late (E, N)
22879 then
22880 raise Pragma_Exit;
22881 end if;
22883 Set_Has_Pragma_Thread_Local_Storage (E);
22884 Set_Has_Gigi_Rep_Item (E);
22885 end Thread_Local_Storage;
22887 ----------------
22888 -- Time_Slice --
22889 ----------------
22891 -- pragma Time_Slice (static_duration_EXPRESSION);
22893 when Pragma_Time_Slice => Time_Slice : declare
22894 Val : Ureal;
22895 Nod : Node_Id;
22897 begin
22898 GNAT_Pragma;
22899 Check_Arg_Count (1);
22900 Check_No_Identifiers;
22901 Check_In_Main_Program;
22902 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_Duration);
22904 if not Error_Posted (Arg1) then
22905 Nod := Next (N);
22906 while Present (Nod) loop
22907 if Nkind (Nod) = N_Pragma
22908 and then Pragma_Name (Nod) = Name_Time_Slice
22909 then
22910 Error_Msg_Name_1 := Pname;
22911 Error_Msg_N ("duplicate pragma% not permitted", Nod);
22912 end if;
22914 Next (Nod);
22915 end loop;
22916 end if;
22918 -- Process only if in main unit
22920 if Get_Source_Unit (Loc) = Main_Unit then
22921 Opt.Time_Slice_Set := True;
22922 Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
22924 if Val <= Ureal_0 then
22925 Opt.Time_Slice_Value := 0;
22927 elsif Val > UR_From_Uint (UI_From_Int (1000)) then
22928 Opt.Time_Slice_Value := 1_000_000_000;
22930 else
22931 Opt.Time_Slice_Value :=
22932 UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
22933 end if;
22934 end if;
22935 end Time_Slice;
22937 -----------
22938 -- Title --
22939 -----------
22941 -- pragma Title (TITLING_OPTION [, TITLING OPTION]);
22943 -- TITLING_OPTION ::=
22944 -- [Title =>] STRING_LITERAL
22945 -- | [Subtitle =>] STRING_LITERAL
22947 when Pragma_Title => Title : declare
22948 Args : Args_List (1 .. 2);
22949 Names : constant Name_List (1 .. 2) := (
22950 Name_Title,
22951 Name_Subtitle);
22953 begin
22954 GNAT_Pragma;
22955 Gather_Associations (Names, Args);
22956 Store_Note (N);
22958 for J in 1 .. 2 loop
22959 if Present (Args (J)) then
22960 Check_Arg_Is_OK_Static_Expression
22961 (Args (J), Standard_String);
22962 end if;
22963 end loop;
22964 end Title;
22966 ----------------------------
22967 -- Type_Invariant[_Class] --
22968 ----------------------------
22970 -- pragma Type_Invariant[_Class]
22971 -- ([Entity =>] type_LOCAL_NAME,
22972 -- [Check =>] EXPRESSION);
22974 when Pragma_Type_Invariant
22975 | Pragma_Type_Invariant_Class
22977 Type_Invariant : declare
22978 I_Pragma : Node_Id;
22980 begin
22981 Check_Arg_Count (2);
22983 -- Rewrite Type_Invariant[_Class] pragma as an Invariant pragma,
22984 -- setting Class_Present for the Type_Invariant_Class case.
22986 Set_Class_Present (N, Prag_Id = Pragma_Type_Invariant_Class);
22987 I_Pragma := New_Copy (N);
22988 Set_Pragma_Identifier
22989 (I_Pragma, Make_Identifier (Loc, Name_Invariant));
22990 Rewrite (N, I_Pragma);
22991 Set_Analyzed (N, False);
22992 Analyze (N);
22993 end Type_Invariant;
22995 ---------------------
22996 -- Unchecked_Union --
22997 ---------------------
22999 -- pragma Unchecked_Union (first_subtype_LOCAL_NAME)
23001 when Pragma_Unchecked_Union => Unchecked_Union : declare
23002 Assoc : constant Node_Id := Arg1;
23003 Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
23004 Clist : Node_Id;
23005 Comp : Node_Id;
23006 Tdef : Node_Id;
23007 Typ : Entity_Id;
23008 Variant : Node_Id;
23009 Vpart : Node_Id;
23011 begin
23012 Ada_2005_Pragma;
23013 Check_No_Identifiers;
23014 Check_Arg_Count (1);
23015 Check_Arg_Is_Local_Name (Arg1);
23017 Find_Type (Type_Id);
23019 Typ := Entity (Type_Id);
23021 -- A pragma that applies to a Ghost entity becomes Ghost for the
23022 -- purposes of legality checks and removal of ignored Ghost code.
23024 Mark_Ghost_Pragma (N, Typ);
23026 if Typ = Any_Type
23027 or else Rep_Item_Too_Early (Typ, N)
23028 then
23029 return;
23030 else
23031 Typ := Underlying_Type (Typ);
23032 end if;
23034 if Rep_Item_Too_Late (Typ, N) then
23035 return;
23036 end if;
23038 Check_First_Subtype (Arg1);
23040 -- Note remaining cases are references to a type in the current
23041 -- declarative part. If we find an error, we post the error on
23042 -- the relevant type declaration at an appropriate point.
23044 if not Is_Record_Type (Typ) then
23045 Error_Msg_N ("unchecked union must be record type", Typ);
23046 return;
23048 elsif Is_Tagged_Type (Typ) then
23049 Error_Msg_N ("unchecked union must not be tagged", Typ);
23050 return;
23052 elsif not Has_Discriminants (Typ) then
23053 Error_Msg_N
23054 ("unchecked union must have one discriminant", Typ);
23055 return;
23057 -- Note: in previous versions of GNAT we used to check for limited
23058 -- types and give an error, but in fact the standard does allow
23059 -- Unchecked_Union on limited types, so this check was removed.
23061 -- Similarly, GNAT used to require that all discriminants have
23062 -- default values, but this is not mandated by the RM.
23064 -- Proceed with basic error checks completed
23066 else
23067 Tdef := Type_Definition (Declaration_Node (Typ));
23068 Clist := Component_List (Tdef);
23070 -- Check presence of component list and variant part
23072 if No (Clist) or else No (Variant_Part (Clist)) then
23073 Error_Msg_N
23074 ("unchecked union must have variant part", Tdef);
23075 return;
23076 end if;
23078 -- Check components
23080 Comp := First (Component_Items (Clist));
23081 while Present (Comp) loop
23082 Check_Component (Comp, Typ);
23083 Next (Comp);
23084 end loop;
23086 -- Check variant part
23088 Vpart := Variant_Part (Clist);
23090 Variant := First (Variants (Vpart));
23091 while Present (Variant) loop
23092 Check_Variant (Variant, Typ);
23093 Next (Variant);
23094 end loop;
23095 end if;
23097 Set_Is_Unchecked_Union (Typ);
23098 Set_Convention (Typ, Convention_C);
23099 Set_Has_Unchecked_Union (Base_Type (Typ));
23100 Set_Is_Unchecked_Union (Base_Type (Typ));
23101 end Unchecked_Union;
23103 ----------------------------
23104 -- Unevaluated_Use_Of_Old --
23105 ----------------------------
23107 -- pragma Unevaluated_Use_Of_Old (Error | Warn | Allow);
23109 when Pragma_Unevaluated_Use_Of_Old =>
23110 GNAT_Pragma;
23111 Check_Arg_Count (1);
23112 Check_No_Identifiers;
23113 Check_Arg_Is_One_Of (Arg1, Name_Error, Name_Warn, Name_Allow);
23115 -- Suppress/Unsuppress can appear as a configuration pragma, or in
23116 -- a declarative part or a package spec.
23118 if not Is_Configuration_Pragma then
23119 Check_Is_In_Decl_Part_Or_Package_Spec;
23120 end if;
23122 -- Store proper setting of Uneval_Old
23124 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
23125 Uneval_Old := Fold_Upper (Name_Buffer (1));
23127 ------------------------
23128 -- Unimplemented_Unit --
23129 ------------------------
23131 -- pragma Unimplemented_Unit;
23133 -- Note: this only gives an error if we are generating code, or if
23134 -- we are in a generic library unit (where the pragma appears in the
23135 -- body, not in the spec).
23137 when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
23138 Cunitent : constant Entity_Id :=
23139 Cunit_Entity (Get_Source_Unit (Loc));
23140 Ent_Kind : constant Entity_Kind := Ekind (Cunitent);
23142 begin
23143 GNAT_Pragma;
23144 Check_Arg_Count (0);
23146 if Operating_Mode = Generate_Code
23147 or else Ent_Kind = E_Generic_Function
23148 or else Ent_Kind = E_Generic_Procedure
23149 or else Ent_Kind = E_Generic_Package
23150 then
23151 Get_Name_String (Chars (Cunitent));
23152 Set_Casing (Mixed_Case);
23153 Write_Str (Name_Buffer (1 .. Name_Len));
23154 Write_Str (" is not supported in this configuration");
23155 Write_Eol;
23156 raise Unrecoverable_Error;
23157 end if;
23158 end Unimplemented_Unit;
23160 ------------------------
23161 -- Universal_Aliasing --
23162 ------------------------
23164 -- pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
23166 when Pragma_Universal_Aliasing => Universal_Alias : declare
23167 E_Id : Entity_Id;
23169 begin
23170 GNAT_Pragma;
23171 Check_Arg_Count (1);
23172 Check_Optional_Identifier (Arg2, Name_Entity);
23173 Check_Arg_Is_Local_Name (Arg1);
23174 E_Id := Entity (Get_Pragma_Arg (Arg1));
23176 if E_Id = Any_Type then
23177 return;
23178 elsif No (E_Id) or else not Is_Type (E_Id) then
23179 Error_Pragma_Arg ("pragma% requires type", Arg1);
23180 end if;
23182 -- A pragma that applies to a Ghost entity becomes Ghost for the
23183 -- purposes of legality checks and removal of ignored Ghost code.
23185 Mark_Ghost_Pragma (N, E_Id);
23186 Set_Universal_Aliasing (Implementation_Base_Type (E_Id));
23187 Record_Rep_Item (E_Id, N);
23188 end Universal_Alias;
23190 --------------------
23191 -- Universal_Data --
23192 --------------------
23194 -- pragma Universal_Data [(library_unit_NAME)];
23196 when Pragma_Universal_Data =>
23197 GNAT_Pragma;
23198 Error_Pragma ("??pragma% ignored (applies only to AAMP)");
23200 ----------------
23201 -- Unmodified --
23202 ----------------
23204 -- pragma Unmodified (LOCAL_NAME {, LOCAL_NAME});
23206 when Pragma_Unmodified =>
23207 Analyze_Unmodified_Or_Unused;
23209 ------------------
23210 -- Unreferenced --
23211 ------------------
23213 -- pragma Unreferenced (LOCAL_NAME {, LOCAL_NAME});
23215 -- or when used in a context clause:
23217 -- pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
23219 when Pragma_Unreferenced =>
23220 Analyze_Unreferenced_Or_Unused;
23222 --------------------------
23223 -- Unreferenced_Objects --
23224 --------------------------
23226 -- pragma Unreferenced_Objects (LOCAL_NAME {, LOCAL_NAME});
23228 when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
23229 Arg : Node_Id;
23230 Arg_Expr : Node_Id;
23231 Arg_Id : Entity_Id;
23233 Ghost_Error_Posted : Boolean := False;
23234 -- Flag set when an error concerning the illegal mix of Ghost and
23235 -- non-Ghost types is emitted.
23237 Ghost_Id : Entity_Id := Empty;
23238 -- The entity of the first Ghost type encountered while processing
23239 -- the arguments of the pragma.
23241 begin
23242 GNAT_Pragma;
23243 Check_At_Least_N_Arguments (1);
23245 Arg := Arg1;
23246 while Present (Arg) loop
23247 Check_No_Identifier (Arg);
23248 Check_Arg_Is_Local_Name (Arg);
23249 Arg_Expr := Get_Pragma_Arg (Arg);
23251 if Is_Entity_Name (Arg_Expr) then
23252 Arg_Id := Entity (Arg_Expr);
23254 if Is_Type (Arg_Id) then
23255 Set_Has_Pragma_Unreferenced_Objects (Arg_Id);
23257 -- A pragma that applies to a Ghost entity becomes Ghost
23258 -- for the purposes of legality checks and removal of
23259 -- ignored Ghost code.
23261 Mark_Ghost_Pragma (N, Arg_Id);
23263 -- Capture the entity of the first Ghost type being
23264 -- processed for error detection purposes.
23266 if Is_Ghost_Entity (Arg_Id) then
23267 if No (Ghost_Id) then
23268 Ghost_Id := Arg_Id;
23269 end if;
23271 -- Otherwise the type is non-Ghost. It is illegal to mix
23272 -- references to Ghost and non-Ghost entities
23273 -- (SPARK RM 6.9).
23275 elsif Present (Ghost_Id)
23276 and then not Ghost_Error_Posted
23277 then
23278 Ghost_Error_Posted := True;
23280 Error_Msg_Name_1 := Pname;
23281 Error_Msg_N
23282 ("pragma % cannot mention ghost and non-ghost types",
23285 Error_Msg_Sloc := Sloc (Ghost_Id);
23286 Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
23288 Error_Msg_Sloc := Sloc (Arg_Id);
23289 Error_Msg_NE ("\& # declared as non-ghost", N, Arg_Id);
23290 end if;
23291 else
23292 Error_Pragma_Arg
23293 ("argument for pragma% must be type or subtype", Arg);
23294 end if;
23295 else
23296 Error_Pragma_Arg
23297 ("argument for pragma% must be type or subtype", Arg);
23298 end if;
23300 Next (Arg);
23301 end loop;
23302 end Unreferenced_Objects;
23304 ------------------------------
23305 -- Unreserve_All_Interrupts --
23306 ------------------------------
23308 -- pragma Unreserve_All_Interrupts;
23310 when Pragma_Unreserve_All_Interrupts =>
23311 GNAT_Pragma;
23312 Check_Arg_Count (0);
23314 if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
23315 Unreserve_All_Interrupts := True;
23316 end if;
23318 ----------------
23319 -- Unsuppress --
23320 ----------------
23322 -- pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
23324 when Pragma_Unsuppress =>
23325 Ada_2005_Pragma;
23326 Process_Suppress_Unsuppress (Suppress_Case => False);
23328 ------------
23329 -- Unused --
23330 ------------
23332 -- pragma Unused (LOCAL_NAME {, LOCAL_NAME});
23334 when Pragma_Unused =>
23335 Analyze_Unmodified_Or_Unused (Is_Unused => True);
23336 Analyze_Unreferenced_Or_Unused (Is_Unused => True);
23338 -------------------
23339 -- Use_VADS_Size --
23340 -------------------
23342 -- pragma Use_VADS_Size;
23344 when Pragma_Use_VADS_Size =>
23345 GNAT_Pragma;
23346 Check_Arg_Count (0);
23347 Check_Valid_Configuration_Pragma;
23348 Use_VADS_Size := True;
23350 ---------------------
23351 -- Validity_Checks --
23352 ---------------------
23354 -- pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
23356 when Pragma_Validity_Checks => Validity_Checks : declare
23357 A : constant Node_Id := Get_Pragma_Arg (Arg1);
23358 S : String_Id;
23359 C : Char_Code;
23361 begin
23362 GNAT_Pragma;
23363 Check_Arg_Count (1);
23364 Check_No_Identifiers;
23366 -- Pragma always active unless in CodePeer or GNATprove modes,
23367 -- which use a fixed configuration of validity checks.
23369 if not (CodePeer_Mode or GNATprove_Mode) then
23370 if Nkind (A) = N_String_Literal then
23371 S := Strval (A);
23373 declare
23374 Slen : constant Natural := Natural (String_Length (S));
23375 Options : String (1 .. Slen);
23376 J : Positive;
23378 begin
23379 -- Couldn't we use a for loop here over Options'Range???
23381 J := 1;
23382 loop
23383 C := Get_String_Char (S, Pos (J));
23385 -- This is a weird test, it skips setting validity
23386 -- checks entirely if any element of S is out of
23387 -- range of Character, what is that about ???
23389 exit when not In_Character_Range (C);
23390 Options (J) := Get_Character (C);
23392 if J = Slen then
23393 Set_Validity_Check_Options (Options);
23394 exit;
23395 else
23396 J := J + 1;
23397 end if;
23398 end loop;
23399 end;
23401 elsif Nkind (A) = N_Identifier then
23402 if Chars (A) = Name_All_Checks then
23403 Set_Validity_Check_Options ("a");
23404 elsif Chars (A) = Name_On then
23405 Validity_Checks_On := True;
23406 elsif Chars (A) = Name_Off then
23407 Validity_Checks_On := False;
23408 end if;
23409 end if;
23410 end if;
23411 end Validity_Checks;
23413 --------------
23414 -- Volatile --
23415 --------------
23417 -- pragma Volatile (LOCAL_NAME);
23419 when Pragma_Volatile =>
23420 Process_Atomic_Independent_Shared_Volatile;
23422 -------------------------
23423 -- Volatile_Components --
23424 -------------------------
23426 -- pragma Volatile_Components (array_LOCAL_NAME);
23428 -- Volatile is handled by the same circuit as Atomic_Components
23430 --------------------------
23431 -- Volatile_Full_Access --
23432 --------------------------
23434 -- pragma Volatile_Full_Access (LOCAL_NAME);
23436 when Pragma_Volatile_Full_Access =>
23437 GNAT_Pragma;
23438 Process_Atomic_Independent_Shared_Volatile;
23440 -----------------------
23441 -- Volatile_Function --
23442 -----------------------
23444 -- pragma Volatile_Function [ (boolean_EXPRESSION) ];
23446 when Pragma_Volatile_Function => Volatile_Function : declare
23447 Over_Id : Entity_Id;
23448 Spec_Id : Entity_Id;
23449 Subp_Decl : Node_Id;
23451 begin
23452 GNAT_Pragma;
23453 Check_No_Identifiers;
23454 Check_At_Most_N_Arguments (1);
23456 Subp_Decl :=
23457 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
23459 -- Generic subprogram
23461 if Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
23462 null;
23464 -- Body acts as spec
23466 elsif Nkind (Subp_Decl) = N_Subprogram_Body
23467 and then No (Corresponding_Spec (Subp_Decl))
23468 then
23469 null;
23471 -- Body stub acts as spec
23473 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
23474 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
23475 then
23476 null;
23478 -- Subprogram
23480 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
23481 null;
23483 else
23484 Pragma_Misplaced;
23485 return;
23486 end if;
23488 Spec_Id := Unique_Defining_Entity (Subp_Decl);
23490 if not Ekind_In (Spec_Id, E_Function, E_Generic_Function) then
23491 Pragma_Misplaced;
23492 return;
23493 end if;
23495 -- A pragma that applies to a Ghost entity becomes Ghost for the
23496 -- purposes of legality checks and removal of ignored Ghost code.
23498 Mark_Ghost_Pragma (N, Spec_Id);
23500 -- Chain the pragma on the contract for completeness
23502 Add_Contract_Item (N, Spec_Id);
23504 -- The legality checks of pragma Volatile_Function are affected by
23505 -- the SPARK mode in effect. Analyze all pragmas in a specific
23506 -- order.
23508 Analyze_If_Present (Pragma_SPARK_Mode);
23510 -- A volatile function cannot override a non-volatile function
23511 -- (SPARK RM 7.1.2(15)). Overriding checks are usually performed
23512 -- in New_Overloaded_Entity, however at that point the pragma has
23513 -- not been processed yet.
23515 Over_Id := Overridden_Operation (Spec_Id);
23517 if Present (Over_Id)
23518 and then not Is_Volatile_Function (Over_Id)
23519 then
23520 Error_Msg_N
23521 ("incompatible volatile function values in effect", Spec_Id);
23523 Error_Msg_Sloc := Sloc (Over_Id);
23524 Error_Msg_N
23525 ("\& declared # with Volatile_Function value False",
23526 Spec_Id);
23528 Error_Msg_Sloc := Sloc (Spec_Id);
23529 Error_Msg_N
23530 ("\overridden # with Volatile_Function value True",
23531 Spec_Id);
23532 end if;
23534 -- Analyze the Boolean expression (if any)
23536 if Present (Arg1) then
23537 Check_Static_Boolean_Expression (Get_Pragma_Arg (Arg1));
23538 end if;
23539 end Volatile_Function;
23541 ----------------------
23542 -- Warning_As_Error --
23543 ----------------------
23545 -- pragma Warning_As_Error (static_string_EXPRESSION);
23547 when Pragma_Warning_As_Error =>
23548 GNAT_Pragma;
23549 Check_Arg_Count (1);
23550 Check_No_Identifiers;
23551 Check_Valid_Configuration_Pragma;
23553 if not Is_Static_String_Expression (Arg1) then
23554 Error_Pragma_Arg
23555 ("argument of pragma% must be static string expression",
23556 Arg1);
23558 -- OK static string expression
23560 else
23561 Acquire_Warning_Match_String (Arg1);
23562 Warnings_As_Errors_Count := Warnings_As_Errors_Count + 1;
23563 Warnings_As_Errors (Warnings_As_Errors_Count) :=
23564 new String'(Name_Buffer (1 .. Name_Len));
23565 end if;
23567 --------------
23568 -- Warnings --
23569 --------------
23571 -- pragma Warnings ([TOOL_NAME,] DETAILS [, REASON]);
23573 -- DETAILS ::= On | Off
23574 -- DETAILS ::= On | Off, local_NAME
23575 -- DETAILS ::= static_string_EXPRESSION
23576 -- DETAILS ::= On | Off, static_string_EXPRESSION
23578 -- TOOL_NAME ::= GNAT | GNATProve
23580 -- REASON ::= Reason => STRING_LITERAL {& STRING_LITERAL}
23582 -- Note: If the first argument matches an allowed tool name, it is
23583 -- always considered to be a tool name, even if there is a string
23584 -- variable of that name.
23586 -- Note if the second argument of DETAILS is a local_NAME then the
23587 -- second form is always understood. If the intention is to use
23588 -- the fourth form, then you can write NAME & "" to force the
23589 -- intepretation as a static_string_EXPRESSION.
23591 when Pragma_Warnings => Warnings : declare
23592 Reason : String_Id;
23594 begin
23595 GNAT_Pragma;
23596 Check_At_Least_N_Arguments (1);
23598 -- See if last argument is labeled Reason. If so, make sure we
23599 -- have a string literal or a concatenation of string literals,
23600 -- and acquire the REASON string. Then remove the REASON argument
23601 -- by decreasing Num_Args by one; Remaining processing looks only
23602 -- at first Num_Args arguments).
23604 declare
23605 Last_Arg : constant Node_Id :=
23606 Last (Pragma_Argument_Associations (N));
23608 begin
23609 if Nkind (Last_Arg) = N_Pragma_Argument_Association
23610 and then Chars (Last_Arg) = Name_Reason
23611 then
23612 Start_String;
23613 Get_Reason_String (Get_Pragma_Arg (Last_Arg));
23614 Reason := End_String;
23615 Arg_Count := Arg_Count - 1;
23617 -- Not allowed in compiler units (bootstrap issues)
23619 Check_Compiler_Unit ("Reason for pragma Warnings", N);
23621 -- No REASON string, set null string as reason
23623 else
23624 Reason := Null_String_Id;
23625 end if;
23626 end;
23628 -- Now proceed with REASON taken care of and eliminated
23630 Check_No_Identifiers;
23632 -- If debug flag -gnatd.i is set, pragma is ignored
23634 if Debug_Flag_Dot_I then
23635 return;
23636 end if;
23638 -- Process various forms of the pragma
23640 declare
23641 Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
23642 Shifted_Args : List_Id;
23644 begin
23645 -- See if first argument is a tool name, currently either
23646 -- GNAT or GNATprove. If so, either ignore the pragma if the
23647 -- tool used does not match, or continue as if no tool name
23648 -- was given otherwise, by shifting the arguments.
23650 if Nkind (Argx) = N_Identifier
23651 and then Nam_In (Chars (Argx), Name_Gnat, Name_Gnatprove)
23652 then
23653 if Chars (Argx) = Name_Gnat then
23654 if CodePeer_Mode or GNATprove_Mode or ASIS_Mode then
23655 Rewrite (N, Make_Null_Statement (Loc));
23656 Analyze (N);
23657 raise Pragma_Exit;
23658 end if;
23660 elsif Chars (Argx) = Name_Gnatprove then
23661 if not GNATprove_Mode then
23662 Rewrite (N, Make_Null_Statement (Loc));
23663 Analyze (N);
23664 raise Pragma_Exit;
23665 end if;
23667 else
23668 raise Program_Error;
23669 end if;
23671 -- At this point, the pragma Warnings applies to the tool,
23672 -- so continue with shifted arguments.
23674 Arg_Count := Arg_Count - 1;
23676 if Arg_Count = 1 then
23677 Shifted_Args := New_List (New_Copy (Arg2));
23678 elsif Arg_Count = 2 then
23679 Shifted_Args := New_List (New_Copy (Arg2),
23680 New_Copy (Arg3));
23681 elsif Arg_Count = 3 then
23682 Shifted_Args := New_List (New_Copy (Arg2),
23683 New_Copy (Arg3),
23684 New_Copy (Arg4));
23685 else
23686 raise Program_Error;
23687 end if;
23689 Rewrite (N,
23690 Make_Pragma (Loc,
23691 Chars => Name_Warnings,
23692 Pragma_Argument_Associations => Shifted_Args));
23693 Analyze (N);
23694 raise Pragma_Exit;
23695 end if;
23697 -- One argument case
23699 if Arg_Count = 1 then
23701 -- On/Off one argument case was processed by parser
23703 if Nkind (Argx) = N_Identifier
23704 and then Nam_In (Chars (Argx), Name_On, Name_Off)
23705 then
23706 null;
23708 -- One argument case must be ON/OFF or static string expr
23710 elsif not Is_Static_String_Expression (Arg1) then
23711 Error_Pragma_Arg
23712 ("argument of pragma% must be On/Off or static string "
23713 & "expression", Arg1);
23715 -- One argument string expression case
23717 else
23718 declare
23719 Lit : constant Node_Id := Expr_Value_S (Argx);
23720 Str : constant String_Id := Strval (Lit);
23721 Len : constant Nat := String_Length (Str);
23722 C : Char_Code;
23723 J : Nat;
23724 OK : Boolean;
23725 Chr : Character;
23727 begin
23728 J := 1;
23729 while J <= Len loop
23730 C := Get_String_Char (Str, J);
23731 OK := In_Character_Range (C);
23733 if OK then
23734 Chr := Get_Character (C);
23736 -- Dash case: only -Wxxx is accepted
23738 if J = 1
23739 and then J < Len
23740 and then Chr = '-'
23741 then
23742 J := J + 1;
23743 C := Get_String_Char (Str, J);
23744 Chr := Get_Character (C);
23745 exit when Chr = 'W';
23746 OK := False;
23748 -- Dot case
23750 elsif J < Len and then Chr = '.' then
23751 J := J + 1;
23752 C := Get_String_Char (Str, J);
23753 Chr := Get_Character (C);
23755 if not Set_Dot_Warning_Switch (Chr) then
23756 Error_Pragma_Arg
23757 ("invalid warning switch character "
23758 & '.' & Chr, Arg1);
23759 end if;
23761 -- Non-Dot case
23763 else
23764 OK := Set_Warning_Switch (Chr);
23765 end if;
23766 end if;
23768 if not OK then
23769 Error_Pragma_Arg
23770 ("invalid warning switch character " & Chr,
23771 Arg1);
23772 end if;
23774 J := J + 1;
23775 end loop;
23776 end;
23777 end if;
23779 -- Two or more arguments (must be two)
23781 else
23782 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
23783 Check_Arg_Count (2);
23785 declare
23786 E_Id : Node_Id;
23787 E : Entity_Id;
23788 Err : Boolean;
23790 begin
23791 E_Id := Get_Pragma_Arg (Arg2);
23792 Analyze (E_Id);
23794 -- In the expansion of an inlined body, a reference to
23795 -- the formal may be wrapped in a conversion if the
23796 -- actual is a conversion. Retrieve the real entity name.
23798 if (In_Instance_Body or In_Inlined_Body)
23799 and then Nkind (E_Id) = N_Unchecked_Type_Conversion
23800 then
23801 E_Id := Expression (E_Id);
23802 end if;
23804 -- Entity name case
23806 if Is_Entity_Name (E_Id) then
23807 E := Entity (E_Id);
23809 if E = Any_Id then
23810 return;
23811 else
23812 loop
23813 Set_Warnings_Off
23814 (E, (Chars (Get_Pragma_Arg (Arg1)) =
23815 Name_Off));
23817 -- For OFF case, make entry in warnings off
23818 -- pragma table for later processing. But we do
23819 -- not do that within an instance, since these
23820 -- warnings are about what is needed in the
23821 -- template, not an instance of it.
23823 if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
23824 and then Warn_On_Warnings_Off
23825 and then not In_Instance
23826 then
23827 Warnings_Off_Pragmas.Append ((N, E, Reason));
23828 end if;
23830 if Is_Enumeration_Type (E) then
23831 declare
23832 Lit : Entity_Id;
23833 begin
23834 Lit := First_Literal (E);
23835 while Present (Lit) loop
23836 Set_Warnings_Off (Lit);
23837 Next_Literal (Lit);
23838 end loop;
23839 end;
23840 end if;
23842 exit when No (Homonym (E));
23843 E := Homonym (E);
23844 end loop;
23845 end if;
23847 -- Error if not entity or static string expression case
23849 elsif not Is_Static_String_Expression (Arg2) then
23850 Error_Pragma_Arg
23851 ("second argument of pragma% must be entity name "
23852 & "or static string expression", Arg2);
23854 -- Static string expression case
23856 else
23857 Acquire_Warning_Match_String (Arg2);
23859 -- Note on configuration pragma case: If this is a
23860 -- configuration pragma, then for an OFF pragma, we
23861 -- just set Config True in the call, which is all
23862 -- that needs to be done. For the case of ON, this
23863 -- is normally an error, unless it is canceling the
23864 -- effect of a previous OFF pragma in the same file.
23865 -- In any other case, an error will be signalled (ON
23866 -- with no matching OFF).
23868 -- Note: We set Used if we are inside a generic to
23869 -- disable the test that the non-config case actually
23870 -- cancels a warning. That's because we can't be sure
23871 -- there isn't an instantiation in some other unit
23872 -- where a warning is suppressed.
23874 -- We could do a little better here by checking if the
23875 -- generic unit we are inside is public, but for now
23876 -- we don't bother with that refinement.
23878 if Chars (Argx) = Name_Off then
23879 Set_Specific_Warning_Off
23880 (Loc, Name_Buffer (1 .. Name_Len), Reason,
23881 Config => Is_Configuration_Pragma,
23882 Used => Inside_A_Generic or else In_Instance);
23884 elsif Chars (Argx) = Name_On then
23885 Set_Specific_Warning_On
23886 (Loc, Name_Buffer (1 .. Name_Len), Err);
23888 if Err then
23889 Error_Msg
23890 ("??pragma Warnings On with no matching "
23891 & "Warnings Off", Loc);
23892 end if;
23893 end if;
23894 end if;
23895 end;
23896 end if;
23897 end;
23898 end Warnings;
23900 -------------------
23901 -- Weak_External --
23902 -------------------
23904 -- pragma Weak_External ([Entity =>] LOCAL_NAME);
23906 when Pragma_Weak_External => Weak_External : declare
23907 Ent : Entity_Id;
23909 begin
23910 GNAT_Pragma;
23911 Check_Arg_Count (1);
23912 Check_Optional_Identifier (Arg1, Name_Entity);
23913 Check_Arg_Is_Library_Level_Local_Name (Arg1);
23914 Ent := Entity (Get_Pragma_Arg (Arg1));
23916 if Rep_Item_Too_Early (Ent, N) then
23917 return;
23918 else
23919 Ent := Underlying_Type (Ent);
23920 end if;
23922 -- The only processing required is to link this item on to the
23923 -- list of rep items for the given entity. This is accomplished
23924 -- by the call to Rep_Item_Too_Late (when no error is detected
23925 -- and False is returned).
23927 if Rep_Item_Too_Late (Ent, N) then
23928 return;
23929 else
23930 Set_Has_Gigi_Rep_Item (Ent);
23931 end if;
23932 end Weak_External;
23934 -----------------------------
23935 -- Wide_Character_Encoding --
23936 -----------------------------
23938 -- pragma Wide_Character_Encoding (IDENTIFIER);
23940 when Pragma_Wide_Character_Encoding =>
23941 GNAT_Pragma;
23943 -- Nothing to do, handled in parser. Note that we do not enforce
23944 -- configuration pragma placement, this pragma can appear at any
23945 -- place in the source, allowing mixed encodings within a single
23946 -- source program.
23948 null;
23950 --------------------
23951 -- Unknown_Pragma --
23952 --------------------
23954 -- Should be impossible, since the case of an unknown pragma is
23955 -- separately processed before the case statement is entered.
23957 when Unknown_Pragma =>
23958 raise Program_Error;
23959 end case;
23961 -- AI05-0144: detect dangerous order dependence. Disabled for now,
23962 -- until AI is formally approved.
23964 -- Check_Order_Dependence;
23966 exception
23967 when Pragma_Exit => null;
23968 end Analyze_Pragma;
23970 ---------------------------------------------
23971 -- Analyze_Pre_Post_Condition_In_Decl_Part --
23972 ---------------------------------------------
23974 -- WARNING: This routine manages Ghost regions. Return statements must be
23975 -- replaced by gotos which jump to the end of the routine and restore the
23976 -- Ghost mode.
23978 procedure Analyze_Pre_Post_Condition_In_Decl_Part
23979 (N : Node_Id;
23980 Freeze_Id : Entity_Id := Empty)
23982 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
23983 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
23985 Disp_Typ : Entity_Id;
23986 -- The dispatching type of the subprogram subject to the pre- or
23987 -- postcondition.
23989 function Check_References (Nod : Node_Id) return Traverse_Result;
23990 -- Check that expression Nod does not mention non-primitives of the
23991 -- type, global objects of the type, or other illegalities described
23992 -- and implied by AI12-0113.
23994 ----------------------
23995 -- Check_References --
23996 ----------------------
23998 function Check_References (Nod : Node_Id) return Traverse_Result is
23999 begin
24000 if Nkind (Nod) = N_Function_Call
24001 and then Is_Entity_Name (Name (Nod))
24002 then
24003 declare
24004 Func : constant Entity_Id := Entity (Name (Nod));
24005 Form : Entity_Id;
24007 begin
24008 -- An operation of the type must be a primitive
24010 if No (Find_Dispatching_Type (Func)) then
24011 Form := First_Formal (Func);
24012 while Present (Form) loop
24013 if Etype (Form) = Disp_Typ then
24014 Error_Msg_NE
24015 ("operation in class-wide condition must be "
24016 & "primitive of &", Nod, Disp_Typ);
24017 end if;
24019 Next_Formal (Form);
24020 end loop;
24022 -- A return object of the type is illegal as well
24024 if Etype (Func) = Disp_Typ
24025 or else Etype (Func) = Class_Wide_Type (Disp_Typ)
24026 then
24027 Error_Msg_NE
24028 ("operation in class-wide condition must be primitive "
24029 & "of &", Nod, Disp_Typ);
24030 end if;
24032 -- Otherwise we have a call to an overridden primitive, and we
24033 -- will create a common class-wide clone for the body of
24034 -- original operation and its eventual inherited versions. If
24035 -- the original operation dispatches on result it is never
24036 -- inherited and there is no need for a clone. There is not
24037 -- need for a clone either in GNATprove mode, as cases that
24038 -- would require it are rejected (when an inherited primitive
24039 -- calls an overridden operation in a class-wide contract), and
24040 -- the clone would make proof impossible in some cases.
24042 elsif not Is_Abstract_Subprogram (Spec_Id)
24043 and then No (Class_Wide_Clone (Spec_Id))
24044 and then not Has_Controlling_Result (Spec_Id)
24045 and then not GNATprove_Mode
24046 then
24047 Build_Class_Wide_Clone_Decl (Spec_Id);
24048 end if;
24049 end;
24051 elsif Is_Entity_Name (Nod)
24052 and then
24053 (Etype (Nod) = Disp_Typ
24054 or else Etype (Nod) = Class_Wide_Type (Disp_Typ))
24055 and then Ekind_In (Entity (Nod), E_Constant, E_Variable)
24056 then
24057 Error_Msg_NE
24058 ("object in class-wide condition must be formal of type &",
24059 Nod, Disp_Typ);
24061 elsif Nkind (Nod) = N_Explicit_Dereference
24062 and then (Etype (Nod) = Disp_Typ
24063 or else Etype (Nod) = Class_Wide_Type (Disp_Typ))
24064 and then (not Is_Entity_Name (Prefix (Nod))
24065 or else not Is_Formal (Entity (Prefix (Nod))))
24066 then
24067 Error_Msg_NE
24068 ("operation in class-wide condition must be primitive of &",
24069 Nod, Disp_Typ);
24070 end if;
24072 return OK;
24073 end Check_References;
24075 procedure Check_Class_Wide_Condition is
24076 new Traverse_Proc (Check_References);
24078 -- Local variables
24080 Expr : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
24081 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
24082 -- Save the Ghost mode to restore on exit
24084 Errors : Nat;
24085 Restore_Scope : Boolean := False;
24087 -- Start of processing for Analyze_Pre_Post_Condition_In_Decl_Part
24089 begin
24090 -- Do not analyze the pragma multiple times
24092 if Is_Analyzed_Pragma (N) then
24093 return;
24094 end if;
24096 -- Set the Ghost mode in effect from the pragma. Due to the delayed
24097 -- analysis of the pragma, the Ghost mode at point of declaration and
24098 -- point of analysis may not necessarily be the same. Use the mode in
24099 -- effect at the point of declaration.
24101 Set_Ghost_Mode (N);
24103 -- Ensure that the subprogram and its formals are visible when analyzing
24104 -- the expression of the pragma.
24106 if not In_Open_Scopes (Spec_Id) then
24107 Restore_Scope := True;
24108 Push_Scope (Spec_Id);
24110 if Is_Generic_Subprogram (Spec_Id) then
24111 Install_Generic_Formals (Spec_Id);
24112 else
24113 Install_Formals (Spec_Id);
24114 end if;
24115 end if;
24117 Errors := Serious_Errors_Detected;
24118 Preanalyze_Assert_Expression (Expr, Standard_Boolean);
24120 -- Emit a clarification message when the expression contains at least
24121 -- one undefined reference, possibly due to contract "freezing".
24123 if Errors /= Serious_Errors_Detected
24124 and then Present (Freeze_Id)
24125 and then Has_Undefined_Reference (Expr)
24126 then
24127 Contract_Freeze_Error (Spec_Id, Freeze_Id);
24128 end if;
24130 if Class_Present (N) then
24132 -- Verify that a class-wide condition is legal, i.e. the operation is
24133 -- a primitive of a tagged type. Note that a generic subprogram is
24134 -- not a primitive operation.
24136 Disp_Typ := Find_Dispatching_Type (Spec_Id);
24138 if No (Disp_Typ) or else Is_Generic_Subprogram (Spec_Id) then
24139 Error_Msg_Name_1 := Original_Aspect_Pragma_Name (N);
24141 if From_Aspect_Specification (N) then
24142 Error_Msg_N
24143 ("aspect % can only be specified for a primitive operation "
24144 & "of a tagged type", Corresponding_Aspect (N));
24146 -- The pragma is a source construct
24148 else
24149 Error_Msg_N
24150 ("pragma % can only be specified for a primitive operation "
24151 & "of a tagged type", N);
24152 end if;
24154 -- Remaining semantic checks require a full tree traversal
24156 else
24157 Check_Class_Wide_Condition (Expr);
24158 end if;
24160 end if;
24162 if Restore_Scope then
24163 End_Scope;
24164 end if;
24166 -- If analysis of the condition indicates that a class-wide clone
24167 -- has been created, build and analyze its declaration.
24169 if Is_Subprogram (Spec_Id)
24170 and then Present (Class_Wide_Clone (Spec_Id))
24171 then
24172 Analyze (Unit_Declaration_Node (Class_Wide_Clone (Spec_Id)));
24173 end if;
24175 -- Currently it is not possible to inline pre/postconditions on a
24176 -- subprogram subject to pragma Inline_Always.
24178 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
24179 Set_Is_Analyzed_Pragma (N);
24181 Restore_Ghost_Mode (Saved_GM);
24182 end Analyze_Pre_Post_Condition_In_Decl_Part;
24184 ------------------------------------------
24185 -- Analyze_Refined_Depends_In_Decl_Part --
24186 ------------------------------------------
24188 procedure Analyze_Refined_Depends_In_Decl_Part (N : Node_Id) is
24189 procedure Check_Dependency_Clause
24190 (Spec_Id : Entity_Id;
24191 Dep_Clause : Node_Id;
24192 Dep_States : Elist_Id;
24193 Refinements : List_Id;
24194 Matched_Items : in out Elist_Id);
24195 -- Try to match a single dependency clause Dep_Clause against one or
24196 -- more refinement clauses found in list Refinements. Each successful
24197 -- match eliminates at least one refinement clause from Refinements.
24198 -- Spec_Id denotes the entity of the related subprogram. Dep_States
24199 -- denotes the entities of all abstract states which appear in pragma
24200 -- Depends. Matched_Items contains the entities of all successfully
24201 -- matched items found in pragma Depends.
24203 procedure Check_Output_States
24204 (Spec_Id : Entity_Id;
24205 Spec_Inputs : Elist_Id;
24206 Spec_Outputs : Elist_Id;
24207 Body_Inputs : Elist_Id;
24208 Body_Outputs : Elist_Id);
24209 -- Determine whether pragma Depends contains an output state with a
24210 -- visible refinement and if so, ensure that pragma Refined_Depends
24211 -- mentions all its constituents as outputs. Spec_Id is the entity of
24212 -- the related subprograms. Spec_Inputs and Spec_Outputs denote the
24213 -- inputs and outputs of the subprogram spec synthesized from pragma
24214 -- Depends. Body_Inputs and Body_Outputs denote the inputs and outputs
24215 -- of the subprogram body synthesized from pragma Refined_Depends.
24217 function Collect_States (Clauses : List_Id) return Elist_Id;
24218 -- Given a normalized list of dependencies obtained from calling
24219 -- Normalize_Clauses, return a list containing the entities of all
24220 -- states appearing in dependencies. It helps in checking refinements
24221 -- involving a state and a corresponding constituent which is not a
24222 -- direct constituent of the state.
24224 procedure Normalize_Clauses (Clauses : List_Id);
24225 -- Given a list of dependence or refinement clauses Clauses, normalize
24226 -- each clause by creating multiple dependencies with exactly one input
24227 -- and one output.
24229 procedure Remove_Extra_Clauses
24230 (Clauses : List_Id;
24231 Matched_Items : Elist_Id);
24232 -- Given a list of refinement clauses Clauses, remove all clauses whose
24233 -- inputs and/or outputs have been previously matched. See the body for
24234 -- all special cases. Matched_Items contains the entities of all matched
24235 -- items found in pragma Depends.
24237 procedure Report_Extra_Clauses
24238 (Spec_Id : Entity_Id;
24239 Clauses : List_Id);
24240 -- Emit an error for each extra clause found in list Clauses. Spec_Id
24241 -- denotes the entity of the related subprogram.
24243 -----------------------------
24244 -- Check_Dependency_Clause --
24245 -----------------------------
24247 procedure Check_Dependency_Clause
24248 (Spec_Id : Entity_Id;
24249 Dep_Clause : Node_Id;
24250 Dep_States : Elist_Id;
24251 Refinements : List_Id;
24252 Matched_Items : in out Elist_Id)
24254 Dep_Input : constant Node_Id := Expression (Dep_Clause);
24255 Dep_Output : constant Node_Id := First (Choices (Dep_Clause));
24257 function Is_Already_Matched (Dep_Item : Node_Id) return Boolean;
24258 -- Determine whether dependency item Dep_Item has been matched in a
24259 -- previous clause.
24261 function Is_In_Out_State_Clause return Boolean;
24262 -- Determine whether dependence clause Dep_Clause denotes an abstract
24263 -- state that depends on itself (State => State).
24265 function Is_Null_Refined_State (Item : Node_Id) return Boolean;
24266 -- Determine whether item Item denotes an abstract state with visible
24267 -- null refinement.
24269 procedure Match_Items
24270 (Dep_Item : Node_Id;
24271 Ref_Item : Node_Id;
24272 Matched : out Boolean);
24273 -- Try to match dependence item Dep_Item against refinement item
24274 -- Ref_Item. To match against a possible null refinement (see 2, 9),
24275 -- set Ref_Item to Empty. Flag Matched is set to True when one of
24276 -- the following conformance scenarios is in effect:
24277 -- 1) Both items denote null
24278 -- 2) Dep_Item denotes null and Ref_Item is Empty (special case)
24279 -- 3) Both items denote attribute 'Result
24280 -- 4) Both items denote the same object
24281 -- 5) Both items denote the same formal parameter
24282 -- 6) Both items denote the same current instance of a type
24283 -- 7) Both items denote the same discriminant
24284 -- 8) Dep_Item is an abstract state with visible null refinement
24285 -- and Ref_Item denotes null.
24286 -- 9) Dep_Item is an abstract state with visible null refinement
24287 -- and Ref_Item is Empty (special case).
24288 -- 10) Dep_Item is an abstract state with full or partial visible
24289 -- non-null refinement and Ref_Item denotes one of its
24290 -- constituents.
24291 -- 11) Dep_Item is an abstract state without a full visible
24292 -- refinement and Ref_Item denotes the same state.
24293 -- When scenario 10 is in effect, the entity of the abstract state
24294 -- denoted by Dep_Item is added to list Refined_States.
24296 procedure Record_Item (Item_Id : Entity_Id);
24297 -- Store the entity of an item denoted by Item_Id in Matched_Items
24299 ------------------------
24300 -- Is_Already_Matched --
24301 ------------------------
24303 function Is_Already_Matched (Dep_Item : Node_Id) return Boolean is
24304 Item_Id : Entity_Id := Empty;
24306 begin
24307 -- When the dependency item denotes attribute 'Result, check for
24308 -- the entity of the related subprogram.
24310 if Is_Attribute_Result (Dep_Item) then
24311 Item_Id := Spec_Id;
24313 elsif Is_Entity_Name (Dep_Item) then
24314 Item_Id := Available_View (Entity_Of (Dep_Item));
24315 end if;
24317 return
24318 Present (Item_Id) and then Contains (Matched_Items, Item_Id);
24319 end Is_Already_Matched;
24321 ----------------------------
24322 -- Is_In_Out_State_Clause --
24323 ----------------------------
24325 function Is_In_Out_State_Clause return Boolean is
24326 Dep_Input_Id : Entity_Id;
24327 Dep_Output_Id : Entity_Id;
24329 begin
24330 -- Detect the following clause:
24331 -- State => State
24333 if Is_Entity_Name (Dep_Input)
24334 and then Is_Entity_Name (Dep_Output)
24335 then
24336 -- Handle abstract views generated for limited with clauses
24338 Dep_Input_Id := Available_View (Entity_Of (Dep_Input));
24339 Dep_Output_Id := Available_View (Entity_Of (Dep_Output));
24341 return
24342 Ekind (Dep_Input_Id) = E_Abstract_State
24343 and then Dep_Input_Id = Dep_Output_Id;
24344 else
24345 return False;
24346 end if;
24347 end Is_In_Out_State_Clause;
24349 ---------------------------
24350 -- Is_Null_Refined_State --
24351 ---------------------------
24353 function Is_Null_Refined_State (Item : Node_Id) return Boolean is
24354 Item_Id : Entity_Id;
24356 begin
24357 if Is_Entity_Name (Item) then
24359 -- Handle abstract views generated for limited with clauses
24361 Item_Id := Available_View (Entity_Of (Item));
24363 return
24364 Ekind (Item_Id) = E_Abstract_State
24365 and then Has_Null_Visible_Refinement (Item_Id);
24366 else
24367 return False;
24368 end if;
24369 end Is_Null_Refined_State;
24371 -----------------
24372 -- Match_Items --
24373 -----------------
24375 procedure Match_Items
24376 (Dep_Item : Node_Id;
24377 Ref_Item : Node_Id;
24378 Matched : out Boolean)
24380 Dep_Item_Id : Entity_Id;
24381 Ref_Item_Id : Entity_Id;
24383 begin
24384 -- Assume that the two items do not match
24386 Matched := False;
24388 -- A null matches null or Empty (special case)
24390 if Nkind (Dep_Item) = N_Null
24391 and then (No (Ref_Item) or else Nkind (Ref_Item) = N_Null)
24392 then
24393 Matched := True;
24395 -- Attribute 'Result matches attribute 'Result
24397 elsif Is_Attribute_Result (Dep_Item)
24398 and then Is_Attribute_Result (Ref_Item)
24399 then
24400 -- Put the entity of the related function on the list of
24401 -- matched items because attribute 'Result does not carry
24402 -- an entity similar to states and constituents.
24404 Record_Item (Spec_Id);
24405 Matched := True;
24407 -- Abstract states, current instances of concurrent types,
24408 -- discriminants, formal parameters and objects.
24410 elsif Is_Entity_Name (Dep_Item) then
24412 -- Handle abstract views generated for limited with clauses
24414 Dep_Item_Id := Available_View (Entity_Of (Dep_Item));
24416 if Ekind (Dep_Item_Id) = E_Abstract_State then
24418 -- An abstract state with visible null refinement matches
24419 -- null or Empty (special case).
24421 if Has_Null_Visible_Refinement (Dep_Item_Id)
24422 and then (No (Ref_Item) or else Nkind (Ref_Item) = N_Null)
24423 then
24424 Record_Item (Dep_Item_Id);
24425 Matched := True;
24427 -- An abstract state with visible non-null refinement
24428 -- matches one of its constituents, or itself for an
24429 -- abstract state with partial visible refinement.
24431 elsif Has_Non_Null_Visible_Refinement (Dep_Item_Id) then
24432 if Is_Entity_Name (Ref_Item) then
24433 Ref_Item_Id := Entity_Of (Ref_Item);
24435 if Ekind_In (Ref_Item_Id, E_Abstract_State,
24436 E_Constant,
24437 E_Variable)
24438 and then Present (Encapsulating_State (Ref_Item_Id))
24439 and then Find_Encapsulating_State
24440 (Dep_States, Ref_Item_Id) = Dep_Item_Id
24441 then
24442 Record_Item (Dep_Item_Id);
24443 Matched := True;
24445 elsif not Has_Visible_Refinement (Dep_Item_Id)
24446 and then Ref_Item_Id = Dep_Item_Id
24447 then
24448 Record_Item (Dep_Item_Id);
24449 Matched := True;
24450 end if;
24451 end if;
24453 -- An abstract state without a visible refinement matches
24454 -- itself.
24456 elsif Is_Entity_Name (Ref_Item)
24457 and then Entity_Of (Ref_Item) = Dep_Item_Id
24458 then
24459 Record_Item (Dep_Item_Id);
24460 Matched := True;
24461 end if;
24463 -- A current instance of a concurrent type, discriminant,
24464 -- formal parameter or an object matches itself.
24466 elsif Is_Entity_Name (Ref_Item)
24467 and then Entity_Of (Ref_Item) = Dep_Item_Id
24468 then
24469 Record_Item (Dep_Item_Id);
24470 Matched := True;
24471 end if;
24472 end if;
24473 end Match_Items;
24475 -----------------
24476 -- Record_Item --
24477 -----------------
24479 procedure Record_Item (Item_Id : Entity_Id) is
24480 begin
24481 if No (Matched_Items) then
24482 Matched_Items := New_Elmt_List;
24483 end if;
24485 Append_Unique_Elmt (Item_Id, Matched_Items);
24486 end Record_Item;
24488 -- Local variables
24490 Clause_Matched : Boolean := False;
24491 Dummy : Boolean := False;
24492 Inputs_Match : Boolean;
24493 Next_Ref_Clause : Node_Id;
24494 Outputs_Match : Boolean;
24495 Ref_Clause : Node_Id;
24496 Ref_Input : Node_Id;
24497 Ref_Output : Node_Id;
24499 -- Start of processing for Check_Dependency_Clause
24501 begin
24502 -- Do not perform this check in an instance because it was already
24503 -- performed successfully in the generic template.
24505 if Is_Generic_Instance (Spec_Id) then
24506 return;
24507 end if;
24509 -- Examine all refinement clauses and compare them against the
24510 -- dependence clause.
24512 Ref_Clause := First (Refinements);
24513 while Present (Ref_Clause) loop
24514 Next_Ref_Clause := Next (Ref_Clause);
24516 -- Obtain the attributes of the current refinement clause
24518 Ref_Input := Expression (Ref_Clause);
24519 Ref_Output := First (Choices (Ref_Clause));
24521 -- The current refinement clause matches the dependence clause
24522 -- when both outputs match and both inputs match. See routine
24523 -- Match_Items for all possible conformance scenarios.
24525 -- Depends Dep_Output => Dep_Input
24526 -- ^ ^
24527 -- match ? match ?
24528 -- v v
24529 -- Refined_Depends Ref_Output => Ref_Input
24531 Match_Items
24532 (Dep_Item => Dep_Input,
24533 Ref_Item => Ref_Input,
24534 Matched => Inputs_Match);
24536 Match_Items
24537 (Dep_Item => Dep_Output,
24538 Ref_Item => Ref_Output,
24539 Matched => Outputs_Match);
24541 -- An In_Out state clause may be matched against a refinement with
24542 -- a null input or null output as long as the non-null side of the
24543 -- relation contains a valid constituent of the In_Out_State.
24545 if Is_In_Out_State_Clause then
24547 -- Depends => (State => State)
24548 -- Refined_Depends => (null => Constit) -- OK
24550 if Inputs_Match
24551 and then not Outputs_Match
24552 and then Nkind (Ref_Output) = N_Null
24553 then
24554 Outputs_Match := True;
24555 end if;
24557 -- Depends => (State => State)
24558 -- Refined_Depends => (Constit => null) -- OK
24560 if not Inputs_Match
24561 and then Outputs_Match
24562 and then Nkind (Ref_Input) = N_Null
24563 then
24564 Inputs_Match := True;
24565 end if;
24566 end if;
24568 -- The current refinement clause is legally constructed following
24569 -- the rules in SPARK RM 7.2.5, therefore it can be removed from
24570 -- the pool of candidates. The seach continues because a single
24571 -- dependence clause may have multiple matching refinements.
24573 if Inputs_Match and Outputs_Match then
24574 Clause_Matched := True;
24575 Remove (Ref_Clause);
24576 end if;
24578 Ref_Clause := Next_Ref_Clause;
24579 end loop;
24581 -- Depending on the order or composition of refinement clauses, an
24582 -- In_Out state clause may not be directly refinable.
24584 -- Refined_State => (State => (Constit_1, Constit_2))
24585 -- Depends => ((Output, State) => (Input, State))
24586 -- Refined_Depends => (Constit_1 => Input, Output => Constit_2)
24588 -- Matching normalized clause (State => State) fails because there is
24589 -- no direct refinement capable of satisfying this relation. Another
24590 -- similar case arises when clauses (Constit_1 => Input) and (Output
24591 -- => Constit_2) are matched first, leaving no candidates for clause
24592 -- (State => State). Both scenarios are legal as long as one of the
24593 -- previous clauses mentioned a valid constituent of State.
24595 if not Clause_Matched
24596 and then Is_In_Out_State_Clause
24597 and then Is_Already_Matched (Dep_Input)
24598 then
24599 Clause_Matched := True;
24600 end if;
24602 -- A clause where the input is an abstract state with visible null
24603 -- refinement or a 'Result attribute is implicitly matched when the
24604 -- output has already been matched in a previous clause.
24606 -- Refined_State => (State => null)
24607 -- Depends => (Output => State) -- implicitly OK
24608 -- Refined_Depends => (Output => ...)
24609 -- Depends => (...'Result => State) -- implicitly OK
24610 -- Refined_Depends => (...'Result => ...)
24612 if not Clause_Matched
24613 and then Is_Null_Refined_State (Dep_Input)
24614 and then Is_Already_Matched (Dep_Output)
24615 then
24616 Clause_Matched := True;
24617 end if;
24619 -- A clause where the output is an abstract state with visible null
24620 -- refinement is implicitly matched when the input has already been
24621 -- matched in a previous clause.
24623 -- Refined_State => (State => null)
24624 -- Depends => (State => Input) -- implicitly OK
24625 -- Refined_Depends => (... => Input)
24627 if not Clause_Matched
24628 and then Is_Null_Refined_State (Dep_Output)
24629 and then Is_Already_Matched (Dep_Input)
24630 then
24631 Clause_Matched := True;
24632 end if;
24634 -- At this point either all refinement clauses have been examined or
24635 -- pragma Refined_Depends contains a solitary null. Only an abstract
24636 -- state with null refinement can possibly match these cases.
24638 -- Refined_State => (State => null)
24639 -- Depends => (State => null)
24640 -- Refined_Depends => null -- OK
24642 if not Clause_Matched then
24643 Match_Items
24644 (Dep_Item => Dep_Input,
24645 Ref_Item => Empty,
24646 Matched => Inputs_Match);
24648 Match_Items
24649 (Dep_Item => Dep_Output,
24650 Ref_Item => Empty,
24651 Matched => Outputs_Match);
24653 Clause_Matched := Inputs_Match and Outputs_Match;
24654 end if;
24656 -- If the contents of Refined_Depends are legal, then the current
24657 -- dependence clause should be satisfied either by an explicit match
24658 -- or by one of the special cases.
24660 if not Clause_Matched then
24661 SPARK_Msg_NE
24662 (Fix_Msg (Spec_Id, "dependence clause of subprogram & has no "
24663 & "matching refinement in body"), Dep_Clause, Spec_Id);
24664 end if;
24665 end Check_Dependency_Clause;
24667 -------------------------
24668 -- Check_Output_States --
24669 -------------------------
24671 procedure Check_Output_States
24672 (Spec_Id : Entity_Id;
24673 Spec_Inputs : Elist_Id;
24674 Spec_Outputs : Elist_Id;
24675 Body_Inputs : Elist_Id;
24676 Body_Outputs : Elist_Id)
24678 procedure Check_Constituent_Usage (State_Id : Entity_Id);
24679 -- Determine whether all constituents of state State_Id with full
24680 -- visible refinement are used as outputs in pragma Refined_Depends.
24681 -- Emit an error if this is not the case (SPARK RM 7.2.4(5)).
24683 -----------------------------
24684 -- Check_Constituent_Usage --
24685 -----------------------------
24687 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
24688 Constits : constant Elist_Id :=
24689 Partial_Refinement_Constituents (State_Id);
24690 Constit_Elmt : Elmt_Id;
24691 Constit_Id : Entity_Id;
24692 Only_Partial : constant Boolean :=
24693 not Has_Visible_Refinement (State_Id);
24694 Posted : Boolean := False;
24696 begin
24697 if Present (Constits) then
24698 Constit_Elmt := First_Elmt (Constits);
24699 while Present (Constit_Elmt) loop
24700 Constit_Id := Node (Constit_Elmt);
24702 -- Issue an error when a constituent of State_Id is used,
24703 -- and State_Id has only partial visible refinement
24704 -- (SPARK RM 7.2.4(3d)).
24706 if Only_Partial then
24707 if (Present (Body_Inputs)
24708 and then Appears_In (Body_Inputs, Constit_Id))
24709 or else
24710 (Present (Body_Outputs)
24711 and then Appears_In (Body_Outputs, Constit_Id))
24712 then
24713 Error_Msg_Name_1 := Chars (State_Id);
24714 SPARK_Msg_NE
24715 ("constituent & of state % cannot be used in "
24716 & "dependence refinement", N, Constit_Id);
24717 Error_Msg_Name_1 := Chars (State_Id);
24718 SPARK_Msg_N ("\use state % instead", N);
24719 end if;
24721 -- The constituent acts as an input (SPARK RM 7.2.5(3))
24723 elsif Present (Body_Inputs)
24724 and then Appears_In (Body_Inputs, Constit_Id)
24725 then
24726 Error_Msg_Name_1 := Chars (State_Id);
24727 SPARK_Msg_NE
24728 ("constituent & of state % must act as output in "
24729 & "dependence refinement", N, Constit_Id);
24731 -- The constituent is altogether missing (SPARK RM 7.2.5(3))
24733 elsif No (Body_Outputs)
24734 or else not Appears_In (Body_Outputs, Constit_Id)
24735 then
24736 if not Posted then
24737 Posted := True;
24738 SPARK_Msg_NE
24739 ("output state & must be replaced by all its "
24740 & "constituents in dependence refinement",
24741 N, State_Id);
24742 end if;
24744 SPARK_Msg_NE
24745 ("\constituent & is missing in output list",
24746 N, Constit_Id);
24747 end if;
24749 Next_Elmt (Constit_Elmt);
24750 end loop;
24751 end if;
24752 end Check_Constituent_Usage;
24754 -- Local variables
24756 Item : Node_Id;
24757 Item_Elmt : Elmt_Id;
24758 Item_Id : Entity_Id;
24760 -- Start of processing for Check_Output_States
24762 begin
24763 -- Do not perform this check in an instance because it was already
24764 -- performed successfully in the generic template.
24766 if Is_Generic_Instance (Spec_Id) then
24767 null;
24769 -- Inspect the outputs of pragma Depends looking for a state with a
24770 -- visible refinement.
24772 elsif Present (Spec_Outputs) then
24773 Item_Elmt := First_Elmt (Spec_Outputs);
24774 while Present (Item_Elmt) loop
24775 Item := Node (Item_Elmt);
24777 -- Deal with the mixed nature of the input and output lists
24779 if Nkind (Item) = N_Defining_Identifier then
24780 Item_Id := Item;
24781 else
24782 Item_Id := Available_View (Entity_Of (Item));
24783 end if;
24785 if Ekind (Item_Id) = E_Abstract_State then
24787 -- The state acts as an input-output, skip it
24789 if Present (Spec_Inputs)
24790 and then Appears_In (Spec_Inputs, Item_Id)
24791 then
24792 null;
24794 -- Ensure that all of the constituents are utilized as
24795 -- outputs in pragma Refined_Depends.
24797 elsif Has_Non_Null_Visible_Refinement (Item_Id) then
24798 Check_Constituent_Usage (Item_Id);
24799 end if;
24800 end if;
24802 Next_Elmt (Item_Elmt);
24803 end loop;
24804 end if;
24805 end Check_Output_States;
24807 --------------------
24808 -- Collect_States --
24809 --------------------
24811 function Collect_States (Clauses : List_Id) return Elist_Id is
24812 procedure Collect_State
24813 (Item : Node_Id;
24814 States : in out Elist_Id);
24815 -- Add the entity of Item to list States when it denotes to a state
24817 -------------------
24818 -- Collect_State --
24819 -------------------
24821 procedure Collect_State
24822 (Item : Node_Id;
24823 States : in out Elist_Id)
24825 Id : Entity_Id;
24827 begin
24828 if Is_Entity_Name (Item) then
24829 Id := Entity_Of (Item);
24831 if Ekind (Id) = E_Abstract_State then
24832 if No (States) then
24833 States := New_Elmt_List;
24834 end if;
24836 Append_Unique_Elmt (Id, States);
24837 end if;
24838 end if;
24839 end Collect_State;
24841 -- Local variables
24843 Clause : Node_Id;
24844 Input : Node_Id;
24845 Output : Node_Id;
24846 States : Elist_Id := No_Elist;
24848 -- Start of processing for Collect_States
24850 begin
24851 Clause := First (Clauses);
24852 while Present (Clause) loop
24853 Input := Expression (Clause);
24854 Output := First (Choices (Clause));
24856 Collect_State (Input, States);
24857 Collect_State (Output, States);
24859 Next (Clause);
24860 end loop;
24862 return States;
24863 end Collect_States;
24865 -----------------------
24866 -- Normalize_Clauses --
24867 -----------------------
24869 procedure Normalize_Clauses (Clauses : List_Id) is
24870 procedure Normalize_Inputs (Clause : Node_Id);
24871 -- Normalize clause Clause by creating multiple clauses for each
24872 -- input item of Clause. It is assumed that Clause has exactly one
24873 -- output. The transformation is as follows:
24875 -- Output => (Input_1, Input_2) -- original
24877 -- Output => Input_1 -- normalizations
24878 -- Output => Input_2
24880 procedure Normalize_Outputs (Clause : Node_Id);
24881 -- Normalize clause Clause by creating multiple clause for each
24882 -- output item of Clause. The transformation is as follows:
24884 -- (Output_1, Output_2) => Input -- original
24886 -- Output_1 => Input -- normalization
24887 -- Output_2 => Input
24889 ----------------------
24890 -- Normalize_Inputs --
24891 ----------------------
24893 procedure Normalize_Inputs (Clause : Node_Id) is
24894 Inputs : constant Node_Id := Expression (Clause);
24895 Loc : constant Source_Ptr := Sloc (Clause);
24896 Output : constant List_Id := Choices (Clause);
24897 Last_Input : Node_Id;
24898 Input : Node_Id;
24899 New_Clause : Node_Id;
24900 Next_Input : Node_Id;
24902 begin
24903 -- Normalization is performed only when the original clause has
24904 -- more than one input. Multiple inputs appear as an aggregate.
24906 if Nkind (Inputs) = N_Aggregate then
24907 Last_Input := Last (Expressions (Inputs));
24909 -- Create a new clause for each input
24911 Input := First (Expressions (Inputs));
24912 while Present (Input) loop
24913 Next_Input := Next (Input);
24915 -- Unhook the current input from the original input list
24916 -- because it will be relocated to a new clause.
24918 Remove (Input);
24920 -- Special processing for the last input. At this point the
24921 -- original aggregate has been stripped down to one element.
24922 -- Replace the aggregate by the element itself.
24924 if Input = Last_Input then
24925 Rewrite (Inputs, Input);
24927 -- Generate a clause of the form:
24928 -- Output => Input
24930 else
24931 New_Clause :=
24932 Make_Component_Association (Loc,
24933 Choices => New_Copy_List_Tree (Output),
24934 Expression => Input);
24936 -- The new clause contains replicated content that has
24937 -- already been analyzed, mark the clause as analyzed.
24939 Set_Analyzed (New_Clause);
24940 Insert_After (Clause, New_Clause);
24941 end if;
24943 Input := Next_Input;
24944 end loop;
24945 end if;
24946 end Normalize_Inputs;
24948 -----------------------
24949 -- Normalize_Outputs --
24950 -----------------------
24952 procedure Normalize_Outputs (Clause : Node_Id) is
24953 Inputs : constant Node_Id := Expression (Clause);
24954 Loc : constant Source_Ptr := Sloc (Clause);
24955 Outputs : constant Node_Id := First (Choices (Clause));
24956 Last_Output : Node_Id;
24957 New_Clause : Node_Id;
24958 Next_Output : Node_Id;
24959 Output : Node_Id;
24961 begin
24962 -- Multiple outputs appear as an aggregate. Nothing to do when
24963 -- the clause has exactly one output.
24965 if Nkind (Outputs) = N_Aggregate then
24966 Last_Output := Last (Expressions (Outputs));
24968 -- Create a clause for each output. Note that each time a new
24969 -- clause is created, the original output list slowly shrinks
24970 -- until there is one item left.
24972 Output := First (Expressions (Outputs));
24973 while Present (Output) loop
24974 Next_Output := Next (Output);
24976 -- Unhook the output from the original output list as it
24977 -- will be relocated to a new clause.
24979 Remove (Output);
24981 -- Special processing for the last output. At this point
24982 -- the original aggregate has been stripped down to one
24983 -- element. Replace the aggregate by the element itself.
24985 if Output = Last_Output then
24986 Rewrite (Outputs, Output);
24988 else
24989 -- Generate a clause of the form:
24990 -- (Output => Inputs)
24992 New_Clause :=
24993 Make_Component_Association (Loc,
24994 Choices => New_List (Output),
24995 Expression => New_Copy_Tree (Inputs));
24997 -- The new clause contains replicated content that has
24998 -- already been analyzed. There is not need to reanalyze
24999 -- them.
25001 Set_Analyzed (New_Clause);
25002 Insert_After (Clause, New_Clause);
25003 end if;
25005 Output := Next_Output;
25006 end loop;
25007 end if;
25008 end Normalize_Outputs;
25010 -- Local variables
25012 Clause : Node_Id;
25014 -- Start of processing for Normalize_Clauses
25016 begin
25017 Clause := First (Clauses);
25018 while Present (Clause) loop
25019 Normalize_Outputs (Clause);
25020 Next (Clause);
25021 end loop;
25023 Clause := First (Clauses);
25024 while Present (Clause) loop
25025 Normalize_Inputs (Clause);
25026 Next (Clause);
25027 end loop;
25028 end Normalize_Clauses;
25030 --------------------------
25031 -- Remove_Extra_Clauses --
25032 --------------------------
25034 procedure Remove_Extra_Clauses
25035 (Clauses : List_Id;
25036 Matched_Items : Elist_Id)
25038 Clause : Node_Id;
25039 Input : Node_Id;
25040 Input_Id : Entity_Id;
25041 Next_Clause : Node_Id;
25042 Output : Node_Id;
25043 State_Id : Entity_Id;
25045 begin
25046 Clause := First (Clauses);
25047 while Present (Clause) loop
25048 Next_Clause := Next (Clause);
25050 Input := Expression (Clause);
25051 Output := First (Choices (Clause));
25053 -- Recognize a clause of the form
25055 -- null => Input
25057 -- where Input is a constituent of a state which was already
25058 -- successfully matched. This clause must be removed because it
25059 -- simply indicates that some of the constituents of the state
25060 -- are not used.
25062 -- Refined_State => (State => (Constit_1, Constit_2))
25063 -- Depends => (Output => State)
25064 -- Refined_Depends => ((Output => Constit_1), -- State matched
25065 -- (null => Constit_2)) -- OK
25067 if Nkind (Output) = N_Null and then Is_Entity_Name (Input) then
25069 -- Handle abstract views generated for limited with clauses
25071 Input_Id := Available_View (Entity_Of (Input));
25073 -- The input must be a constituent of a state
25075 if Ekind_In (Input_Id, E_Abstract_State,
25076 E_Constant,
25077 E_Variable)
25078 and then Present (Encapsulating_State (Input_Id))
25079 then
25080 State_Id := Encapsulating_State (Input_Id);
25082 -- The state must have a non-null visible refinement and be
25083 -- matched in a previous clause.
25085 if Has_Non_Null_Visible_Refinement (State_Id)
25086 and then Contains (Matched_Items, State_Id)
25087 then
25088 Remove (Clause);
25089 end if;
25090 end if;
25092 -- Recognize a clause of the form
25094 -- Output => null
25096 -- where Output is an arbitrary item. This clause must be removed
25097 -- because a null input legitimately matches anything.
25099 elsif Nkind (Input) = N_Null then
25100 Remove (Clause);
25101 end if;
25103 Clause := Next_Clause;
25104 end loop;
25105 end Remove_Extra_Clauses;
25107 --------------------------
25108 -- Report_Extra_Clauses --
25109 --------------------------
25111 procedure Report_Extra_Clauses
25112 (Spec_Id : Entity_Id;
25113 Clauses : List_Id)
25115 Clause : Node_Id;
25117 begin
25118 -- Do not perform this check in an instance because it was already
25119 -- performed successfully in the generic template.
25121 if Is_Generic_Instance (Spec_Id) then
25122 null;
25124 elsif Present (Clauses) then
25125 Clause := First (Clauses);
25126 while Present (Clause) loop
25127 SPARK_Msg_N
25128 ("unmatched or extra clause in dependence refinement",
25129 Clause);
25131 Next (Clause);
25132 end loop;
25133 end if;
25134 end Report_Extra_Clauses;
25136 -- Local variables
25138 Body_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
25139 Body_Id : constant Entity_Id := Defining_Entity (Body_Decl);
25140 Errors : constant Nat := Serious_Errors_Detected;
25142 Clause : Node_Id;
25143 Deps : Node_Id;
25144 Dummy : Boolean;
25145 Refs : Node_Id;
25147 Body_Inputs : Elist_Id := No_Elist;
25148 Body_Outputs : Elist_Id := No_Elist;
25149 -- The inputs and outputs of the subprogram body synthesized from pragma
25150 -- Refined_Depends.
25152 Dependencies : List_Id := No_List;
25153 Depends : Node_Id;
25154 -- The corresponding Depends pragma along with its clauses
25156 Matched_Items : Elist_Id := No_Elist;
25157 -- A list containing the entities of all successfully matched items
25158 -- found in pragma Depends.
25160 Refinements : List_Id := No_List;
25161 -- The clauses of pragma Refined_Depends
25163 Spec_Id : Entity_Id;
25164 -- The entity of the subprogram subject to pragma Refined_Depends
25166 Spec_Inputs : Elist_Id := No_Elist;
25167 Spec_Outputs : Elist_Id := No_Elist;
25168 -- The inputs and outputs of the subprogram spec synthesized from pragma
25169 -- Depends.
25171 States : Elist_Id := No_Elist;
25172 -- A list containing the entities of all states whose constituents
25173 -- appear in pragma Depends.
25175 -- Start of processing for Analyze_Refined_Depends_In_Decl_Part
25177 begin
25178 -- Do not analyze the pragma multiple times
25180 if Is_Analyzed_Pragma (N) then
25181 return;
25182 end if;
25184 Spec_Id := Unique_Defining_Entity (Body_Decl);
25186 -- Use the anonymous object as the proper spec when Refined_Depends
25187 -- applies to the body of a single task type. The object carries the
25188 -- proper Chars as well as all non-refined versions of pragmas.
25190 if Is_Single_Concurrent_Type (Spec_Id) then
25191 Spec_Id := Anonymous_Object (Spec_Id);
25192 end if;
25194 Depends := Get_Pragma (Spec_Id, Pragma_Depends);
25196 -- Subprogram declarations lacks pragma Depends. Refined_Depends is
25197 -- rendered useless as there is nothing to refine (SPARK RM 7.2.5(2)).
25199 if No (Depends) then
25200 SPARK_Msg_NE
25201 (Fix_Msg (Spec_Id, "useless refinement, declaration of subprogram "
25202 & "& lacks aspect or pragma Depends"), N, Spec_Id);
25203 goto Leave;
25204 end if;
25206 Deps := Expression (Get_Argument (Depends, Spec_Id));
25208 -- A null dependency relation renders the refinement useless because it
25209 -- cannot possibly mention abstract states with visible refinement. Note
25210 -- that the inverse is not true as states may be refined to null
25211 -- (SPARK RM 7.2.5(2)).
25213 if Nkind (Deps) = N_Null then
25214 SPARK_Msg_NE
25215 (Fix_Msg (Spec_Id, "useless refinement, subprogram & does not "
25216 & "depend on abstract state with visible refinement"), N, Spec_Id);
25217 goto Leave;
25218 end if;
25220 -- Analyze Refined_Depends as if it behaved as a regular pragma Depends.
25221 -- This ensures that the categorization of all refined dependency items
25222 -- is consistent with their role.
25224 Analyze_Depends_In_Decl_Part (N);
25226 -- Do not match dependencies against refinements if Refined_Depends is
25227 -- illegal to avoid emitting misleading error.
25229 if Serious_Errors_Detected = Errors then
25231 -- The related subprogram lacks pragma [Refined_]Global. Synthesize
25232 -- the inputs and outputs of the subprogram spec and body to verify
25233 -- the use of states with visible refinement and their constituents.
25235 if No (Get_Pragma (Spec_Id, Pragma_Global))
25236 or else No (Get_Pragma (Body_Id, Pragma_Refined_Global))
25237 then
25238 Collect_Subprogram_Inputs_Outputs
25239 (Subp_Id => Spec_Id,
25240 Synthesize => True,
25241 Subp_Inputs => Spec_Inputs,
25242 Subp_Outputs => Spec_Outputs,
25243 Global_Seen => Dummy);
25245 Collect_Subprogram_Inputs_Outputs
25246 (Subp_Id => Body_Id,
25247 Synthesize => True,
25248 Subp_Inputs => Body_Inputs,
25249 Subp_Outputs => Body_Outputs,
25250 Global_Seen => Dummy);
25252 -- For an output state with a visible refinement, ensure that all
25253 -- constituents appear as outputs in the dependency refinement.
25255 Check_Output_States
25256 (Spec_Id => Spec_Id,
25257 Spec_Inputs => Spec_Inputs,
25258 Spec_Outputs => Spec_Outputs,
25259 Body_Inputs => Body_Inputs,
25260 Body_Outputs => Body_Outputs);
25261 end if;
25263 -- Matching is disabled in ASIS because clauses are not normalized as
25264 -- this is a tree altering activity similar to expansion.
25266 if ASIS_Mode then
25267 goto Leave;
25268 end if;
25270 -- Multiple dependency clauses appear as component associations of an
25271 -- aggregate. Note that the clauses are copied because the algorithm
25272 -- modifies them and this should not be visible in Depends.
25274 pragma Assert (Nkind (Deps) = N_Aggregate);
25275 Dependencies := New_Copy_List_Tree (Component_Associations (Deps));
25276 Normalize_Clauses (Dependencies);
25278 -- Gather all states which appear in Depends
25280 States := Collect_States (Dependencies);
25282 Refs := Expression (Get_Argument (N, Spec_Id));
25284 if Nkind (Refs) = N_Null then
25285 Refinements := No_List;
25287 -- Multiple dependency clauses appear as component associations of an
25288 -- aggregate. Note that the clauses are copied because the algorithm
25289 -- modifies them and this should not be visible in Refined_Depends.
25291 else pragma Assert (Nkind (Refs) = N_Aggregate);
25292 Refinements := New_Copy_List_Tree (Component_Associations (Refs));
25293 Normalize_Clauses (Refinements);
25294 end if;
25296 -- At this point the clauses of pragmas Depends and Refined_Depends
25297 -- have been normalized into simple dependencies between one output
25298 -- and one input. Examine all clauses of pragma Depends looking for
25299 -- matching clauses in pragma Refined_Depends.
25301 Clause := First (Dependencies);
25302 while Present (Clause) loop
25303 Check_Dependency_Clause
25304 (Spec_Id => Spec_Id,
25305 Dep_Clause => Clause,
25306 Dep_States => States,
25307 Refinements => Refinements,
25308 Matched_Items => Matched_Items);
25310 Next (Clause);
25311 end loop;
25313 -- Pragma Refined_Depends may contain multiple clarification clauses
25314 -- which indicate that certain constituents do not influence the data
25315 -- flow in any way. Such clauses must be removed as long as the state
25316 -- has been matched, otherwise they will be incorrectly flagged as
25317 -- unmatched.
25319 -- Refined_State => (State => (Constit_1, Constit_2))
25320 -- Depends => (Output => State)
25321 -- Refined_Depends => ((Output => Constit_1), -- State matched
25322 -- (null => Constit_2)) -- must be removed
25324 Remove_Extra_Clauses (Refinements, Matched_Items);
25326 if Serious_Errors_Detected = Errors then
25327 Report_Extra_Clauses (Spec_Id, Refinements);
25328 end if;
25329 end if;
25331 <<Leave>>
25332 Set_Is_Analyzed_Pragma (N);
25333 end Analyze_Refined_Depends_In_Decl_Part;
25335 -----------------------------------------
25336 -- Analyze_Refined_Global_In_Decl_Part --
25337 -----------------------------------------
25339 procedure Analyze_Refined_Global_In_Decl_Part (N : Node_Id) is
25340 Global : Node_Id;
25341 -- The corresponding Global pragma
25343 Has_In_State : Boolean := False;
25344 Has_In_Out_State : Boolean := False;
25345 Has_Out_State : Boolean := False;
25346 Has_Proof_In_State : Boolean := False;
25347 -- These flags are set when the corresponding Global pragma has a state
25348 -- of mode Input, In_Out, Output or Proof_In respectively with a visible
25349 -- refinement.
25351 Has_Null_State : Boolean := False;
25352 -- This flag is set when the corresponding Global pragma has at least
25353 -- one state with a null refinement.
25355 In_Constits : Elist_Id := No_Elist;
25356 In_Out_Constits : Elist_Id := No_Elist;
25357 Out_Constits : Elist_Id := No_Elist;
25358 Proof_In_Constits : Elist_Id := No_Elist;
25359 -- These lists contain the entities of all Input, In_Out, Output and
25360 -- Proof_In constituents that appear in Refined_Global and participate
25361 -- in state refinement.
25363 In_Items : Elist_Id := No_Elist;
25364 In_Out_Items : Elist_Id := No_Elist;
25365 Out_Items : Elist_Id := No_Elist;
25366 Proof_In_Items : Elist_Id := No_Elist;
25367 -- These lists contain the entities of all Input, In_Out, Output and
25368 -- Proof_In items defined in the corresponding Global pragma.
25370 Repeat_Items : Elist_Id := No_Elist;
25371 -- A list of all global items without full visible refinement found
25372 -- in pragma Global. These states should be repeated in the global
25373 -- refinement (SPARK RM 7.2.4(3c)) unless they have a partial visible
25374 -- refinement, in which case they may be repeated (SPARK RM 7.2.4(3d)).
25376 Spec_Id : Entity_Id;
25377 -- The entity of the subprogram subject to pragma Refined_Global
25379 States : Elist_Id := No_Elist;
25380 -- A list of all states with full or partial visible refinement found in
25381 -- pragma Global.
25383 procedure Check_In_Out_States;
25384 -- Determine whether the corresponding Global pragma mentions In_Out
25385 -- states with visible refinement and if so, ensure that one of the
25386 -- following completions apply to the constituents of the state:
25387 -- 1) there is at least one constituent of mode In_Out
25388 -- 2) there is at least one Input and one Output constituent
25389 -- 3) not all constituents are present and one of them is of mode
25390 -- Output.
25391 -- This routine may remove elements from In_Constits, In_Out_Constits,
25392 -- Out_Constits and Proof_In_Constits.
25394 procedure Check_Input_States;
25395 -- Determine whether the corresponding Global pragma mentions Input
25396 -- states with visible refinement and if so, ensure that at least one of
25397 -- its constituents appears as an Input item in Refined_Global.
25398 -- This routine may remove elements from In_Constits, In_Out_Constits,
25399 -- Out_Constits and Proof_In_Constits.
25401 procedure Check_Output_States;
25402 -- Determine whether the corresponding Global pragma mentions Output
25403 -- states with visible refinement and if so, ensure that all of its
25404 -- constituents appear as Output items in Refined_Global.
25405 -- This routine may remove elements from In_Constits, In_Out_Constits,
25406 -- Out_Constits and Proof_In_Constits.
25408 procedure Check_Proof_In_States;
25409 -- Determine whether the corresponding Global pragma mentions Proof_In
25410 -- states with visible refinement and if so, ensure that at least one of
25411 -- its constituents appears as a Proof_In item in Refined_Global.
25412 -- This routine may remove elements from In_Constits, In_Out_Constits,
25413 -- Out_Constits and Proof_In_Constits.
25415 procedure Check_Refined_Global_List
25416 (List : Node_Id;
25417 Global_Mode : Name_Id := Name_Input);
25418 -- Verify the legality of a single global list declaration. Global_Mode
25419 -- denotes the current mode in effect.
25421 procedure Collect_Global_Items
25422 (List : Node_Id;
25423 Mode : Name_Id := Name_Input);
25424 -- Gather all Input, In_Out, Output and Proof_In items from node List
25425 -- and separate them in lists In_Items, In_Out_Items, Out_Items and
25426 -- Proof_In_Items. Flags Has_In_State, Has_In_Out_State, Has_Out_State
25427 -- and Has_Proof_In_State are set when there is at least one abstract
25428 -- state with full or partial visible refinement available in the
25429 -- corresponding mode. Flag Has_Null_State is set when at least state
25430 -- has a null refinement. Mode denotes the current global mode in
25431 -- effect.
25433 function Present_Then_Remove
25434 (List : Elist_Id;
25435 Item : Entity_Id) return Boolean;
25436 -- Search List for a particular entity Item. If Item has been found,
25437 -- remove it from List. This routine is used to strip lists In_Constits,
25438 -- In_Out_Constits and Out_Constits of valid constituents.
25440 procedure Present_Then_Remove (List : Elist_Id; Item : Entity_Id);
25441 -- Same as function Present_Then_Remove, but do not report the presence
25442 -- of Item in List.
25444 procedure Report_Extra_Constituents;
25445 -- Emit an error for each constituent found in lists In_Constits,
25446 -- In_Out_Constits and Out_Constits.
25448 procedure Report_Missing_Items;
25449 -- Emit an error for each global item not repeated found in list
25450 -- Repeat_Items.
25452 -------------------------
25453 -- Check_In_Out_States --
25454 -------------------------
25456 procedure Check_In_Out_States is
25457 procedure Check_Constituent_Usage (State_Id : Entity_Id);
25458 -- Determine whether one of the following coverage scenarios is in
25459 -- effect:
25460 -- 1) there is at least one constituent of mode In_Out or Output
25461 -- 2) there is at least one pair of constituents with modes Input
25462 -- and Output, or Proof_In and Output.
25463 -- 3) there is at least one constituent of mode Output and not all
25464 -- constituents are present.
25465 -- If this is not the case, emit an error (SPARK RM 7.2.4(5)).
25467 -----------------------------
25468 -- Check_Constituent_Usage --
25469 -----------------------------
25471 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
25472 Constits : constant Elist_Id :=
25473 Partial_Refinement_Constituents (State_Id);
25474 Constit_Elmt : Elmt_Id;
25475 Constit_Id : Entity_Id;
25476 Has_Missing : Boolean := False;
25477 In_Out_Seen : Boolean := False;
25478 Input_Seen : Boolean := False;
25479 Output_Seen : Boolean := False;
25480 Proof_In_Seen : Boolean := False;
25482 begin
25483 -- Process all the constituents of the state and note their modes
25484 -- within the global refinement.
25486 if Present (Constits) then
25487 Constit_Elmt := First_Elmt (Constits);
25488 while Present (Constit_Elmt) loop
25489 Constit_Id := Node (Constit_Elmt);
25491 if Present_Then_Remove (In_Constits, Constit_Id) then
25492 Input_Seen := True;
25494 elsif Present_Then_Remove (In_Out_Constits, Constit_Id) then
25495 In_Out_Seen := True;
25497 elsif Present_Then_Remove (Out_Constits, Constit_Id) then
25498 Output_Seen := True;
25500 elsif Present_Then_Remove (Proof_In_Constits, Constit_Id)
25501 then
25502 Proof_In_Seen := True;
25504 else
25505 Has_Missing := True;
25506 end if;
25508 Next_Elmt (Constit_Elmt);
25509 end loop;
25510 end if;
25512 -- An In_Out constituent is a valid completion
25514 if In_Out_Seen then
25515 null;
25517 -- A pair of one Input/Proof_In and one Output constituent is a
25518 -- valid completion.
25520 elsif (Input_Seen or Proof_In_Seen) and Output_Seen then
25521 null;
25523 elsif Output_Seen then
25525 -- A single Output constituent is a valid completion only when
25526 -- some of the other constituents are missing.
25528 if Has_Missing then
25529 null;
25531 -- Otherwise all constituents are of mode Output
25533 else
25534 SPARK_Msg_NE
25535 ("global refinement of state & must include at least one "
25536 & "constituent of mode `In_Out`, `Input`, or `Proof_In`",
25537 N, State_Id);
25538 end if;
25540 -- The state lacks a completion. When full refinement is visible,
25541 -- always emit an error (SPARK RM 7.2.4(3a)). When only partial
25542 -- refinement is visible, emit an error if the abstract state
25543 -- itself is not utilized (SPARK RM 7.2.4(3d)). In the case where
25544 -- both are utilized, Check_State_And_Constituent_Use. will issue
25545 -- the error.
25547 elsif not Input_Seen
25548 and then not In_Out_Seen
25549 and then not Output_Seen
25550 and then not Proof_In_Seen
25551 then
25552 if Has_Visible_Refinement (State_Id)
25553 or else Contains (Repeat_Items, State_Id)
25554 then
25555 SPARK_Msg_NE
25556 ("missing global refinement of state &", N, State_Id);
25557 end if;
25559 -- Otherwise the state has a malformed completion where at least
25560 -- one of the constituents has a different mode.
25562 else
25563 SPARK_Msg_NE
25564 ("global refinement of state & redefines the mode of its "
25565 & "constituents", N, State_Id);
25566 end if;
25567 end Check_Constituent_Usage;
25569 -- Local variables
25571 Item_Elmt : Elmt_Id;
25572 Item_Id : Entity_Id;
25574 -- Start of processing for Check_In_Out_States
25576 begin
25577 -- Do not perform this check in an instance because it was already
25578 -- performed successfully in the generic template.
25580 if Is_Generic_Instance (Spec_Id) then
25581 null;
25583 -- Inspect the In_Out items of the corresponding Global pragma
25584 -- looking for a state with a visible refinement.
25586 elsif Has_In_Out_State and then Present (In_Out_Items) then
25587 Item_Elmt := First_Elmt (In_Out_Items);
25588 while Present (Item_Elmt) loop
25589 Item_Id := Node (Item_Elmt);
25591 -- Ensure that one of the three coverage variants is satisfied
25593 if Ekind (Item_Id) = E_Abstract_State
25594 and then Has_Non_Null_Visible_Refinement (Item_Id)
25595 then
25596 Check_Constituent_Usage (Item_Id);
25597 end if;
25599 Next_Elmt (Item_Elmt);
25600 end loop;
25601 end if;
25602 end Check_In_Out_States;
25604 ------------------------
25605 -- Check_Input_States --
25606 ------------------------
25608 procedure Check_Input_States is
25609 procedure Check_Constituent_Usage (State_Id : Entity_Id);
25610 -- Determine whether at least one constituent of state State_Id with
25611 -- full or partial visible refinement is used and has mode Input.
25612 -- Ensure that the remaining constituents do not have In_Out or
25613 -- Output modes. Emit an error if this is not the case
25614 -- (SPARK RM 7.2.4(5)).
25616 -----------------------------
25617 -- Check_Constituent_Usage --
25618 -----------------------------
25620 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
25621 Constits : constant Elist_Id :=
25622 Partial_Refinement_Constituents (State_Id);
25623 Constit_Elmt : Elmt_Id;
25624 Constit_Id : Entity_Id;
25625 In_Seen : Boolean := False;
25627 begin
25628 if Present (Constits) then
25629 Constit_Elmt := First_Elmt (Constits);
25630 while Present (Constit_Elmt) loop
25631 Constit_Id := Node (Constit_Elmt);
25633 -- At least one of the constituents appears as an Input
25635 if Present_Then_Remove (In_Constits, Constit_Id) then
25636 In_Seen := True;
25638 -- A Proof_In constituent can refine an Input state as long
25639 -- as there is at least one Input constituent present.
25641 elsif Present_Then_Remove (Proof_In_Constits, Constit_Id)
25642 then
25643 null;
25645 -- The constituent appears in the global refinement, but has
25646 -- mode In_Out or Output (SPARK RM 7.2.4(5)).
25648 elsif Present_Then_Remove (In_Out_Constits, Constit_Id)
25649 or else Present_Then_Remove (Out_Constits, Constit_Id)
25650 then
25651 Error_Msg_Name_1 := Chars (State_Id);
25652 SPARK_Msg_NE
25653 ("constituent & of state % must have mode `Input` in "
25654 & "global refinement", N, Constit_Id);
25655 end if;
25657 Next_Elmt (Constit_Elmt);
25658 end loop;
25659 end if;
25661 -- Not one of the constituents appeared as Input. Always emit an
25662 -- error when the full refinement is visible (SPARK RM 7.2.4(3a)).
25663 -- When only partial refinement is visible, emit an error if the
25664 -- abstract state itself is not utilized (SPARK RM 7.2.4(3d)). In
25665 -- the case where both are utilized, an error will be issued in
25666 -- Check_State_And_Constituent_Use.
25668 if not In_Seen
25669 and then (Has_Visible_Refinement (State_Id)
25670 or else Contains (Repeat_Items, State_Id))
25671 then
25672 SPARK_Msg_NE
25673 ("global refinement of state & must include at least one "
25674 & "constituent of mode `Input`", N, State_Id);
25675 end if;
25676 end Check_Constituent_Usage;
25678 -- Local variables
25680 Item_Elmt : Elmt_Id;
25681 Item_Id : Entity_Id;
25683 -- Start of processing for Check_Input_States
25685 begin
25686 -- Do not perform this check in an instance because it was already
25687 -- performed successfully in the generic template.
25689 if Is_Generic_Instance (Spec_Id) then
25690 null;
25692 -- Inspect the Input items of the corresponding Global pragma looking
25693 -- for a state with a visible refinement.
25695 elsif Has_In_State and then Present (In_Items) then
25696 Item_Elmt := First_Elmt (In_Items);
25697 while Present (Item_Elmt) loop
25698 Item_Id := Node (Item_Elmt);
25700 -- When full refinement is visible, ensure that at least one of
25701 -- the constituents is utilized and is of mode Input. When only
25702 -- partial refinement is visible, ensure that either one of
25703 -- the constituents is utilized and is of mode Input, or the
25704 -- abstract state is repeated and no constituent is utilized.
25706 if Ekind (Item_Id) = E_Abstract_State
25707 and then Has_Non_Null_Visible_Refinement (Item_Id)
25708 then
25709 Check_Constituent_Usage (Item_Id);
25710 end if;
25712 Next_Elmt (Item_Elmt);
25713 end loop;
25714 end if;
25715 end Check_Input_States;
25717 -------------------------
25718 -- Check_Output_States --
25719 -------------------------
25721 procedure Check_Output_States is
25722 procedure Check_Constituent_Usage (State_Id : Entity_Id);
25723 -- Determine whether all constituents of state State_Id with full
25724 -- visible refinement are used and have mode Output. Emit an error
25725 -- if this is not the case (SPARK RM 7.2.4(5)).
25727 -----------------------------
25728 -- Check_Constituent_Usage --
25729 -----------------------------
25731 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
25732 Constits : constant Elist_Id :=
25733 Partial_Refinement_Constituents (State_Id);
25734 Only_Partial : constant Boolean :=
25735 not Has_Visible_Refinement (State_Id);
25736 Constit_Elmt : Elmt_Id;
25737 Constit_Id : Entity_Id;
25738 Posted : Boolean := False;
25740 begin
25741 if Present (Constits) then
25742 Constit_Elmt := First_Elmt (Constits);
25743 while Present (Constit_Elmt) loop
25744 Constit_Id := Node (Constit_Elmt);
25746 -- Issue an error when a constituent of State_Id is utilized
25747 -- and State_Id has only partial visible refinement
25748 -- (SPARK RM 7.2.4(3d)).
25750 if Only_Partial then
25751 if Present_Then_Remove (Out_Constits, Constit_Id)
25752 or else Present_Then_Remove (In_Constits, Constit_Id)
25753 or else
25754 Present_Then_Remove (In_Out_Constits, Constit_Id)
25755 or else
25756 Present_Then_Remove (Proof_In_Constits, Constit_Id)
25757 then
25758 Error_Msg_Name_1 := Chars (State_Id);
25759 SPARK_Msg_NE
25760 ("constituent & of state % cannot be used in global "
25761 & "refinement", N, Constit_Id);
25762 Error_Msg_Name_1 := Chars (State_Id);
25763 SPARK_Msg_N ("\use state % instead", N);
25764 end if;
25766 elsif Present_Then_Remove (Out_Constits, Constit_Id) then
25767 null;
25769 -- The constituent appears in the global refinement, but has
25770 -- mode Input, In_Out or Proof_In (SPARK RM 7.2.4(5)).
25772 elsif Present_Then_Remove (In_Constits, Constit_Id)
25773 or else Present_Then_Remove (In_Out_Constits, Constit_Id)
25774 or else Present_Then_Remove (Proof_In_Constits, Constit_Id)
25775 then
25776 Error_Msg_Name_1 := Chars (State_Id);
25777 SPARK_Msg_NE
25778 ("constituent & of state % must have mode `Output` in "
25779 & "global refinement", N, Constit_Id);
25781 -- The constituent is altogether missing (SPARK RM 7.2.5(3))
25783 else
25784 if not Posted then
25785 Posted := True;
25786 SPARK_Msg_NE
25787 ("`Output` state & must be replaced by all its "
25788 & "constituents in global refinement", N, State_Id);
25789 end if;
25791 SPARK_Msg_NE
25792 ("\constituent & is missing in output list",
25793 N, Constit_Id);
25794 end if;
25796 Next_Elmt (Constit_Elmt);
25797 end loop;
25798 end if;
25799 end Check_Constituent_Usage;
25801 -- Local variables
25803 Item_Elmt : Elmt_Id;
25804 Item_Id : Entity_Id;
25806 -- Start of processing for Check_Output_States
25808 begin
25809 -- Do not perform this check in an instance because it was already
25810 -- performed successfully in the generic template.
25812 if Is_Generic_Instance (Spec_Id) then
25813 null;
25815 -- Inspect the Output items of the corresponding Global pragma
25816 -- looking for a state with a visible refinement.
25818 elsif Has_Out_State and then Present (Out_Items) then
25819 Item_Elmt := First_Elmt (Out_Items);
25820 while Present (Item_Elmt) loop
25821 Item_Id := Node (Item_Elmt);
25823 -- When full refinement is visible, ensure that all of the
25824 -- constituents are utilized and they have mode Output. When
25825 -- only partial refinement is visible, ensure that no
25826 -- constituent is utilized.
25828 if Ekind (Item_Id) = E_Abstract_State
25829 and then Has_Non_Null_Visible_Refinement (Item_Id)
25830 then
25831 Check_Constituent_Usage (Item_Id);
25832 end if;
25834 Next_Elmt (Item_Elmt);
25835 end loop;
25836 end if;
25837 end Check_Output_States;
25839 ---------------------------
25840 -- Check_Proof_In_States --
25841 ---------------------------
25843 procedure Check_Proof_In_States is
25844 procedure Check_Constituent_Usage (State_Id : Entity_Id);
25845 -- Determine whether at least one constituent of state State_Id with
25846 -- full or partial visible refinement is used and has mode Proof_In.
25847 -- Ensure that the remaining constituents do not have Input, In_Out,
25848 -- or Output modes. Emit an error if this is not the case
25849 -- (SPARK RM 7.2.4(5)).
25851 -----------------------------
25852 -- Check_Constituent_Usage --
25853 -----------------------------
25855 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
25856 Constits : constant Elist_Id :=
25857 Partial_Refinement_Constituents (State_Id);
25858 Constit_Elmt : Elmt_Id;
25859 Constit_Id : Entity_Id;
25860 Proof_In_Seen : Boolean := False;
25862 begin
25863 if Present (Constits) then
25864 Constit_Elmt := First_Elmt (Constits);
25865 while Present (Constit_Elmt) loop
25866 Constit_Id := Node (Constit_Elmt);
25868 -- At least one of the constituents appears as Proof_In
25870 if Present_Then_Remove (Proof_In_Constits, Constit_Id) then
25871 Proof_In_Seen := True;
25873 -- The constituent appears in the global refinement, but has
25874 -- mode Input, In_Out or Output (SPARK RM 7.2.4(5)).
25876 elsif Present_Then_Remove (In_Constits, Constit_Id)
25877 or else Present_Then_Remove (In_Out_Constits, Constit_Id)
25878 or else Present_Then_Remove (Out_Constits, Constit_Id)
25879 then
25880 Error_Msg_Name_1 := Chars (State_Id);
25881 SPARK_Msg_NE
25882 ("constituent & of state % must have mode `Proof_In` "
25883 & "in global refinement", N, Constit_Id);
25884 end if;
25886 Next_Elmt (Constit_Elmt);
25887 end loop;
25888 end if;
25890 -- Not one of the constituents appeared as Proof_In. Always emit
25891 -- an error when full refinement is visible (SPARK RM 7.2.4(3a)).
25892 -- When only partial refinement is visible, emit an error if the
25893 -- abstract state itself is not utilized (SPARK RM 7.2.4(3d)). In
25894 -- the case where both are utilized, an error will be issued by
25895 -- Check_State_And_Constituent_Use.
25897 if not Proof_In_Seen
25898 and then (Has_Visible_Refinement (State_Id)
25899 or else Contains (Repeat_Items, State_Id))
25900 then
25901 SPARK_Msg_NE
25902 ("global refinement of state & must include at least one "
25903 & "constituent of mode `Proof_In`", N, State_Id);
25904 end if;
25905 end Check_Constituent_Usage;
25907 -- Local variables
25909 Item_Elmt : Elmt_Id;
25910 Item_Id : Entity_Id;
25912 -- Start of processing for Check_Proof_In_States
25914 begin
25915 -- Do not perform this check in an instance because it was already
25916 -- performed successfully in the generic template.
25918 if Is_Generic_Instance (Spec_Id) then
25919 null;
25921 -- Inspect the Proof_In items of the corresponding Global pragma
25922 -- looking for a state with a visible refinement.
25924 elsif Has_Proof_In_State and then Present (Proof_In_Items) then
25925 Item_Elmt := First_Elmt (Proof_In_Items);
25926 while Present (Item_Elmt) loop
25927 Item_Id := Node (Item_Elmt);
25929 -- Ensure that at least one of the constituents is utilized
25930 -- and is of mode Proof_In. When only partial refinement is
25931 -- visible, ensure that either one of the constituents is
25932 -- utilized and is of mode Proof_In, or the abstract state
25933 -- is repeated and no constituent is utilized.
25935 if Ekind (Item_Id) = E_Abstract_State
25936 and then Has_Non_Null_Visible_Refinement (Item_Id)
25937 then
25938 Check_Constituent_Usage (Item_Id);
25939 end if;
25941 Next_Elmt (Item_Elmt);
25942 end loop;
25943 end if;
25944 end Check_Proof_In_States;
25946 -------------------------------
25947 -- Check_Refined_Global_List --
25948 -------------------------------
25950 procedure Check_Refined_Global_List
25951 (List : Node_Id;
25952 Global_Mode : Name_Id := Name_Input)
25954 procedure Check_Refined_Global_Item
25955 (Item : Node_Id;
25956 Global_Mode : Name_Id);
25957 -- Verify the legality of a single global item declaration. Parameter
25958 -- Global_Mode denotes the current mode in effect.
25960 -------------------------------
25961 -- Check_Refined_Global_Item --
25962 -------------------------------
25964 procedure Check_Refined_Global_Item
25965 (Item : Node_Id;
25966 Global_Mode : Name_Id)
25968 Item_Id : constant Entity_Id := Entity_Of (Item);
25970 procedure Inconsistent_Mode_Error (Expect : Name_Id);
25971 -- Issue a common error message for all mode mismatches. Expect
25972 -- denotes the expected mode.
25974 -----------------------------
25975 -- Inconsistent_Mode_Error --
25976 -----------------------------
25978 procedure Inconsistent_Mode_Error (Expect : Name_Id) is
25979 begin
25980 SPARK_Msg_NE
25981 ("global item & has inconsistent modes", Item, Item_Id);
25983 Error_Msg_Name_1 := Global_Mode;
25984 Error_Msg_Name_2 := Expect;
25985 SPARK_Msg_N ("\expected mode %, found mode %", Item);
25986 end Inconsistent_Mode_Error;
25988 -- Local variables
25990 Enc_State : Entity_Id := Empty;
25991 -- Encapsulating state for constituent, Empty otherwise
25993 -- Start of processing for Check_Refined_Global_Item
25995 begin
25996 if Ekind_In (Item_Id, E_Abstract_State,
25997 E_Constant,
25998 E_Variable)
25999 then
26000 Enc_State := Find_Encapsulating_State (States, Item_Id);
26001 end if;
26003 -- When the state or object acts as a constituent of another
26004 -- state with a visible refinement, collect it for the state
26005 -- completeness checks performed later on. Note that the item
26006 -- acts as a constituent only when the encapsulating state is
26007 -- present in pragma Global.
26009 if Present (Enc_State)
26010 and then (Has_Visible_Refinement (Enc_State)
26011 or else Has_Partial_Visible_Refinement (Enc_State))
26012 and then Contains (States, Enc_State)
26013 then
26014 -- If the state has only partial visible refinement, remove it
26015 -- from the list of items that should be repeated from pragma
26016 -- Global.
26018 if not Has_Visible_Refinement (Enc_State) then
26019 Present_Then_Remove (Repeat_Items, Enc_State);
26020 end if;
26022 if Global_Mode = Name_Input then
26023 Append_New_Elmt (Item_Id, In_Constits);
26025 elsif Global_Mode = Name_In_Out then
26026 Append_New_Elmt (Item_Id, In_Out_Constits);
26028 elsif Global_Mode = Name_Output then
26029 Append_New_Elmt (Item_Id, Out_Constits);
26031 elsif Global_Mode = Name_Proof_In then
26032 Append_New_Elmt (Item_Id, Proof_In_Constits);
26033 end if;
26035 -- When not a constituent, ensure that both occurrences of the
26036 -- item in pragmas Global and Refined_Global match. Also remove
26037 -- it when present from the list of items that should be repeated
26038 -- from pragma Global.
26040 else
26041 Present_Then_Remove (Repeat_Items, Item_Id);
26043 if Contains (In_Items, Item_Id) then
26044 if Global_Mode /= Name_Input then
26045 Inconsistent_Mode_Error (Name_Input);
26046 end if;
26048 elsif Contains (In_Out_Items, Item_Id) then
26049 if Global_Mode /= Name_In_Out then
26050 Inconsistent_Mode_Error (Name_In_Out);
26051 end if;
26053 elsif Contains (Out_Items, Item_Id) then
26054 if Global_Mode /= Name_Output then
26055 Inconsistent_Mode_Error (Name_Output);
26056 end if;
26058 elsif Contains (Proof_In_Items, Item_Id) then
26059 null;
26061 -- The item does not appear in the corresponding Global pragma,
26062 -- it must be an extra (SPARK RM 7.2.4(3)).
26064 else
26065 SPARK_Msg_NE ("extra global item &", Item, Item_Id);
26066 end if;
26067 end if;
26068 end Check_Refined_Global_Item;
26070 -- Local variables
26072 Item : Node_Id;
26074 -- Start of processing for Check_Refined_Global_List
26076 begin
26077 -- Do not perform this check in an instance because it was already
26078 -- performed successfully in the generic template.
26080 if Is_Generic_Instance (Spec_Id) then
26081 null;
26083 elsif Nkind (List) = N_Null then
26084 null;
26086 -- Single global item declaration
26088 elsif Nkind_In (List, N_Expanded_Name,
26089 N_Identifier,
26090 N_Selected_Component)
26091 then
26092 Check_Refined_Global_Item (List, Global_Mode);
26094 -- Simple global list or moded global list declaration
26096 elsif Nkind (List) = N_Aggregate then
26098 -- The declaration of a simple global list appear as a collection
26099 -- of expressions.
26101 if Present (Expressions (List)) then
26102 Item := First (Expressions (List));
26103 while Present (Item) loop
26104 Check_Refined_Global_Item (Item, Global_Mode);
26105 Next (Item);
26106 end loop;
26108 -- The declaration of a moded global list appears as a collection
26109 -- of component associations where individual choices denote
26110 -- modes.
26112 elsif Present (Component_Associations (List)) then
26113 Item := First (Component_Associations (List));
26114 while Present (Item) loop
26115 Check_Refined_Global_List
26116 (List => Expression (Item),
26117 Global_Mode => Chars (First (Choices (Item))));
26119 Next (Item);
26120 end loop;
26122 -- Invalid tree
26124 else
26125 raise Program_Error;
26126 end if;
26128 -- Invalid list
26130 else
26131 raise Program_Error;
26132 end if;
26133 end Check_Refined_Global_List;
26135 --------------------------
26136 -- Collect_Global_Items --
26137 --------------------------
26139 procedure Collect_Global_Items
26140 (List : Node_Id;
26141 Mode : Name_Id := Name_Input)
26143 procedure Collect_Global_Item
26144 (Item : Node_Id;
26145 Item_Mode : Name_Id);
26146 -- Add a single item to the appropriate list. Item_Mode denotes the
26147 -- current mode in effect.
26149 -------------------------
26150 -- Collect_Global_Item --
26151 -------------------------
26153 procedure Collect_Global_Item
26154 (Item : Node_Id;
26155 Item_Mode : Name_Id)
26157 Item_Id : constant Entity_Id := Available_View (Entity_Of (Item));
26158 -- The above handles abstract views of variables and states built
26159 -- for limited with clauses.
26161 begin
26162 -- Signal that the global list contains at least one abstract
26163 -- state with a visible refinement. Note that the refinement may
26164 -- be null in which case there are no constituents.
26166 if Ekind (Item_Id) = E_Abstract_State then
26167 if Has_Null_Visible_Refinement (Item_Id) then
26168 Has_Null_State := True;
26170 elsif Has_Non_Null_Visible_Refinement (Item_Id) then
26171 Append_New_Elmt (Item_Id, States);
26173 if Item_Mode = Name_Input then
26174 Has_In_State := True;
26175 elsif Item_Mode = Name_In_Out then
26176 Has_In_Out_State := True;
26177 elsif Item_Mode = Name_Output then
26178 Has_Out_State := True;
26179 elsif Item_Mode = Name_Proof_In then
26180 Has_Proof_In_State := True;
26181 end if;
26182 end if;
26183 end if;
26185 -- Record global items without full visible refinement found in
26186 -- pragma Global which should be repeated in the global refinement
26187 -- (SPARK RM 7.2.4(3c), SPARK RM 7.2.4(3d)).
26189 if Ekind (Item_Id) /= E_Abstract_State
26190 or else not Has_Visible_Refinement (Item_Id)
26191 then
26192 Append_New_Elmt (Item_Id, Repeat_Items);
26193 end if;
26195 -- Add the item to the proper list
26197 if Item_Mode = Name_Input then
26198 Append_New_Elmt (Item_Id, In_Items);
26199 elsif Item_Mode = Name_In_Out then
26200 Append_New_Elmt (Item_Id, In_Out_Items);
26201 elsif Item_Mode = Name_Output then
26202 Append_New_Elmt (Item_Id, Out_Items);
26203 elsif Item_Mode = Name_Proof_In then
26204 Append_New_Elmt (Item_Id, Proof_In_Items);
26205 end if;
26206 end Collect_Global_Item;
26208 -- Local variables
26210 Item : Node_Id;
26212 -- Start of processing for Collect_Global_Items
26214 begin
26215 if Nkind (List) = N_Null then
26216 null;
26218 -- Single global item declaration
26220 elsif Nkind_In (List, N_Expanded_Name,
26221 N_Identifier,
26222 N_Selected_Component)
26223 then
26224 Collect_Global_Item (List, Mode);
26226 -- Single global list or moded global list declaration
26228 elsif Nkind (List) = N_Aggregate then
26230 -- The declaration of a simple global list appear as a collection
26231 -- of expressions.
26233 if Present (Expressions (List)) then
26234 Item := First (Expressions (List));
26235 while Present (Item) loop
26236 Collect_Global_Item (Item, Mode);
26237 Next (Item);
26238 end loop;
26240 -- The declaration of a moded global list appears as a collection
26241 -- of component associations where individual choices denote mode.
26243 elsif Present (Component_Associations (List)) then
26244 Item := First (Component_Associations (List));
26245 while Present (Item) loop
26246 Collect_Global_Items
26247 (List => Expression (Item),
26248 Mode => Chars (First (Choices (Item))));
26250 Next (Item);
26251 end loop;
26253 -- Invalid tree
26255 else
26256 raise Program_Error;
26257 end if;
26259 -- To accommodate partial decoration of disabled SPARK features, this
26260 -- routine may be called with illegal input. If this is the case, do
26261 -- not raise Program_Error.
26263 else
26264 null;
26265 end if;
26266 end Collect_Global_Items;
26268 -------------------------
26269 -- Present_Then_Remove --
26270 -------------------------
26272 function Present_Then_Remove
26273 (List : Elist_Id;
26274 Item : Entity_Id) return Boolean
26276 Elmt : Elmt_Id;
26278 begin
26279 if Present (List) then
26280 Elmt := First_Elmt (List);
26281 while Present (Elmt) loop
26282 if Node (Elmt) = Item then
26283 Remove_Elmt (List, Elmt);
26284 return True;
26285 end if;
26287 Next_Elmt (Elmt);
26288 end loop;
26289 end if;
26291 return False;
26292 end Present_Then_Remove;
26294 procedure Present_Then_Remove (List : Elist_Id; Item : Entity_Id) is
26295 Ignore : Boolean;
26296 begin
26297 Ignore := Present_Then_Remove (List, Item);
26298 end Present_Then_Remove;
26300 -------------------------------
26301 -- Report_Extra_Constituents --
26302 -------------------------------
26304 procedure Report_Extra_Constituents is
26305 procedure Report_Extra_Constituents_In_List (List : Elist_Id);
26306 -- Emit an error for every element of List
26308 ---------------------------------------
26309 -- Report_Extra_Constituents_In_List --
26310 ---------------------------------------
26312 procedure Report_Extra_Constituents_In_List (List : Elist_Id) is
26313 Constit_Elmt : Elmt_Id;
26315 begin
26316 if Present (List) then
26317 Constit_Elmt := First_Elmt (List);
26318 while Present (Constit_Elmt) loop
26319 SPARK_Msg_NE ("extra constituent &", N, Node (Constit_Elmt));
26320 Next_Elmt (Constit_Elmt);
26321 end loop;
26322 end if;
26323 end Report_Extra_Constituents_In_List;
26325 -- Start of processing for Report_Extra_Constituents
26327 begin
26328 -- Do not perform this check in an instance because it was already
26329 -- performed successfully in the generic template.
26331 if Is_Generic_Instance (Spec_Id) then
26332 null;
26334 else
26335 Report_Extra_Constituents_In_List (In_Constits);
26336 Report_Extra_Constituents_In_List (In_Out_Constits);
26337 Report_Extra_Constituents_In_List (Out_Constits);
26338 Report_Extra_Constituents_In_List (Proof_In_Constits);
26339 end if;
26340 end Report_Extra_Constituents;
26342 --------------------------
26343 -- Report_Missing_Items --
26344 --------------------------
26346 procedure Report_Missing_Items is
26347 Item_Elmt : Elmt_Id;
26348 Item_Id : Entity_Id;
26350 begin
26351 -- Do not perform this check in an instance because it was already
26352 -- performed successfully in the generic template.
26354 if Is_Generic_Instance (Spec_Id) then
26355 null;
26357 else
26358 if Present (Repeat_Items) then
26359 Item_Elmt := First_Elmt (Repeat_Items);
26360 while Present (Item_Elmt) loop
26361 Item_Id := Node (Item_Elmt);
26362 SPARK_Msg_NE ("missing global item &", N, Item_Id);
26363 Next_Elmt (Item_Elmt);
26364 end loop;
26365 end if;
26366 end if;
26367 end Report_Missing_Items;
26369 -- Local variables
26371 Body_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
26372 Errors : constant Nat := Serious_Errors_Detected;
26373 Items : Node_Id;
26374 No_Constit : Boolean;
26376 -- Start of processing for Analyze_Refined_Global_In_Decl_Part
26378 begin
26379 -- Do not analyze the pragma multiple times
26381 if Is_Analyzed_Pragma (N) then
26382 return;
26383 end if;
26385 Spec_Id := Unique_Defining_Entity (Body_Decl);
26387 -- Use the anonymous object as the proper spec when Refined_Global
26388 -- applies to the body of a single task type. The object carries the
26389 -- proper Chars as well as all non-refined versions of pragmas.
26391 if Is_Single_Concurrent_Type (Spec_Id) then
26392 Spec_Id := Anonymous_Object (Spec_Id);
26393 end if;
26395 Global := Get_Pragma (Spec_Id, Pragma_Global);
26396 Items := Expression (Get_Argument (N, Spec_Id));
26398 -- The subprogram declaration lacks pragma Global. This renders
26399 -- Refined_Global useless as there is nothing to refine.
26401 if No (Global) then
26402 SPARK_Msg_NE
26403 (Fix_Msg (Spec_Id, "useless refinement, declaration of subprogram "
26404 & "& lacks aspect or pragma Global"), N, Spec_Id);
26405 goto Leave;
26406 end if;
26408 -- Extract all relevant items from the corresponding Global pragma
26410 Collect_Global_Items (Expression (Get_Argument (Global, Spec_Id)));
26412 -- Package and subprogram bodies are instantiated individually in
26413 -- a separate compiler pass. Due to this mode of instantiation, the
26414 -- refinement of a state may no longer be visible when a subprogram
26415 -- body contract is instantiated. Since the generic template is legal,
26416 -- do not perform this check in the instance to circumvent this oddity.
26418 if Is_Generic_Instance (Spec_Id) then
26419 null;
26421 -- Non-instance case
26423 else
26424 -- The corresponding Global pragma must mention at least one
26425 -- state with a visible refinement at the point Refined_Global
26426 -- is processed. States with null refinements need Refined_Global
26427 -- pragma (SPARK RM 7.2.4(2)).
26429 if not Has_In_State
26430 and then not Has_In_Out_State
26431 and then not Has_Out_State
26432 and then not Has_Proof_In_State
26433 and then not Has_Null_State
26434 then
26435 SPARK_Msg_NE
26436 (Fix_Msg (Spec_Id, "useless refinement, subprogram & does not "
26437 & "depend on abstract state with visible refinement"),
26438 N, Spec_Id);
26439 goto Leave;
26441 -- The global refinement of inputs and outputs cannot be null when
26442 -- the corresponding Global pragma contains at least one item except
26443 -- in the case where we have states with null refinements.
26445 elsif Nkind (Items) = N_Null
26446 and then
26447 (Present (In_Items)
26448 or else Present (In_Out_Items)
26449 or else Present (Out_Items)
26450 or else Present (Proof_In_Items))
26451 and then not Has_Null_State
26452 then
26453 SPARK_Msg_NE
26454 (Fix_Msg (Spec_Id, "refinement cannot be null, subprogram & has "
26455 & "global items"), N, Spec_Id);
26456 goto Leave;
26457 end if;
26458 end if;
26460 -- Analyze Refined_Global as if it behaved as a regular pragma Global.
26461 -- This ensures that the categorization of all refined global items is
26462 -- consistent with their role.
26464 Analyze_Global_In_Decl_Part (N);
26466 -- Perform all refinement checks with respect to completeness and mode
26467 -- matching.
26469 if Serious_Errors_Detected = Errors then
26470 Check_Refined_Global_List (Items);
26471 end if;
26473 -- Store the information that no constituent is used in the global
26474 -- refinement, prior to calling checking procedures which remove items
26475 -- from the list of constituents.
26477 No_Constit :=
26478 No (In_Constits)
26479 and then No (In_Out_Constits)
26480 and then No (Out_Constits)
26481 and then No (Proof_In_Constits);
26483 -- For Input states with visible refinement, at least one constituent
26484 -- must be used as an Input in the global refinement.
26486 if Serious_Errors_Detected = Errors then
26487 Check_Input_States;
26488 end if;
26490 -- Verify all possible completion variants for In_Out states with
26491 -- visible refinement.
26493 if Serious_Errors_Detected = Errors then
26494 Check_In_Out_States;
26495 end if;
26497 -- For Output states with visible refinement, all constituents must be
26498 -- used as Outputs in the global refinement.
26500 if Serious_Errors_Detected = Errors then
26501 Check_Output_States;
26502 end if;
26504 -- For Proof_In states with visible refinement, at least one constituent
26505 -- must be used as Proof_In in the global refinement.
26507 if Serious_Errors_Detected = Errors then
26508 Check_Proof_In_States;
26509 end if;
26511 -- Emit errors for all constituents that belong to other states with
26512 -- visible refinement that do not appear in Global.
26514 if Serious_Errors_Detected = Errors then
26515 Report_Extra_Constituents;
26516 end if;
26518 -- Emit errors for all items in Global that are not repeated in the
26519 -- global refinement and for which there is no full visible refinement
26520 -- and, in the case of states with partial visible refinement, no
26521 -- constituent is mentioned in the global refinement.
26523 if Serious_Errors_Detected = Errors then
26524 Report_Missing_Items;
26525 end if;
26527 -- Emit an error if no constituent is used in the global refinement
26528 -- (SPARK RM 7.2.4(3f)). Emit this error last, in case a more precise
26529 -- one may be issued by the checking procedures. Do not perform this
26530 -- check in an instance because it was already performed successfully
26531 -- in the generic template.
26533 if Serious_Errors_Detected = Errors
26534 and then not Is_Generic_Instance (Spec_Id)
26535 and then not Has_Null_State
26536 and then No_Constit
26537 then
26538 SPARK_Msg_N ("missing refinement", N);
26539 end if;
26541 <<Leave>>
26542 Set_Is_Analyzed_Pragma (N);
26543 end Analyze_Refined_Global_In_Decl_Part;
26545 ----------------------------------------
26546 -- Analyze_Refined_State_In_Decl_Part --
26547 ----------------------------------------
26549 procedure Analyze_Refined_State_In_Decl_Part
26550 (N : Node_Id;
26551 Freeze_Id : Entity_Id := Empty)
26553 Body_Decl : constant Node_Id := Find_Related_Package_Or_Body (N);
26554 Body_Id : constant Entity_Id := Defining_Entity (Body_Decl);
26555 Spec_Id : constant Entity_Id := Corresponding_Spec (Body_Decl);
26557 Available_States : Elist_Id := No_Elist;
26558 -- A list of all abstract states defined in the package declaration that
26559 -- are available for refinement. The list is used to report unrefined
26560 -- states.
26562 Body_States : Elist_Id := No_Elist;
26563 -- A list of all hidden states that appear in the body of the related
26564 -- package. The list is used to report unused hidden states.
26566 Constituents_Seen : Elist_Id := No_Elist;
26567 -- A list that contains all constituents processed so far. The list is
26568 -- used to detect multiple uses of the same constituent.
26570 Freeze_Posted : Boolean := False;
26571 -- A flag that controls the output of a freezing-related error (see use
26572 -- below).
26574 Refined_States_Seen : Elist_Id := No_Elist;
26575 -- A list that contains all refined states processed so far. The list is
26576 -- used to detect duplicate refinements.
26578 procedure Analyze_Refinement_Clause (Clause : Node_Id);
26579 -- Perform full analysis of a single refinement clause
26581 procedure Report_Unrefined_States (States : Elist_Id);
26582 -- Emit errors for all unrefined abstract states found in list States
26584 -------------------------------
26585 -- Analyze_Refinement_Clause --
26586 -------------------------------
26588 procedure Analyze_Refinement_Clause (Clause : Node_Id) is
26589 AR_Constit : Entity_Id := Empty;
26590 AW_Constit : Entity_Id := Empty;
26591 ER_Constit : Entity_Id := Empty;
26592 EW_Constit : Entity_Id := Empty;
26593 -- The entities of external constituents that contain one of the
26594 -- following enabled properties: Async_Readers, Async_Writers,
26595 -- Effective_Reads and Effective_Writes.
26597 External_Constit_Seen : Boolean := False;
26598 -- Flag used to mark when at least one external constituent is part
26599 -- of the state refinement.
26601 Non_Null_Seen : Boolean := False;
26602 Null_Seen : Boolean := False;
26603 -- Flags used to detect multiple uses of null in a single clause or a
26604 -- mixture of null and non-null constituents.
26606 Part_Of_Constits : Elist_Id := No_Elist;
26607 -- A list of all candidate constituents subject to indicator Part_Of
26608 -- where the encapsulating state is the current state.
26610 State : Node_Id;
26611 State_Id : Entity_Id;
26612 -- The current state being refined
26614 procedure Analyze_Constituent (Constit : Node_Id);
26615 -- Perform full analysis of a single constituent
26617 procedure Check_External_Property
26618 (Prop_Nam : Name_Id;
26619 Enabled : Boolean;
26620 Constit : Entity_Id);
26621 -- Determine whether a property denoted by name Prop_Nam is present
26622 -- in the refined state. Emit an error if this is not the case. Flag
26623 -- Enabled should be set when the property applies to the refined
26624 -- state. Constit denotes the constituent (if any) which introduces
26625 -- the property in the refinement.
26627 procedure Match_State;
26628 -- Determine whether the state being refined appears in list
26629 -- Available_States. Emit an error when attempting to re-refine the
26630 -- state or when the state is not defined in the package declaration,
26631 -- otherwise remove the state from Available_States.
26633 procedure Report_Unused_Constituents (Constits : Elist_Id);
26634 -- Emit errors for all unused Part_Of constituents in list Constits
26636 -------------------------
26637 -- Analyze_Constituent --
26638 -------------------------
26640 procedure Analyze_Constituent (Constit : Node_Id) is
26641 procedure Match_Constituent (Constit_Id : Entity_Id);
26642 -- Determine whether constituent Constit denoted by its entity
26643 -- Constit_Id appears in Body_States. Emit an error when the
26644 -- constituent is not a valid hidden state of the related package
26645 -- or when it is used more than once. Otherwise remove the
26646 -- constituent from Body_States.
26648 -----------------------
26649 -- Match_Constituent --
26650 -----------------------
26652 procedure Match_Constituent (Constit_Id : Entity_Id) is
26653 procedure Collect_Constituent;
26654 -- Verify the legality of constituent Constit_Id and add it to
26655 -- the refinements of State_Id.
26657 -------------------------
26658 -- Collect_Constituent --
26659 -------------------------
26661 procedure Collect_Constituent is
26662 Constits : Elist_Id;
26664 begin
26665 -- The Ghost policy in effect at the point of abstract state
26666 -- declaration and constituent must match (SPARK RM 6.9(15))
26668 Check_Ghost_Refinement
26669 (State, State_Id, Constit, Constit_Id);
26671 -- A synchronized state must be refined by a synchronized
26672 -- object or another synchronized state (SPARK RM 9.6).
26674 if Is_Synchronized_State (State_Id)
26675 and then not Is_Synchronized_Object (Constit_Id)
26676 and then not Is_Synchronized_State (Constit_Id)
26677 then
26678 SPARK_Msg_NE
26679 ("constituent of synchronized state & must be "
26680 & "synchronized", Constit, State_Id);
26681 end if;
26683 -- Add the constituent to the list of processed items to aid
26684 -- with the detection of duplicates.
26686 Append_New_Elmt (Constit_Id, Constituents_Seen);
26688 -- Collect the constituent in the list of refinement items
26689 -- and establish a relation between the refined state and
26690 -- the item.
26692 Constits := Refinement_Constituents (State_Id);
26694 if No (Constits) then
26695 Constits := New_Elmt_List;
26696 Set_Refinement_Constituents (State_Id, Constits);
26697 end if;
26699 Append_Elmt (Constit_Id, Constits);
26700 Set_Encapsulating_State (Constit_Id, State_Id);
26702 -- The state has at least one legal constituent, mark the
26703 -- start of the refinement region. The region ends when the
26704 -- body declarations end (see routine Analyze_Declarations).
26706 Set_Has_Visible_Refinement (State_Id);
26708 -- When the constituent is external, save its relevant
26709 -- property for further checks.
26711 if Async_Readers_Enabled (Constit_Id) then
26712 AR_Constit := Constit_Id;
26713 External_Constit_Seen := True;
26714 end if;
26716 if Async_Writers_Enabled (Constit_Id) then
26717 AW_Constit := Constit_Id;
26718 External_Constit_Seen := True;
26719 end if;
26721 if Effective_Reads_Enabled (Constit_Id) then
26722 ER_Constit := Constit_Id;
26723 External_Constit_Seen := True;
26724 end if;
26726 if Effective_Writes_Enabled (Constit_Id) then
26727 EW_Constit := Constit_Id;
26728 External_Constit_Seen := True;
26729 end if;
26730 end Collect_Constituent;
26732 -- Local variables
26734 State_Elmt : Elmt_Id;
26736 -- Start of processing for Match_Constituent
26738 begin
26739 -- Detect a duplicate use of a constituent
26741 if Contains (Constituents_Seen, Constit_Id) then
26742 SPARK_Msg_NE
26743 ("duplicate use of constituent &", Constit, Constit_Id);
26744 return;
26745 end if;
26747 -- The constituent is subject to a Part_Of indicator
26749 if Present (Encapsulating_State (Constit_Id)) then
26750 if Encapsulating_State (Constit_Id) = State_Id then
26751 Remove (Part_Of_Constits, Constit_Id);
26752 Collect_Constituent;
26754 -- The constituent is part of another state and is used
26755 -- incorrectly in the refinement of the current state.
26757 else
26758 Error_Msg_Name_1 := Chars (State_Id);
26759 SPARK_Msg_NE
26760 ("& cannot act as constituent of state %",
26761 Constit, Constit_Id);
26762 SPARK_Msg_NE
26763 ("\Part_Of indicator specifies encapsulator &",
26764 Constit, Encapsulating_State (Constit_Id));
26765 end if;
26767 -- The only other source of legal constituents is the body
26768 -- state space of the related package.
26770 else
26771 if Present (Body_States) then
26772 State_Elmt := First_Elmt (Body_States);
26773 while Present (State_Elmt) loop
26775 -- Consume a valid constituent to signal that it has
26776 -- been encountered.
26778 if Node (State_Elmt) = Constit_Id then
26779 Remove_Elmt (Body_States, State_Elmt);
26780 Collect_Constituent;
26781 return;
26782 end if;
26784 Next_Elmt (State_Elmt);
26785 end loop;
26786 end if;
26788 -- Constants are part of the hidden state of a package, but
26789 -- the compiler cannot determine whether they have variable
26790 -- input (SPARK RM 7.1.1(2)) and cannot classify them as a
26791 -- hidden state. Accept the constant quietly even if it is
26792 -- a visible state or lacks a Part_Of indicator.
26794 if Ekind (Constit_Id) = E_Constant then
26795 Collect_Constituent;
26797 -- If we get here, then the constituent is not a hidden
26798 -- state of the related package and may not be used in a
26799 -- refinement (SPARK RM 7.2.2(9)).
26801 else
26802 Error_Msg_Name_1 := Chars (Spec_Id);
26803 SPARK_Msg_NE
26804 ("cannot use & in refinement, constituent is not a "
26805 & "hidden state of package %", Constit, Constit_Id);
26806 end if;
26807 end if;
26808 end Match_Constituent;
26810 -- Local variables
26812 Constit_Id : Entity_Id;
26813 Constits : Elist_Id;
26815 -- Start of processing for Analyze_Constituent
26817 begin
26818 -- Detect multiple uses of null in a single refinement clause or a
26819 -- mixture of null and non-null constituents.
26821 if Nkind (Constit) = N_Null then
26822 if Null_Seen then
26823 SPARK_Msg_N
26824 ("multiple null constituents not allowed", Constit);
26826 elsif Non_Null_Seen then
26827 SPARK_Msg_N
26828 ("cannot mix null and non-null constituents", Constit);
26830 else
26831 Null_Seen := True;
26833 -- Collect the constituent in the list of refinement items
26835 Constits := Refinement_Constituents (State_Id);
26837 if No (Constits) then
26838 Constits := New_Elmt_List;
26839 Set_Refinement_Constituents (State_Id, Constits);
26840 end if;
26842 Append_Elmt (Constit, Constits);
26844 -- The state has at least one legal constituent, mark the
26845 -- start of the refinement region. The region ends when the
26846 -- body declarations end (see Analyze_Declarations).
26848 Set_Has_Visible_Refinement (State_Id);
26849 end if;
26851 -- Non-null constituents
26853 else
26854 Non_Null_Seen := True;
26856 if Null_Seen then
26857 SPARK_Msg_N
26858 ("cannot mix null and non-null constituents", Constit);
26859 end if;
26861 Analyze (Constit);
26862 Resolve_State (Constit);
26864 -- Ensure that the constituent denotes a valid state or a
26865 -- whole object (SPARK RM 7.2.2(5)).
26867 if Is_Entity_Name (Constit) then
26868 Constit_Id := Entity_Of (Constit);
26870 -- When a constituent is declared after a subprogram body
26871 -- that caused "freezing" of the related contract where
26872 -- pragma Refined_State resides, the constituent appears
26873 -- undefined and carries Any_Id as its entity.
26875 -- package body Pack
26876 -- with Refined_State => (State => Constit)
26877 -- is
26878 -- procedure Proc
26879 -- with Refined_Global => (Input => Constit)
26880 -- is
26881 -- ...
26882 -- end Proc;
26884 -- Constit : ...;
26885 -- end Pack;
26887 if Constit_Id = Any_Id then
26888 SPARK_Msg_NE ("& is undefined", Constit, Constit_Id);
26890 -- Emit a specialized info message when the contract of
26891 -- the related package body was "frozen" by another body.
26892 -- Note that it is not possible to precisely identify why
26893 -- the constituent is undefined because it is not visible
26894 -- when pragma Refined_State is analyzed. This message is
26895 -- a reasonable approximation.
26897 if Present (Freeze_Id) and then not Freeze_Posted then
26898 Freeze_Posted := True;
26900 Error_Msg_Name_1 := Chars (Body_Id);
26901 Error_Msg_Sloc := Sloc (Freeze_Id);
26902 SPARK_Msg_NE
26903 ("body & declared # freezes the contract of %",
26904 N, Freeze_Id);
26905 SPARK_Msg_N
26906 ("\all constituents must be declared before body #",
26909 -- A misplaced constituent is a critical error because
26910 -- pragma Refined_Depends or Refined_Global depends on
26911 -- the proper link between a state and a constituent.
26912 -- Stop the compilation, as this leads to a multitude
26913 -- of misleading cascaded errors.
26915 raise Program_Error;
26916 end if;
26918 -- The constituent is a valid state or object
26920 elsif Ekind_In (Constit_Id, E_Abstract_State,
26921 E_Constant,
26922 E_Variable)
26923 then
26924 Match_Constituent (Constit_Id);
26926 -- The variable may eventually become a constituent of a
26927 -- single protected/task type. Record the reference now
26928 -- and verify its legality when analyzing the contract of
26929 -- the variable (SPARK RM 9.3).
26931 if Ekind (Constit_Id) = E_Variable then
26932 Record_Possible_Part_Of_Reference
26933 (Var_Id => Constit_Id,
26934 Ref => Constit);
26935 end if;
26937 -- Otherwise the constituent is illegal
26939 else
26940 SPARK_Msg_NE
26941 ("constituent & must denote object or state",
26942 Constit, Constit_Id);
26943 end if;
26945 -- The constituent is illegal
26947 else
26948 SPARK_Msg_N ("malformed constituent", Constit);
26949 end if;
26950 end if;
26951 end Analyze_Constituent;
26953 -----------------------------
26954 -- Check_External_Property --
26955 -----------------------------
26957 procedure Check_External_Property
26958 (Prop_Nam : Name_Id;
26959 Enabled : Boolean;
26960 Constit : Entity_Id)
26962 begin
26963 -- The property is missing in the declaration of the state, but
26964 -- a constituent is introducing it in the state refinement
26965 -- (SPARK RM 7.2.8(2)).
26967 if not Enabled and then Present (Constit) then
26968 Error_Msg_Name_1 := Prop_Nam;
26969 Error_Msg_Name_2 := Chars (State_Id);
26970 SPARK_Msg_NE
26971 ("constituent & introduces external property % in refinement "
26972 & "of state %", State, Constit);
26974 Error_Msg_Sloc := Sloc (State_Id);
26975 SPARK_Msg_N
26976 ("\property is missing in abstract state declaration #",
26977 State);
26978 end if;
26979 end Check_External_Property;
26981 -----------------
26982 -- Match_State --
26983 -----------------
26985 procedure Match_State is
26986 State_Elmt : Elmt_Id;
26988 begin
26989 -- Detect a duplicate refinement of a state (SPARK RM 7.2.2(8))
26991 if Contains (Refined_States_Seen, State_Id) then
26992 SPARK_Msg_NE
26993 ("duplicate refinement of state &", State, State_Id);
26994 return;
26995 end if;
26997 -- Inspect the abstract states defined in the package declaration
26998 -- looking for a match.
27000 State_Elmt := First_Elmt (Available_States);
27001 while Present (State_Elmt) loop
27003 -- A valid abstract state is being refined in the body. Add
27004 -- the state to the list of processed refined states to aid
27005 -- with the detection of duplicate refinements. Remove the
27006 -- state from Available_States to signal that it has already
27007 -- been refined.
27009 if Node (State_Elmt) = State_Id then
27010 Append_New_Elmt (State_Id, Refined_States_Seen);
27011 Remove_Elmt (Available_States, State_Elmt);
27012 return;
27013 end if;
27015 Next_Elmt (State_Elmt);
27016 end loop;
27018 -- If we get here, we are refining a state that is not defined in
27019 -- the package declaration.
27021 Error_Msg_Name_1 := Chars (Spec_Id);
27022 SPARK_Msg_NE
27023 ("cannot refine state, & is not defined in package %",
27024 State, State_Id);
27025 end Match_State;
27027 --------------------------------
27028 -- Report_Unused_Constituents --
27029 --------------------------------
27031 procedure Report_Unused_Constituents (Constits : Elist_Id) is
27032 Constit_Elmt : Elmt_Id;
27033 Constit_Id : Entity_Id;
27034 Posted : Boolean := False;
27036 begin
27037 if Present (Constits) then
27038 Constit_Elmt := First_Elmt (Constits);
27039 while Present (Constit_Elmt) loop
27040 Constit_Id := Node (Constit_Elmt);
27042 -- Generate an error message of the form:
27044 -- state ... has unused Part_Of constituents
27045 -- abstract state ... defined at ...
27046 -- constant ... defined at ...
27047 -- variable ... defined at ...
27049 if not Posted then
27050 Posted := True;
27051 SPARK_Msg_NE
27052 ("state & has unused Part_Of constituents",
27053 State, State_Id);
27054 end if;
27056 Error_Msg_Sloc := Sloc (Constit_Id);
27058 if Ekind (Constit_Id) = E_Abstract_State then
27059 SPARK_Msg_NE
27060 ("\abstract state & defined #", State, Constit_Id);
27062 elsif Ekind (Constit_Id) = E_Constant then
27063 SPARK_Msg_NE
27064 ("\constant & defined #", State, Constit_Id);
27066 else
27067 pragma Assert (Ekind (Constit_Id) = E_Variable);
27068 SPARK_Msg_NE ("\variable & defined #", State, Constit_Id);
27069 end if;
27071 Next_Elmt (Constit_Elmt);
27072 end loop;
27073 end if;
27074 end Report_Unused_Constituents;
27076 -- Local declarations
27078 Body_Ref : Node_Id;
27079 Body_Ref_Elmt : Elmt_Id;
27080 Constit : Node_Id;
27081 Extra_State : Node_Id;
27083 -- Start of processing for Analyze_Refinement_Clause
27085 begin
27086 -- A refinement clause appears as a component association where the
27087 -- sole choice is the state and the expressions are the constituents.
27088 -- This is a syntax error, always report.
27090 if Nkind (Clause) /= N_Component_Association then
27091 Error_Msg_N ("malformed state refinement clause", Clause);
27092 return;
27093 end if;
27095 -- Analyze the state name of a refinement clause
27097 State := First (Choices (Clause));
27099 Analyze (State);
27100 Resolve_State (State);
27102 -- Ensure that the state name denotes a valid abstract state that is
27103 -- defined in the spec of the related package.
27105 if Is_Entity_Name (State) then
27106 State_Id := Entity_Of (State);
27108 -- When the abstract state is undefined, it appears as Any_Id. Do
27109 -- not continue with the analysis of the clause.
27111 if State_Id = Any_Id then
27112 return;
27114 -- Catch any attempts to re-refine a state or refine a state that
27115 -- is not defined in the package declaration.
27117 elsif Ekind (State_Id) = E_Abstract_State then
27118 Match_State;
27120 else
27121 SPARK_Msg_NE ("& must denote abstract state", State, State_Id);
27122 return;
27123 end if;
27125 -- References to a state with visible refinement are illegal.
27126 -- When nested packages are involved, detecting such references is
27127 -- tricky because pragma Refined_State is analyzed later than the
27128 -- offending pragma Depends or Global. References that occur in
27129 -- such nested context are stored in a list. Emit errors for all
27130 -- references found in Body_References (SPARK RM 6.1.4(8)).
27132 if Present (Body_References (State_Id)) then
27133 Body_Ref_Elmt := First_Elmt (Body_References (State_Id));
27134 while Present (Body_Ref_Elmt) loop
27135 Body_Ref := Node (Body_Ref_Elmt);
27137 SPARK_Msg_N ("reference to & not allowed", Body_Ref);
27138 Error_Msg_Sloc := Sloc (State);
27139 SPARK_Msg_N ("\refinement of & is visible#", Body_Ref);
27141 Next_Elmt (Body_Ref_Elmt);
27142 end loop;
27143 end if;
27145 -- The state name is illegal. This is a syntax error, always report.
27147 else
27148 Error_Msg_N ("malformed state name in refinement clause", State);
27149 return;
27150 end if;
27152 -- A refinement clause may only refine one state at a time
27154 Extra_State := Next (State);
27156 if Present (Extra_State) then
27157 SPARK_Msg_N
27158 ("refinement clause cannot cover multiple states", Extra_State);
27159 end if;
27161 -- Replicate the Part_Of constituents of the refined state because
27162 -- the algorithm will consume items.
27164 Part_Of_Constits := New_Copy_Elist (Part_Of_Constituents (State_Id));
27166 -- Analyze all constituents of the refinement. Multiple constituents
27167 -- appear as an aggregate.
27169 Constit := Expression (Clause);
27171 if Nkind (Constit) = N_Aggregate then
27172 if Present (Component_Associations (Constit)) then
27173 SPARK_Msg_N
27174 ("constituents of refinement clause must appear in "
27175 & "positional form", Constit);
27177 else pragma Assert (Present (Expressions (Constit)));
27178 Constit := First (Expressions (Constit));
27179 while Present (Constit) loop
27180 Analyze_Constituent (Constit);
27181 Next (Constit);
27182 end loop;
27183 end if;
27185 -- Various forms of a single constituent. Note that these may include
27186 -- malformed constituents.
27188 else
27189 Analyze_Constituent (Constit);
27190 end if;
27192 -- Verify that external constituents do not introduce new external
27193 -- property in the state refinement (SPARK RM 7.2.8(2)).
27195 if Is_External_State (State_Id) then
27196 Check_External_Property
27197 (Prop_Nam => Name_Async_Readers,
27198 Enabled => Async_Readers_Enabled (State_Id),
27199 Constit => AR_Constit);
27201 Check_External_Property
27202 (Prop_Nam => Name_Async_Writers,
27203 Enabled => Async_Writers_Enabled (State_Id),
27204 Constit => AW_Constit);
27206 Check_External_Property
27207 (Prop_Nam => Name_Effective_Reads,
27208 Enabled => Effective_Reads_Enabled (State_Id),
27209 Constit => ER_Constit);
27211 Check_External_Property
27212 (Prop_Nam => Name_Effective_Writes,
27213 Enabled => Effective_Writes_Enabled (State_Id),
27214 Constit => EW_Constit);
27216 -- When a refined state is not external, it should not have external
27217 -- constituents (SPARK RM 7.2.8(1)).
27219 elsif External_Constit_Seen then
27220 SPARK_Msg_NE
27221 ("non-external state & cannot contain external constituents in "
27222 & "refinement", State, State_Id);
27223 end if;
27225 -- Ensure that all Part_Of candidate constituents have been mentioned
27226 -- in the refinement clause.
27228 Report_Unused_Constituents (Part_Of_Constits);
27229 end Analyze_Refinement_Clause;
27231 -----------------------------
27232 -- Report_Unrefined_States --
27233 -----------------------------
27235 procedure Report_Unrefined_States (States : Elist_Id) is
27236 State_Elmt : Elmt_Id;
27238 begin
27239 if Present (States) then
27240 State_Elmt := First_Elmt (States);
27241 while Present (State_Elmt) loop
27242 SPARK_Msg_N
27243 ("abstract state & must be refined", Node (State_Elmt));
27245 Next_Elmt (State_Elmt);
27246 end loop;
27247 end if;
27248 end Report_Unrefined_States;
27250 -- Local declarations
27252 Clauses : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
27253 Clause : Node_Id;
27255 -- Start of processing for Analyze_Refined_State_In_Decl_Part
27257 begin
27258 -- Do not analyze the pragma multiple times
27260 if Is_Analyzed_Pragma (N) then
27261 return;
27262 end if;
27264 -- Replicate the abstract states declared by the package because the
27265 -- matching algorithm will consume states.
27267 Available_States := New_Copy_Elist (Abstract_States (Spec_Id));
27269 -- Gather all abstract states and objects declared in the visible
27270 -- state space of the package body. These items must be utilized as
27271 -- constituents in a state refinement.
27273 Body_States := Collect_Body_States (Body_Id);
27275 -- Multiple non-null state refinements appear as an aggregate
27277 if Nkind (Clauses) = N_Aggregate then
27278 if Present (Expressions (Clauses)) then
27279 SPARK_Msg_N
27280 ("state refinements must appear as component associations",
27281 Clauses);
27283 else pragma Assert (Present (Component_Associations (Clauses)));
27284 Clause := First (Component_Associations (Clauses));
27285 while Present (Clause) loop
27286 Analyze_Refinement_Clause (Clause);
27287 Next (Clause);
27288 end loop;
27289 end if;
27291 -- Various forms of a single state refinement. Note that these may
27292 -- include malformed refinements.
27294 else
27295 Analyze_Refinement_Clause (Clauses);
27296 end if;
27298 -- List all abstract states that were left unrefined
27300 Report_Unrefined_States (Available_States);
27302 Set_Is_Analyzed_Pragma (N);
27303 end Analyze_Refined_State_In_Decl_Part;
27305 ------------------------------------
27306 -- Analyze_Test_Case_In_Decl_Part --
27307 ------------------------------------
27309 procedure Analyze_Test_Case_In_Decl_Part (N : Node_Id) is
27310 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
27311 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
27313 procedure Preanalyze_Test_Case_Arg (Arg_Nam : Name_Id);
27314 -- Preanalyze one of the optional arguments "Requires" or "Ensures"
27315 -- denoted by Arg_Nam.
27317 ------------------------------
27318 -- Preanalyze_Test_Case_Arg --
27319 ------------------------------
27321 procedure Preanalyze_Test_Case_Arg (Arg_Nam : Name_Id) is
27322 Arg : Node_Id;
27324 begin
27325 -- Preanalyze the original aspect argument for ASIS or for a generic
27326 -- subprogram to properly capture global references.
27328 if ASIS_Mode or else Is_Generic_Subprogram (Spec_Id) then
27329 Arg :=
27330 Test_Case_Arg
27331 (Prag => N,
27332 Arg_Nam => Arg_Nam,
27333 From_Aspect => True);
27335 if Present (Arg) then
27336 Preanalyze_Assert_Expression
27337 (Expression (Arg), Standard_Boolean);
27338 end if;
27339 end if;
27341 Arg := Test_Case_Arg (N, Arg_Nam);
27343 if Present (Arg) then
27344 Preanalyze_Assert_Expression (Expression (Arg), Standard_Boolean);
27345 end if;
27346 end Preanalyze_Test_Case_Arg;
27348 -- Local variables
27350 Restore_Scope : Boolean := False;
27352 -- Start of processing for Analyze_Test_Case_In_Decl_Part
27354 begin
27355 -- Do not analyze the pragma multiple times
27357 if Is_Analyzed_Pragma (N) then
27358 return;
27359 end if;
27361 -- Ensure that the formal parameters are visible when analyzing all
27362 -- clauses. This falls out of the general rule of aspects pertaining
27363 -- to subprogram declarations.
27365 if not In_Open_Scopes (Spec_Id) then
27366 Restore_Scope := True;
27367 Push_Scope (Spec_Id);
27369 if Is_Generic_Subprogram (Spec_Id) then
27370 Install_Generic_Formals (Spec_Id);
27371 else
27372 Install_Formals (Spec_Id);
27373 end if;
27374 end if;
27376 Preanalyze_Test_Case_Arg (Name_Requires);
27377 Preanalyze_Test_Case_Arg (Name_Ensures);
27379 if Restore_Scope then
27380 End_Scope;
27381 end if;
27383 -- Currently it is not possible to inline pre/postconditions on a
27384 -- subprogram subject to pragma Inline_Always.
27386 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
27388 Set_Is_Analyzed_Pragma (N);
27389 end Analyze_Test_Case_In_Decl_Part;
27391 ----------------
27392 -- Appears_In --
27393 ----------------
27395 function Appears_In (List : Elist_Id; Item_Id : Entity_Id) return Boolean is
27396 Elmt : Elmt_Id;
27397 Id : Entity_Id;
27399 begin
27400 if Present (List) then
27401 Elmt := First_Elmt (List);
27402 while Present (Elmt) loop
27403 if Nkind (Node (Elmt)) = N_Defining_Identifier then
27404 Id := Node (Elmt);
27405 else
27406 Id := Entity_Of (Node (Elmt));
27407 end if;
27409 if Id = Item_Id then
27410 return True;
27411 end if;
27413 Next_Elmt (Elmt);
27414 end loop;
27415 end if;
27417 return False;
27418 end Appears_In;
27420 -----------------------------------
27421 -- Build_Pragma_Check_Equivalent --
27422 -----------------------------------
27424 function Build_Pragma_Check_Equivalent
27425 (Prag : Node_Id;
27426 Subp_Id : Entity_Id := Empty;
27427 Inher_Id : Entity_Id := Empty;
27428 Keep_Pragma_Id : Boolean := False) return Node_Id
27430 function Suppress_Reference (N : Node_Id) return Traverse_Result;
27431 -- Detect whether node N references a formal parameter subject to
27432 -- pragma Unreferenced. If this is the case, set Comes_From_Source
27433 -- to False to suppress the generation of a reference when analyzing
27434 -- N later on.
27436 ------------------------
27437 -- Suppress_Reference --
27438 ------------------------
27440 function Suppress_Reference (N : Node_Id) return Traverse_Result is
27441 Formal : Entity_Id;
27443 begin
27444 if Is_Entity_Name (N) and then Present (Entity (N)) then
27445 Formal := Entity (N);
27447 -- The formal parameter is subject to pragma Unreferenced. Prevent
27448 -- the generation of references by resetting the Comes_From_Source
27449 -- flag.
27451 if Is_Formal (Formal)
27452 and then Has_Pragma_Unreferenced (Formal)
27453 then
27454 Set_Comes_From_Source (N, False);
27455 end if;
27456 end if;
27458 return OK;
27459 end Suppress_Reference;
27461 procedure Suppress_References is
27462 new Traverse_Proc (Suppress_Reference);
27464 -- Local variables
27466 Loc : constant Source_Ptr := Sloc (Prag);
27467 Prag_Nam : constant Name_Id := Pragma_Name (Prag);
27468 Check_Prag : Node_Id;
27469 Msg_Arg : Node_Id;
27470 Nam : Name_Id;
27472 Needs_Wrapper : Boolean;
27473 pragma Unreferenced (Needs_Wrapper);
27475 -- Start of processing for Build_Pragma_Check_Equivalent
27477 begin
27478 -- When the pre- or postcondition is inherited, map the formals of the
27479 -- inherited subprogram to those of the current subprogram. In addition,
27480 -- map primitive operations of the parent type into the corresponding
27481 -- primitive operations of the descendant.
27483 if Present (Inher_Id) then
27484 pragma Assert (Present (Subp_Id));
27486 Update_Primitives_Mapping (Inher_Id, Subp_Id);
27488 -- Use generic machinery to copy inherited pragma, as if it were an
27489 -- instantiation, resetting source locations appropriately, so that
27490 -- expressions inside the inherited pragma use chained locations.
27491 -- This is used in particular in GNATprove to locate precisely
27492 -- messages on a given inherited pragma.
27494 Set_Copied_Sloc_For_Inherited_Pragma
27495 (Unit_Declaration_Node (Subp_Id), Inher_Id);
27496 Check_Prag := New_Copy_Tree (Source => Prag);
27498 -- Build the inherited class-wide condition
27500 Build_Class_Wide_Expression
27501 (Prag => Check_Prag,
27502 Subp => Subp_Id,
27503 Par_Subp => Inher_Id,
27504 Adjust_Sloc => True,
27505 Needs_Wrapper => Needs_Wrapper);
27507 -- If not an inherited condition simply copy the original pragma
27509 else
27510 Check_Prag := New_Copy_Tree (Source => Prag);
27511 end if;
27513 -- Mark the pragma as being internally generated and reset the Analyzed
27514 -- flag.
27516 Set_Analyzed (Check_Prag, False);
27517 Set_Comes_From_Source (Check_Prag, False);
27519 -- The tree of the original pragma may contain references to the
27520 -- formal parameters of the related subprogram. At the same time
27521 -- the corresponding body may mark the formals as unreferenced:
27523 -- procedure Proc (Formal : ...)
27524 -- with Pre => Formal ...;
27526 -- procedure Proc (Formal : ...) is
27527 -- pragma Unreferenced (Formal);
27528 -- ...
27530 -- This creates problems because all pragma Check equivalents are
27531 -- analyzed at the end of the body declarations. Since all source
27532 -- references have already been accounted for, reset any references
27533 -- to such formals in the generated pragma Check equivalent.
27535 Suppress_References (Check_Prag);
27537 if Present (Corresponding_Aspect (Prag)) then
27538 Nam := Chars (Identifier (Corresponding_Aspect (Prag)));
27539 else
27540 Nam := Prag_Nam;
27541 end if;
27543 -- Unless Keep_Pragma_Id is True in order to keep the identifier of
27544 -- the copied pragma in the newly created pragma, convert the copy into
27545 -- pragma Check by correcting the name and adding a check_kind argument.
27547 if not Keep_Pragma_Id then
27548 Set_Class_Present (Check_Prag, False);
27550 Set_Pragma_Identifier
27551 (Check_Prag, Make_Identifier (Loc, Name_Check));
27553 Prepend_To (Pragma_Argument_Associations (Check_Prag),
27554 Make_Pragma_Argument_Association (Loc,
27555 Expression => Make_Identifier (Loc, Nam)));
27556 end if;
27558 -- Update the error message when the pragma is inherited
27560 if Present (Inher_Id) then
27561 Msg_Arg := Last (Pragma_Argument_Associations (Check_Prag));
27563 if Chars (Msg_Arg) = Name_Message then
27564 String_To_Name_Buffer (Strval (Expression (Msg_Arg)));
27566 -- Insert "inherited" to improve the error message
27568 if Name_Buffer (1 .. 8) = "failed p" then
27569 Insert_Str_In_Name_Buffer ("inherited ", 8);
27570 Set_Strval (Expression (Msg_Arg), String_From_Name_Buffer);
27571 end if;
27572 end if;
27573 end if;
27575 return Check_Prag;
27576 end Build_Pragma_Check_Equivalent;
27578 -----------------------------
27579 -- Check_Applicable_Policy --
27580 -----------------------------
27582 procedure Check_Applicable_Policy (N : Node_Id) is
27583 PP : Node_Id;
27584 Policy : Name_Id;
27586 Ename : constant Name_Id := Original_Aspect_Pragma_Name (N);
27588 begin
27589 -- No effect if not valid assertion kind name
27591 if not Is_Valid_Assertion_Kind (Ename) then
27592 return;
27593 end if;
27595 -- Loop through entries in check policy list
27597 PP := Opt.Check_Policy_List;
27598 while Present (PP) loop
27599 declare
27600 PPA : constant List_Id := Pragma_Argument_Associations (PP);
27601 Pnm : constant Name_Id := Chars (Get_Pragma_Arg (First (PPA)));
27603 begin
27604 if Ename = Pnm
27605 or else Pnm = Name_Assertion
27606 or else (Pnm = Name_Statement_Assertions
27607 and then Nam_In (Ename, Name_Assert,
27608 Name_Assert_And_Cut,
27609 Name_Assume,
27610 Name_Loop_Invariant,
27611 Name_Loop_Variant))
27612 then
27613 Policy := Chars (Get_Pragma_Arg (Last (PPA)));
27615 case Policy is
27616 when Name_Ignore
27617 | Name_Off
27619 Set_Is_Ignored (N, True);
27620 Set_Is_Checked (N, False);
27622 when Name_Check
27623 | Name_On
27625 Set_Is_Checked (N, True);
27626 Set_Is_Ignored (N, False);
27628 when Name_Disable =>
27629 Set_Is_Ignored (N, True);
27630 Set_Is_Checked (N, False);
27631 Set_Is_Disabled (N, True);
27633 -- That should be exhaustive, the null here is a defence
27634 -- against a malformed tree from previous errors.
27636 when others =>
27637 null;
27638 end case;
27640 return;
27641 end if;
27643 PP := Next_Pragma (PP);
27644 end;
27645 end loop;
27647 -- If there are no specific entries that matched, then we let the
27648 -- setting of assertions govern. Note that this provides the needed
27649 -- compatibility with the RM for the cases of assertion, invariant,
27650 -- precondition, predicate, and postcondition.
27652 if Assertions_Enabled then
27653 Set_Is_Checked (N, True);
27654 Set_Is_Ignored (N, False);
27655 else
27656 Set_Is_Checked (N, False);
27657 Set_Is_Ignored (N, True);
27658 end if;
27659 end Check_Applicable_Policy;
27661 -------------------------------
27662 -- Check_External_Properties --
27663 -------------------------------
27665 procedure Check_External_Properties
27666 (Item : Node_Id;
27667 AR : Boolean;
27668 AW : Boolean;
27669 ER : Boolean;
27670 EW : Boolean)
27672 begin
27673 -- All properties enabled
27675 if AR and AW and ER and EW then
27676 null;
27678 -- Async_Readers + Effective_Writes
27679 -- Async_Readers + Async_Writers + Effective_Writes
27681 elsif AR and EW and not ER then
27682 null;
27684 -- Async_Writers + Effective_Reads
27685 -- Async_Readers + Async_Writers + Effective_Reads
27687 elsif AW and ER and not EW then
27688 null;
27690 -- Async_Readers + Async_Writers
27692 elsif AR and AW and not ER and not EW then
27693 null;
27695 -- Async_Readers
27697 elsif AR and not AW and not ER and not EW then
27698 null;
27700 -- Async_Writers
27702 elsif AW and not AR and not ER and not EW then
27703 null;
27705 else
27706 SPARK_Msg_N
27707 ("illegal combination of external properties (SPARK RM 7.1.2(6))",
27708 Item);
27709 end if;
27710 end Check_External_Properties;
27712 ----------------
27713 -- Check_Kind --
27714 ----------------
27716 function Check_Kind (Nam : Name_Id) return Name_Id is
27717 PP : Node_Id;
27719 begin
27720 -- Loop through entries in check policy list
27722 PP := Opt.Check_Policy_List;
27723 while Present (PP) loop
27724 declare
27725 PPA : constant List_Id := Pragma_Argument_Associations (PP);
27726 Pnm : constant Name_Id := Chars (Get_Pragma_Arg (First (PPA)));
27728 begin
27729 if Nam = Pnm
27730 or else (Pnm = Name_Assertion
27731 and then Is_Valid_Assertion_Kind (Nam))
27732 or else (Pnm = Name_Statement_Assertions
27733 and then Nam_In (Nam, Name_Assert,
27734 Name_Assert_And_Cut,
27735 Name_Assume,
27736 Name_Loop_Invariant,
27737 Name_Loop_Variant))
27738 then
27739 case (Chars (Get_Pragma_Arg (Last (PPA)))) is
27740 when Name_Check
27741 | Name_On
27743 return Name_Check;
27745 when Name_Ignore
27746 | Name_Off
27748 return Name_Ignore;
27750 when Name_Disable =>
27751 return Name_Disable;
27753 when others =>
27754 raise Program_Error;
27755 end case;
27757 else
27758 PP := Next_Pragma (PP);
27759 end if;
27760 end;
27761 end loop;
27763 -- If there are no specific entries that matched, then we let the
27764 -- setting of assertions govern. Note that this provides the needed
27765 -- compatibility with the RM for the cases of assertion, invariant,
27766 -- precondition, predicate, and postcondition.
27768 if Assertions_Enabled then
27769 return Name_Check;
27770 else
27771 return Name_Ignore;
27772 end if;
27773 end Check_Kind;
27775 ---------------------------
27776 -- Check_Missing_Part_Of --
27777 ---------------------------
27779 procedure Check_Missing_Part_Of (Item_Id : Entity_Id) is
27780 function Has_Visible_State (Pack_Id : Entity_Id) return Boolean;
27781 -- Determine whether a package denoted by Pack_Id declares at least one
27782 -- visible state.
27784 -----------------------
27785 -- Has_Visible_State --
27786 -----------------------
27788 function Has_Visible_State (Pack_Id : Entity_Id) return Boolean is
27789 Item_Id : Entity_Id;
27791 begin
27792 -- Traverse the entity chain of the package trying to find at least
27793 -- one visible abstract state, variable or a package [instantiation]
27794 -- that declares a visible state.
27796 Item_Id := First_Entity (Pack_Id);
27797 while Present (Item_Id)
27798 and then not In_Private_Part (Item_Id)
27799 loop
27800 -- Do not consider internally generated items
27802 if not Comes_From_Source (Item_Id) then
27803 null;
27805 -- A visible state has been found
27807 elsif Ekind_In (Item_Id, E_Abstract_State, E_Variable) then
27808 return True;
27810 -- Recursively peek into nested packages and instantiations
27812 elsif Ekind (Item_Id) = E_Package
27813 and then Has_Visible_State (Item_Id)
27814 then
27815 return True;
27816 end if;
27818 Next_Entity (Item_Id);
27819 end loop;
27821 return False;
27822 end Has_Visible_State;
27824 -- Local variables
27826 Pack_Id : Entity_Id;
27827 Placement : State_Space_Kind;
27829 -- Start of processing for Check_Missing_Part_Of
27831 begin
27832 -- Do not consider abstract states, variables or package instantiations
27833 -- coming from an instance as those always inherit the Part_Of indicator
27834 -- of the instance itself.
27836 if In_Instance then
27837 return;
27839 -- Do not consider internally generated entities as these can never
27840 -- have a Part_Of indicator.
27842 elsif not Comes_From_Source (Item_Id) then
27843 return;
27845 -- Perform these checks only when SPARK_Mode is enabled as they will
27846 -- interfere with standard Ada rules and produce false positives.
27848 elsif SPARK_Mode /= On then
27849 return;
27851 -- Do not consider constants, because the compiler cannot accurately
27852 -- determine whether they have variable input (SPARK RM 7.1.1(2)) and
27853 -- act as a hidden state of a package.
27855 elsif Ekind (Item_Id) = E_Constant then
27856 return;
27857 end if;
27859 -- Find where the abstract state, variable or package instantiation
27860 -- lives with respect to the state space.
27862 Find_Placement_In_State_Space
27863 (Item_Id => Item_Id,
27864 Placement => Placement,
27865 Pack_Id => Pack_Id);
27867 -- Items that appear in a non-package construct (subprogram, block, etc)
27868 -- do not require a Part_Of indicator because they can never act as a
27869 -- hidden state.
27871 if Placement = Not_In_Package then
27872 null;
27874 -- An item declared in the body state space of a package always act as a
27875 -- constituent and does not need explicit Part_Of indicator.
27877 elsif Placement = Body_State_Space then
27878 null;
27880 -- In general an item declared in the visible state space of a package
27881 -- does not require a Part_Of indicator. The only exception is when the
27882 -- related package is a private child unit in which case Part_Of must
27883 -- denote a state in the parent unit or in one of its descendants.
27885 elsif Placement = Visible_State_Space then
27886 if Is_Child_Unit (Pack_Id)
27887 and then Is_Private_Descendant (Pack_Id)
27888 then
27889 -- A package instantiation does not need a Part_Of indicator when
27890 -- the related generic template has no visible state.
27892 if Ekind (Item_Id) = E_Package
27893 and then Is_Generic_Instance (Item_Id)
27894 and then not Has_Visible_State (Item_Id)
27895 then
27896 null;
27898 -- All other cases require Part_Of
27900 else
27901 Error_Msg_N
27902 ("indicator Part_Of is required in this context "
27903 & "(SPARK RM 7.2.6(3))", Item_Id);
27904 Error_Msg_Name_1 := Chars (Pack_Id);
27905 Error_Msg_N
27906 ("\& is declared in the visible part of private child "
27907 & "unit %", Item_Id);
27908 end if;
27909 end if;
27911 -- When the item appears in the private state space of a packge, it must
27912 -- be a part of some state declared by the said package.
27914 else pragma Assert (Placement = Private_State_Space);
27916 -- The related package does not declare a state, the item cannot act
27917 -- as a Part_Of constituent.
27919 if No (Get_Pragma (Pack_Id, Pragma_Abstract_State)) then
27920 null;
27922 -- A package instantiation does not need a Part_Of indicator when the
27923 -- related generic template has no visible state.
27925 elsif Ekind (Pack_Id) = E_Package
27926 and then Is_Generic_Instance (Pack_Id)
27927 and then not Has_Visible_State (Pack_Id)
27928 then
27929 null;
27931 -- All other cases require Part_Of
27933 else
27934 Error_Msg_N
27935 ("indicator Part_Of is required in this context "
27936 & "(SPARK RM 7.2.6(2))", Item_Id);
27937 Error_Msg_Name_1 := Chars (Pack_Id);
27938 Error_Msg_N
27939 ("\& is declared in the private part of package %", Item_Id);
27940 end if;
27941 end if;
27942 end Check_Missing_Part_Of;
27944 ---------------------------------------------------
27945 -- Check_Postcondition_Use_In_Inlined_Subprogram --
27946 ---------------------------------------------------
27948 procedure Check_Postcondition_Use_In_Inlined_Subprogram
27949 (Prag : Node_Id;
27950 Spec_Id : Entity_Id)
27952 begin
27953 if Warn_On_Redundant_Constructs
27954 and then Has_Pragma_Inline_Always (Spec_Id)
27955 then
27956 Error_Msg_Name_1 := Original_Aspect_Pragma_Name (Prag);
27958 if From_Aspect_Specification (Prag) then
27959 Error_Msg_NE
27960 ("aspect % not enforced on inlined subprogram &?r?",
27961 Corresponding_Aspect (Prag), Spec_Id);
27962 else
27963 Error_Msg_NE
27964 ("pragma % not enforced on inlined subprogram &?r?",
27965 Prag, Spec_Id);
27966 end if;
27967 end if;
27968 end Check_Postcondition_Use_In_Inlined_Subprogram;
27970 -------------------------------------
27971 -- Check_State_And_Constituent_Use --
27972 -------------------------------------
27974 procedure Check_State_And_Constituent_Use
27975 (States : Elist_Id;
27976 Constits : Elist_Id;
27977 Context : Node_Id)
27979 Constit_Elmt : Elmt_Id;
27980 Constit_Id : Entity_Id;
27981 State_Id : Entity_Id;
27983 begin
27984 -- Nothing to do if there are no states or constituents
27986 if No (States) or else No (Constits) then
27987 return;
27988 end if;
27990 -- Inspect the list of constituents and try to determine whether its
27991 -- encapsulating state is in list States.
27993 Constit_Elmt := First_Elmt (Constits);
27994 while Present (Constit_Elmt) loop
27995 Constit_Id := Node (Constit_Elmt);
27997 -- Determine whether the constituent is part of an encapsulating
27998 -- state that appears in the same context and if this is the case,
27999 -- emit an error (SPARK RM 7.2.6(7)).
28001 State_Id := Find_Encapsulating_State (States, Constit_Id);
28003 if Present (State_Id) then
28004 Error_Msg_Name_1 := Chars (Constit_Id);
28005 SPARK_Msg_NE
28006 ("cannot mention state & and its constituent % in the same "
28007 & "context", Context, State_Id);
28008 exit;
28009 end if;
28011 Next_Elmt (Constit_Elmt);
28012 end loop;
28013 end Check_State_And_Constituent_Use;
28015 ---------------------------------------------
28016 -- Collect_Inherited_Class_Wide_Conditions --
28017 ---------------------------------------------
28019 procedure Collect_Inherited_Class_Wide_Conditions (Subp : Entity_Id) is
28020 Parent_Subp : constant Entity_Id :=
28021 Ultimate_Alias (Overridden_Operation (Subp));
28022 -- The Overridden_Operation may itself be inherited and as such have no
28023 -- explicit contract.
28025 Prags : constant Node_Id := Contract (Parent_Subp);
28026 In_Spec_Expr : Boolean;
28027 Installed : Boolean;
28028 Prag : Node_Id;
28029 New_Prag : Node_Id;
28031 begin
28032 Installed := False;
28034 -- Iterate over the contract of the overridden subprogram to find all
28035 -- inherited class-wide pre- and postconditions.
28037 if Present (Prags) then
28038 Prag := Pre_Post_Conditions (Prags);
28040 while Present (Prag) loop
28041 if Nam_In (Pragma_Name_Unmapped (Prag),
28042 Name_Precondition, Name_Postcondition)
28043 and then Class_Present (Prag)
28044 then
28045 -- The generated pragma must be analyzed in the context of
28046 -- the subprogram, to make its formals visible. In addition,
28047 -- we must inhibit freezing and full analysis because the
28048 -- controlling type of the subprogram is not frozen yet, and
28049 -- may have further primitives.
28051 if not Installed then
28052 Installed := True;
28053 Push_Scope (Subp);
28054 Install_Formals (Subp);
28055 In_Spec_Expr := In_Spec_Expression;
28056 In_Spec_Expression := True;
28057 end if;
28059 New_Prag :=
28060 Build_Pragma_Check_Equivalent
28061 (Prag, Subp, Parent_Subp, Keep_Pragma_Id => True);
28063 Insert_After (Unit_Declaration_Node (Subp), New_Prag);
28064 Preanalyze (New_Prag);
28066 -- Prevent further analysis in subsequent processing of the
28067 -- current list of declarations
28069 Set_Analyzed (New_Prag);
28070 end if;
28072 Prag := Next_Pragma (Prag);
28073 end loop;
28075 if Installed then
28076 In_Spec_Expression := In_Spec_Expr;
28077 End_Scope;
28078 end if;
28079 end if;
28080 end Collect_Inherited_Class_Wide_Conditions;
28082 ---------------------------------------
28083 -- Collect_Subprogram_Inputs_Outputs --
28084 ---------------------------------------
28086 procedure Collect_Subprogram_Inputs_Outputs
28087 (Subp_Id : Entity_Id;
28088 Synthesize : Boolean := False;
28089 Subp_Inputs : in out Elist_Id;
28090 Subp_Outputs : in out Elist_Id;
28091 Global_Seen : out Boolean)
28093 procedure Collect_Dependency_Clause (Clause : Node_Id);
28094 -- Collect all relevant items from a dependency clause
28096 procedure Collect_Global_List
28097 (List : Node_Id;
28098 Mode : Name_Id := Name_Input);
28099 -- Collect all relevant items from a global list
28101 -------------------------------
28102 -- Collect_Dependency_Clause --
28103 -------------------------------
28105 procedure Collect_Dependency_Clause (Clause : Node_Id) is
28106 procedure Collect_Dependency_Item
28107 (Item : Node_Id;
28108 Is_Input : Boolean);
28109 -- Add an item to the proper subprogram input or output collection
28111 -----------------------------
28112 -- Collect_Dependency_Item --
28113 -----------------------------
28115 procedure Collect_Dependency_Item
28116 (Item : Node_Id;
28117 Is_Input : Boolean)
28119 Extra : Node_Id;
28121 begin
28122 -- Nothing to collect when the item is null
28124 if Nkind (Item) = N_Null then
28125 null;
28127 -- Ditto for attribute 'Result
28129 elsif Is_Attribute_Result (Item) then
28130 null;
28132 -- Multiple items appear as an aggregate
28134 elsif Nkind (Item) = N_Aggregate then
28135 Extra := First (Expressions (Item));
28136 while Present (Extra) loop
28137 Collect_Dependency_Item (Extra, Is_Input);
28138 Next (Extra);
28139 end loop;
28141 -- Otherwise this is a solitary item
28143 else
28144 if Is_Input then
28145 Append_New_Elmt (Item, Subp_Inputs);
28146 else
28147 Append_New_Elmt (Item, Subp_Outputs);
28148 end if;
28149 end if;
28150 end Collect_Dependency_Item;
28152 -- Start of processing for Collect_Dependency_Clause
28154 begin
28155 if Nkind (Clause) = N_Null then
28156 null;
28158 -- A dependency cause appears as component association
28160 elsif Nkind (Clause) = N_Component_Association then
28161 Collect_Dependency_Item
28162 (Item => Expression (Clause),
28163 Is_Input => True);
28165 Collect_Dependency_Item
28166 (Item => First (Choices (Clause)),
28167 Is_Input => False);
28169 -- To accommodate partial decoration of disabled SPARK features, this
28170 -- routine may be called with illegal input. If this is the case, do
28171 -- not raise Program_Error.
28173 else
28174 null;
28175 end if;
28176 end Collect_Dependency_Clause;
28178 -------------------------
28179 -- Collect_Global_List --
28180 -------------------------
28182 procedure Collect_Global_List
28183 (List : Node_Id;
28184 Mode : Name_Id := Name_Input)
28186 procedure Collect_Global_Item (Item : Node_Id; Mode : Name_Id);
28187 -- Add an item to the proper subprogram input or output collection
28189 -------------------------
28190 -- Collect_Global_Item --
28191 -------------------------
28193 procedure Collect_Global_Item (Item : Node_Id; Mode : Name_Id) is
28194 begin
28195 if Nam_In (Mode, Name_In_Out, Name_Input) then
28196 Append_New_Elmt (Item, Subp_Inputs);
28197 end if;
28199 if Nam_In (Mode, Name_In_Out, Name_Output) then
28200 Append_New_Elmt (Item, Subp_Outputs);
28201 end if;
28202 end Collect_Global_Item;
28204 -- Local variables
28206 Assoc : Node_Id;
28207 Item : Node_Id;
28209 -- Start of processing for Collect_Global_List
28211 begin
28212 if Nkind (List) = N_Null then
28213 null;
28215 -- Single global item declaration
28217 elsif Nkind_In (List, N_Expanded_Name,
28218 N_Identifier,
28219 N_Selected_Component)
28220 then
28221 Collect_Global_Item (List, Mode);
28223 -- Simple global list or moded global list declaration
28225 elsif Nkind (List) = N_Aggregate then
28226 if Present (Expressions (List)) then
28227 Item := First (Expressions (List));
28228 while Present (Item) loop
28229 Collect_Global_Item (Item, Mode);
28230 Next (Item);
28231 end loop;
28233 else
28234 Assoc := First (Component_Associations (List));
28235 while Present (Assoc) loop
28236 Collect_Global_List
28237 (List => Expression (Assoc),
28238 Mode => Chars (First (Choices (Assoc))));
28239 Next (Assoc);
28240 end loop;
28241 end if;
28243 -- To accommodate partial decoration of disabled SPARK features, this
28244 -- routine may be called with illegal input. If this is the case, do
28245 -- not raise Program_Error.
28247 else
28248 null;
28249 end if;
28250 end Collect_Global_List;
28252 -- Local variables
28254 Clause : Node_Id;
28255 Clauses : Node_Id;
28256 Depends : Node_Id;
28257 Formal : Entity_Id;
28258 Global : Node_Id;
28259 Spec_Id : Entity_Id;
28260 Subp_Decl : Node_Id;
28261 Typ : Entity_Id;
28263 -- Start of processing for Collect_Subprogram_Inputs_Outputs
28265 begin
28266 Global_Seen := False;
28268 -- Process all formal parameters of entries, [generic] subprograms, and
28269 -- their bodies.
28271 if Ekind_In (Subp_Id, E_Entry,
28272 E_Entry_Family,
28273 E_Function,
28274 E_Generic_Function,
28275 E_Generic_Procedure,
28276 E_Procedure,
28277 E_Subprogram_Body)
28278 then
28279 Subp_Decl := Unit_Declaration_Node (Subp_Id);
28280 Spec_Id := Unique_Defining_Entity (Subp_Decl);
28282 -- Process all [generic] formal parameters
28284 Formal := First_Entity (Spec_Id);
28285 while Present (Formal) loop
28286 if Ekind_In (Formal, E_Generic_In_Parameter,
28287 E_In_Out_Parameter,
28288 E_In_Parameter)
28289 then
28290 Append_New_Elmt (Formal, Subp_Inputs);
28291 end if;
28293 if Ekind_In (Formal, E_Generic_In_Out_Parameter,
28294 E_In_Out_Parameter,
28295 E_Out_Parameter)
28296 then
28297 Append_New_Elmt (Formal, Subp_Outputs);
28299 -- Out parameters can act as inputs when the related type is
28300 -- tagged, unconstrained array, unconstrained record, or record
28301 -- with unconstrained components.
28303 if Ekind (Formal) = E_Out_Parameter
28304 and then Is_Unconstrained_Or_Tagged_Item (Formal)
28305 then
28306 Append_New_Elmt (Formal, Subp_Inputs);
28307 end if;
28308 end if;
28310 Next_Entity (Formal);
28311 end loop;
28313 -- Otherwise the input denotes a task type, a task body, or the
28314 -- anonymous object created for a single task type.
28316 elsif Ekind_In (Subp_Id, E_Task_Type, E_Task_Body)
28317 or else Is_Single_Task_Object (Subp_Id)
28318 then
28319 Subp_Decl := Declaration_Node (Subp_Id);
28320 Spec_Id := Unique_Defining_Entity (Subp_Decl);
28321 end if;
28323 -- When processing an entry, subprogram or task body, look for pragmas
28324 -- Refined_Depends and Refined_Global as they specify the inputs and
28325 -- outputs.
28327 if Is_Entry_Body (Subp_Id)
28328 or else Ekind_In (Subp_Id, E_Subprogram_Body, E_Task_Body)
28329 then
28330 Depends := Get_Pragma (Subp_Id, Pragma_Refined_Depends);
28331 Global := Get_Pragma (Subp_Id, Pragma_Refined_Global);
28333 -- Subprogram declaration or stand alone body case, look for pragmas
28334 -- Depends and Global
28336 else
28337 Depends := Get_Pragma (Spec_Id, Pragma_Depends);
28338 Global := Get_Pragma (Spec_Id, Pragma_Global);
28339 end if;
28341 -- Pragma [Refined_]Global takes precedence over [Refined_]Depends
28342 -- because it provides finer granularity of inputs and outputs.
28344 if Present (Global) then
28345 Global_Seen := True;
28346 Collect_Global_List (Expression (Get_Argument (Global, Spec_Id)));
28348 -- When the related subprogram lacks pragma [Refined_]Global, fall back
28349 -- to [Refined_]Depends if the caller requests this behavior. Synthesize
28350 -- the inputs and outputs from [Refined_]Depends.
28352 elsif Synthesize and then Present (Depends) then
28353 Clauses := Expression (Get_Argument (Depends, Spec_Id));
28355 -- Multiple dependency clauses appear as an aggregate
28357 if Nkind (Clauses) = N_Aggregate then
28358 Clause := First (Component_Associations (Clauses));
28359 while Present (Clause) loop
28360 Collect_Dependency_Clause (Clause);
28361 Next (Clause);
28362 end loop;
28364 -- Otherwise this is a single dependency clause
28366 else
28367 Collect_Dependency_Clause (Clauses);
28368 end if;
28369 end if;
28371 -- The current instance of a protected type acts as a formal parameter
28372 -- of mode IN for functions and IN OUT for entries and procedures
28373 -- (SPARK RM 6.1.4).
28375 if Ekind (Scope (Spec_Id)) = E_Protected_Type then
28376 Typ := Scope (Spec_Id);
28378 -- Use the anonymous object when the type is single protected
28380 if Is_Single_Concurrent_Type_Declaration (Declaration_Node (Typ)) then
28381 Typ := Anonymous_Object (Typ);
28382 end if;
28384 Append_New_Elmt (Typ, Subp_Inputs);
28386 if Ekind_In (Spec_Id, E_Entry, E_Entry_Family, E_Procedure) then
28387 Append_New_Elmt (Typ, Subp_Outputs);
28388 end if;
28390 -- The current instance of a task type acts as a formal parameter of
28391 -- mode IN OUT (SPARK RM 6.1.4).
28393 elsif Ekind (Spec_Id) = E_Task_Type then
28394 Typ := Spec_Id;
28396 -- Use the anonymous object when the type is single task
28398 if Is_Single_Concurrent_Type_Declaration (Declaration_Node (Typ)) then
28399 Typ := Anonymous_Object (Typ);
28400 end if;
28402 Append_New_Elmt (Typ, Subp_Inputs);
28403 Append_New_Elmt (Typ, Subp_Outputs);
28405 elsif Is_Single_Task_Object (Spec_Id) then
28406 Append_New_Elmt (Spec_Id, Subp_Inputs);
28407 Append_New_Elmt (Spec_Id, Subp_Outputs);
28408 end if;
28409 end Collect_Subprogram_Inputs_Outputs;
28411 ---------------------------
28412 -- Contract_Freeze_Error --
28413 ---------------------------
28415 procedure Contract_Freeze_Error
28416 (Contract_Id : Entity_Id;
28417 Freeze_Id : Entity_Id)
28419 begin
28420 Error_Msg_Name_1 := Chars (Contract_Id);
28421 Error_Msg_Sloc := Sloc (Freeze_Id);
28423 SPARK_Msg_NE
28424 ("body & declared # freezes the contract of%", Contract_Id, Freeze_Id);
28425 SPARK_Msg_N
28426 ("\all contractual items must be declared before body #", Contract_Id);
28427 end Contract_Freeze_Error;
28429 ---------------------------------
28430 -- Delay_Config_Pragma_Analyze --
28431 ---------------------------------
28433 function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
28434 begin
28435 return Nam_In (Pragma_Name_Unmapped (N),
28436 Name_Interrupt_State, Name_Priority_Specific_Dispatching);
28437 end Delay_Config_Pragma_Analyze;
28439 -----------------------
28440 -- Duplication_Error --
28441 -----------------------
28443 procedure Duplication_Error (Prag : Node_Id; Prev : Node_Id) is
28444 Prag_From_Asp : constant Boolean := From_Aspect_Specification (Prag);
28445 Prev_From_Asp : constant Boolean := From_Aspect_Specification (Prev);
28447 begin
28448 Error_Msg_Sloc := Sloc (Prev);
28449 Error_Msg_Name_1 := Original_Aspect_Pragma_Name (Prag);
28451 -- Emit a precise message to distinguish between source pragmas and
28452 -- pragmas generated from aspects. The ordering of the two pragmas is
28453 -- the following:
28455 -- Prev -- ok
28456 -- Prag -- duplicate
28458 -- No error is emitted when both pragmas come from aspects because this
28459 -- is already detected by the general aspect analysis mechanism.
28461 if Prag_From_Asp and Prev_From_Asp then
28462 null;
28463 elsif Prag_From_Asp then
28464 Error_Msg_N ("aspect % duplicates pragma declared #", Prag);
28465 elsif Prev_From_Asp then
28466 Error_Msg_N ("pragma % duplicates aspect declared #", Prag);
28467 else
28468 Error_Msg_N ("pragma % duplicates pragma declared #", Prag);
28469 end if;
28470 end Duplication_Error;
28472 ------------------------------
28473 -- Find_Encapsulating_State --
28474 ------------------------------
28476 function Find_Encapsulating_State
28477 (States : Elist_Id;
28478 Constit_Id : Entity_Id) return Entity_Id
28480 State_Id : Entity_Id;
28482 begin
28483 -- Since a constituent may be part of a larger constituent set, climb
28484 -- the encapsulating state chain looking for a state that appears in
28485 -- States.
28487 State_Id := Encapsulating_State (Constit_Id);
28488 while Present (State_Id) loop
28489 if Contains (States, State_Id) then
28490 return State_Id;
28491 end if;
28493 State_Id := Encapsulating_State (State_Id);
28494 end loop;
28496 return Empty;
28497 end Find_Encapsulating_State;
28499 --------------------------
28500 -- Find_Related_Context --
28501 --------------------------
28503 function Find_Related_Context
28504 (Prag : Node_Id;
28505 Do_Checks : Boolean := False) return Node_Id
28507 Stmt : Node_Id;
28509 begin
28510 Stmt := Prev (Prag);
28511 while Present (Stmt) loop
28513 -- Skip prior pragmas, but check for duplicates
28515 if Nkind (Stmt) = N_Pragma then
28516 if Do_Checks
28517 and then Pragma_Name (Stmt) = Pragma_Name (Prag)
28518 then
28519 Duplication_Error
28520 (Prag => Prag,
28521 Prev => Stmt);
28522 end if;
28524 -- Skip internally generated code
28526 elsif not Comes_From_Source (Stmt) then
28528 -- The anonymous object created for a single concurrent type is a
28529 -- suitable context.
28531 if Nkind (Stmt) = N_Object_Declaration
28532 and then Is_Single_Concurrent_Object (Defining_Entity (Stmt))
28533 then
28534 return Stmt;
28535 end if;
28537 -- Return the current source construct
28539 else
28540 return Stmt;
28541 end if;
28543 Prev (Stmt);
28544 end loop;
28546 return Empty;
28547 end Find_Related_Context;
28549 --------------------------------------
28550 -- Find_Related_Declaration_Or_Body --
28551 --------------------------------------
28553 function Find_Related_Declaration_Or_Body
28554 (Prag : Node_Id;
28555 Do_Checks : Boolean := False) return Node_Id
28557 Prag_Nam : constant Name_Id := Original_Aspect_Pragma_Name (Prag);
28559 procedure Expression_Function_Error;
28560 -- Emit an error concerning pragma Prag that illegaly applies to an
28561 -- expression function.
28563 -------------------------------
28564 -- Expression_Function_Error --
28565 -------------------------------
28567 procedure Expression_Function_Error is
28568 begin
28569 Error_Msg_Name_1 := Prag_Nam;
28571 -- Emit a precise message to distinguish between source pragmas and
28572 -- pragmas generated from aspects.
28574 if From_Aspect_Specification (Prag) then
28575 Error_Msg_N
28576 ("aspect % cannot apply to a stand alone expression function",
28577 Prag);
28578 else
28579 Error_Msg_N
28580 ("pragma % cannot apply to a stand alone expression function",
28581 Prag);
28582 end if;
28583 end Expression_Function_Error;
28585 -- Local variables
28587 Context : constant Node_Id := Parent (Prag);
28588 Stmt : Node_Id;
28590 Look_For_Body : constant Boolean :=
28591 Nam_In (Prag_Nam, Name_Refined_Depends,
28592 Name_Refined_Global,
28593 Name_Refined_Post);
28594 -- Refinement pragmas must be associated with a subprogram body [stub]
28596 -- Start of processing for Find_Related_Declaration_Or_Body
28598 begin
28599 Stmt := Prev (Prag);
28600 while Present (Stmt) loop
28602 -- Skip prior pragmas, but check for duplicates. Pragmas produced
28603 -- by splitting a complex pre/postcondition are not considered to
28604 -- be duplicates.
28606 if Nkind (Stmt) = N_Pragma then
28607 if Do_Checks
28608 and then not Split_PPC (Stmt)
28609 and then Original_Aspect_Pragma_Name (Stmt) = Prag_Nam
28610 then
28611 Duplication_Error
28612 (Prag => Prag,
28613 Prev => Stmt);
28614 end if;
28616 -- Emit an error when a refinement pragma appears on an expression
28617 -- function without a completion.
28619 elsif Do_Checks
28620 and then Look_For_Body
28621 and then Nkind (Stmt) = N_Subprogram_Declaration
28622 and then Nkind (Original_Node (Stmt)) = N_Expression_Function
28623 and then not Has_Completion (Defining_Entity (Stmt))
28624 then
28625 Expression_Function_Error;
28626 return Empty;
28628 -- The refinement pragma applies to a subprogram body stub
28630 elsif Look_For_Body
28631 and then Nkind (Stmt) = N_Subprogram_Body_Stub
28632 then
28633 return Stmt;
28635 -- Skip internally generated code
28637 elsif not Comes_From_Source (Stmt) then
28639 -- The anonymous object created for a single concurrent type is a
28640 -- suitable context.
28642 if Nkind (Stmt) = N_Object_Declaration
28643 and then Is_Single_Concurrent_Object (Defining_Entity (Stmt))
28644 then
28645 return Stmt;
28647 elsif Nkind (Stmt) = N_Subprogram_Declaration then
28649 -- The subprogram declaration is an internally generated spec
28650 -- for an expression function.
28652 if Nkind (Original_Node (Stmt)) = N_Expression_Function then
28653 return Stmt;
28655 -- The subprogram is actually an instance housed within an
28656 -- anonymous wrapper package.
28658 elsif Present (Generic_Parent (Specification (Stmt))) then
28659 return Stmt;
28660 end if;
28661 end if;
28663 -- Return the current construct which is either a subprogram body,
28664 -- a subprogram declaration or is illegal.
28666 else
28667 return Stmt;
28668 end if;
28670 Prev (Stmt);
28671 end loop;
28673 -- If we fall through, then the pragma was either the first declaration
28674 -- or it was preceded by other pragmas and no source constructs.
28676 -- The pragma is associated with a library-level subprogram
28678 if Nkind (Context) = N_Compilation_Unit_Aux then
28679 return Unit (Parent (Context));
28681 -- The pragma appears inside the declarations of an entry body
28683 elsif Nkind (Context) = N_Entry_Body then
28684 return Context;
28686 -- The pragma appears inside the statements of a subprogram body. This
28687 -- placement is the result of subprogram contract expansion.
28689 elsif Nkind (Context) = N_Handled_Sequence_Of_Statements then
28690 return Parent (Context);
28692 -- The pragma appears inside the declarative part of a subprogram body
28694 elsif Nkind (Context) = N_Subprogram_Body then
28695 return Context;
28697 -- The pragma appears inside the declarative part of a task body
28699 elsif Nkind (Context) = N_Task_Body then
28700 return Context;
28702 -- The pragma is a byproduct of aspect expansion, return the related
28703 -- context of the original aspect. This case has a lower priority as
28704 -- the above circuitry pinpoints precisely the related context.
28706 elsif Present (Corresponding_Aspect (Prag)) then
28707 return Parent (Corresponding_Aspect (Prag));
28709 -- No candidate subprogram [body] found
28711 else
28712 return Empty;
28713 end if;
28714 end Find_Related_Declaration_Or_Body;
28716 ----------------------------------
28717 -- Find_Related_Package_Or_Body --
28718 ----------------------------------
28720 function Find_Related_Package_Or_Body
28721 (Prag : Node_Id;
28722 Do_Checks : Boolean := False) return Node_Id
28724 Context : constant Node_Id := Parent (Prag);
28725 Prag_Nam : constant Name_Id := Pragma_Name (Prag);
28726 Stmt : Node_Id;
28728 begin
28729 Stmt := Prev (Prag);
28730 while Present (Stmt) loop
28732 -- Skip prior pragmas, but check for duplicates
28734 if Nkind (Stmt) = N_Pragma then
28735 if Do_Checks and then Pragma_Name (Stmt) = Prag_Nam then
28736 Duplication_Error
28737 (Prag => Prag,
28738 Prev => Stmt);
28739 end if;
28741 -- Skip internally generated code
28743 elsif not Comes_From_Source (Stmt) then
28744 if Nkind (Stmt) = N_Subprogram_Declaration then
28746 -- The subprogram declaration is an internally generated spec
28747 -- for an expression function.
28749 if Nkind (Original_Node (Stmt)) = N_Expression_Function then
28750 return Stmt;
28752 -- The subprogram is actually an instance housed within an
28753 -- anonymous wrapper package.
28755 elsif Present (Generic_Parent (Specification (Stmt))) then
28756 return Stmt;
28757 end if;
28758 end if;
28760 -- Return the current source construct which is illegal
28762 else
28763 return Stmt;
28764 end if;
28766 Prev (Stmt);
28767 end loop;
28769 -- If we fall through, then the pragma was either the first declaration
28770 -- or it was preceded by other pragmas and no source constructs.
28772 -- The pragma is associated with a package. The immediate context in
28773 -- this case is the specification of the package.
28775 if Nkind (Context) = N_Package_Specification then
28776 return Parent (Context);
28778 -- The pragma appears in the declarations of a package body
28780 elsif Nkind (Context) = N_Package_Body then
28781 return Context;
28783 -- The pragma appears in the statements of a package body
28785 elsif Nkind (Context) = N_Handled_Sequence_Of_Statements
28786 and then Nkind (Parent (Context)) = N_Package_Body
28787 then
28788 return Parent (Context);
28790 -- The pragma is a byproduct of aspect expansion, return the related
28791 -- context of the original aspect. This case has a lower priority as
28792 -- the above circuitry pinpoints precisely the related context.
28794 elsif Present (Corresponding_Aspect (Prag)) then
28795 return Parent (Corresponding_Aspect (Prag));
28797 -- No candidate packge [body] found
28799 else
28800 return Empty;
28801 end if;
28802 end Find_Related_Package_Or_Body;
28804 ------------------
28805 -- Get_Argument --
28806 ------------------
28808 function Get_Argument
28809 (Prag : Node_Id;
28810 Context_Id : Entity_Id := Empty) return Node_Id
28812 Args : constant List_Id := Pragma_Argument_Associations (Prag);
28814 begin
28815 -- Use the expression of the original aspect when compiling for ASIS or
28816 -- when analyzing the template of a generic unit. In both cases the
28817 -- aspect's tree must be decorated to allow for ASIS queries or to save
28818 -- the global references in the generic context.
28820 if From_Aspect_Specification (Prag)
28821 and then (ASIS_Mode or else (Present (Context_Id)
28822 and then Is_Generic_Unit (Context_Id)))
28823 then
28824 return Corresponding_Aspect (Prag);
28826 -- Otherwise use the expression of the pragma
28828 elsif Present (Args) then
28829 return First (Args);
28831 else
28832 return Empty;
28833 end if;
28834 end Get_Argument;
28836 -------------------------
28837 -- Get_Base_Subprogram --
28838 -------------------------
28840 function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
28841 Result : Entity_Id;
28843 begin
28844 -- Follow subprogram renaming chain
28846 Result := Def_Id;
28848 if Is_Subprogram (Result)
28849 and then
28850 Nkind (Parent (Declaration_Node (Result))) =
28851 N_Subprogram_Renaming_Declaration
28852 and then Present (Alias (Result))
28853 then
28854 Result := Alias (Result);
28855 end if;
28857 return Result;
28858 end Get_Base_Subprogram;
28860 -----------------------
28861 -- Get_SPARK_Mode_Type --
28862 -----------------------
28864 function Get_SPARK_Mode_Type (N : Name_Id) return SPARK_Mode_Type is
28865 begin
28866 if N = Name_On then
28867 return On;
28868 elsif N = Name_Off then
28869 return Off;
28871 -- Any other argument is illegal
28873 else
28874 raise Program_Error;
28875 end if;
28876 end Get_SPARK_Mode_Type;
28878 ------------------------------------
28879 -- Get_SPARK_Mode_From_Annotation --
28880 ------------------------------------
28882 function Get_SPARK_Mode_From_Annotation
28883 (N : Node_Id) return SPARK_Mode_Type
28885 Mode : Node_Id;
28887 begin
28888 if Nkind (N) = N_Aspect_Specification then
28889 Mode := Expression (N);
28891 else pragma Assert (Nkind (N) = N_Pragma);
28892 Mode := First (Pragma_Argument_Associations (N));
28894 if Present (Mode) then
28895 Mode := Get_Pragma_Arg (Mode);
28896 end if;
28897 end if;
28899 -- Aspect or pragma SPARK_Mode specifies an explicit mode
28901 if Present (Mode) then
28902 if Nkind (Mode) = N_Identifier then
28903 return Get_SPARK_Mode_Type (Chars (Mode));
28905 -- In case of a malformed aspect or pragma, return the default None
28907 else
28908 return None;
28909 end if;
28911 -- Otherwise the lack of an expression defaults SPARK_Mode to On
28913 else
28914 return On;
28915 end if;
28916 end Get_SPARK_Mode_From_Annotation;
28918 ---------------------------
28919 -- Has_Extra_Parentheses --
28920 ---------------------------
28922 function Has_Extra_Parentheses (Clause : Node_Id) return Boolean is
28923 Expr : Node_Id;
28925 begin
28926 -- The aggregate should not have an expression list because a clause
28927 -- is always interpreted as a component association. The only way an
28928 -- expression list can sneak in is by adding extra parentheses around
28929 -- the individual clauses:
28931 -- Depends (Output => Input) -- proper form
28932 -- Depends ((Output => Input)) -- extra parentheses
28934 -- Since the extra parentheses are not allowed by the syntax of the
28935 -- pragma, flag them now to avoid emitting misleading errors down the
28936 -- line.
28938 if Nkind (Clause) = N_Aggregate
28939 and then Present (Expressions (Clause))
28940 then
28941 Expr := First (Expressions (Clause));
28942 while Present (Expr) loop
28944 -- A dependency clause surrounded by extra parentheses appears
28945 -- as an aggregate of component associations with an optional
28946 -- Paren_Count set.
28948 if Nkind (Expr) = N_Aggregate
28949 and then Present (Component_Associations (Expr))
28950 then
28951 SPARK_Msg_N
28952 ("dependency clause contains extra parentheses", Expr);
28954 -- Otherwise the expression is a malformed construct
28956 else
28957 SPARK_Msg_N ("malformed dependency clause", Expr);
28958 end if;
28960 Next (Expr);
28961 end loop;
28963 return True;
28964 end if;
28966 return False;
28967 end Has_Extra_Parentheses;
28969 ----------------
28970 -- Initialize --
28971 ----------------
28973 procedure Initialize is
28974 begin
28975 Externals.Init;
28976 end Initialize;
28978 --------
28979 -- ip --
28980 --------
28982 procedure ip is
28983 begin
28984 Dummy := Dummy + 1;
28985 end ip;
28987 -----------------------------
28988 -- Is_Config_Static_String --
28989 -----------------------------
28991 function Is_Config_Static_String (Arg : Node_Id) return Boolean is
28993 function Add_Config_Static_String (Arg : Node_Id) return Boolean;
28994 -- This is an internal recursive function that is just like the outer
28995 -- function except that it adds the string to the name buffer rather
28996 -- than placing the string in the name buffer.
28998 ------------------------------
28999 -- Add_Config_Static_String --
29000 ------------------------------
29002 function Add_Config_Static_String (Arg : Node_Id) return Boolean is
29003 N : Node_Id;
29004 C : Char_Code;
29006 begin
29007 N := Arg;
29009 if Nkind (N) = N_Op_Concat then
29010 if Add_Config_Static_String (Left_Opnd (N)) then
29011 N := Right_Opnd (N);
29012 else
29013 return False;
29014 end if;
29015 end if;
29017 if Nkind (N) /= N_String_Literal then
29018 Error_Msg_N ("string literal expected for pragma argument", N);
29019 return False;
29021 else
29022 for J in 1 .. String_Length (Strval (N)) loop
29023 C := Get_String_Char (Strval (N), J);
29025 if not In_Character_Range (C) then
29026 Error_Msg
29027 ("string literal contains invalid wide character",
29028 Sloc (N) + 1 + Source_Ptr (J));
29029 return False;
29030 end if;
29032 Add_Char_To_Name_Buffer (Get_Character (C));
29033 end loop;
29034 end if;
29036 return True;
29037 end Add_Config_Static_String;
29039 -- Start of processing for Is_Config_Static_String
29041 begin
29042 Name_Len := 0;
29044 return Add_Config_Static_String (Arg);
29045 end Is_Config_Static_String;
29047 ---------------------
29048 -- Is_CCT_Instance --
29049 ---------------------
29051 function Is_CCT_Instance
29052 (Ref_Id : Entity_Id;
29053 Context_Id : Entity_Id) return Boolean
29055 S : Entity_Id;
29056 Typ : Entity_Id;
29058 begin
29059 -- When the reference denotes a single protected type, the context is
29060 -- either a protected subprogram or its body.
29062 if Is_Single_Protected_Object (Ref_Id) then
29063 Typ := Scope (Context_Id);
29065 return
29066 Ekind (Typ) = E_Protected_Type
29067 and then Present (Anonymous_Object (Typ))
29068 and then Anonymous_Object (Typ) = Ref_Id;
29070 -- When the reference denotes a single task type, the context is either
29071 -- the same type or if inside the body, the anonymous task type.
29073 elsif Is_Single_Task_Object (Ref_Id) then
29074 if Ekind (Context_Id) = E_Task_Type then
29075 return
29076 Present (Anonymous_Object (Context_Id))
29077 and then Anonymous_Object (Context_Id) = Ref_Id;
29078 else
29079 return Ref_Id = Context_Id;
29080 end if;
29082 -- Otherwise the reference denotes a protected or a task type. Climb the
29083 -- scope chain looking for an enclosing concurrent type that matches the
29084 -- referenced entity.
29086 else
29087 pragma Assert (Ekind_In (Ref_Id, E_Protected_Type, E_Task_Type));
29089 S := Current_Scope;
29090 while Present (S) and then S /= Standard_Standard loop
29091 if Ekind_In (S, E_Protected_Type, E_Task_Type)
29092 and then S = Ref_Id
29093 then
29094 return True;
29095 end if;
29097 S := Scope (S);
29098 end loop;
29099 end if;
29101 return False;
29102 end Is_CCT_Instance;
29104 -------------------------------
29105 -- Is_Elaboration_SPARK_Mode --
29106 -------------------------------
29108 function Is_Elaboration_SPARK_Mode (N : Node_Id) return Boolean is
29109 begin
29110 pragma Assert
29111 (Nkind (N) = N_Pragma
29112 and then Pragma_Name (N) = Name_SPARK_Mode
29113 and then Is_List_Member (N));
29115 -- Pragma SPARK_Mode affects the elaboration of a package body when it
29116 -- appears in the statement part of the body.
29118 return
29119 Present (Parent (N))
29120 and then Nkind (Parent (N)) = N_Handled_Sequence_Of_Statements
29121 and then List_Containing (N) = Statements (Parent (N))
29122 and then Present (Parent (Parent (N)))
29123 and then Nkind (Parent (Parent (N))) = N_Package_Body;
29124 end Is_Elaboration_SPARK_Mode;
29126 -----------------------
29127 -- Is_Enabled_Pragma --
29128 -----------------------
29130 function Is_Enabled_Pragma (Prag : Node_Id) return Boolean is
29131 Arg : Node_Id;
29133 begin
29134 if Present (Prag) then
29135 Arg := First (Pragma_Argument_Associations (Prag));
29137 if Present (Arg) then
29138 return Is_True (Expr_Value (Get_Pragma_Arg (Arg)));
29140 -- The lack of a Boolean argument automatically enables the pragma
29142 else
29143 return True;
29144 end if;
29146 -- The pragma is missing, therefore it is not enabled
29148 else
29149 return False;
29150 end if;
29151 end Is_Enabled_Pragma;
29153 -----------------------------------------
29154 -- Is_Non_Significant_Pragma_Reference --
29155 -----------------------------------------
29157 -- This function makes use of the following static table which indicates
29158 -- whether appearance of some name in a given pragma is to be considered
29159 -- as a reference for the purposes of warnings about unreferenced objects.
29161 -- -1 indicates that appearence in any argument is significant
29162 -- 0 indicates that appearance in any argument is not significant
29163 -- +n indicates that appearance as argument n is significant, but all
29164 -- other arguments are not significant
29165 -- 9n arguments from n on are significant, before n insignificant
29167 Sig_Flags : constant array (Pragma_Id) of Int :=
29168 (Pragma_Abort_Defer => -1,
29169 Pragma_Abstract_State => -1,
29170 Pragma_Ada_83 => -1,
29171 Pragma_Ada_95 => -1,
29172 Pragma_Ada_05 => -1,
29173 Pragma_Ada_2005 => -1,
29174 Pragma_Ada_12 => -1,
29175 Pragma_Ada_2012 => -1,
29176 Pragma_All_Calls_Remote => -1,
29177 Pragma_Allow_Integer_Address => -1,
29178 Pragma_Annotate => 93,
29179 Pragma_Assert => -1,
29180 Pragma_Assert_And_Cut => -1,
29181 Pragma_Assertion_Policy => 0,
29182 Pragma_Assume => -1,
29183 Pragma_Assume_No_Invalid_Values => 0,
29184 Pragma_Async_Readers => 0,
29185 Pragma_Async_Writers => 0,
29186 Pragma_Asynchronous => 0,
29187 Pragma_Atomic => 0,
29188 Pragma_Atomic_Components => 0,
29189 Pragma_Attach_Handler => -1,
29190 Pragma_Attribute_Definition => 92,
29191 Pragma_Check => -1,
29192 Pragma_Check_Float_Overflow => 0,
29193 Pragma_Check_Name => 0,
29194 Pragma_Check_Policy => 0,
29195 Pragma_CPP_Class => 0,
29196 Pragma_CPP_Constructor => 0,
29197 Pragma_CPP_Virtual => 0,
29198 Pragma_CPP_Vtable => 0,
29199 Pragma_CPU => -1,
29200 Pragma_C_Pass_By_Copy => 0,
29201 Pragma_Comment => -1,
29202 Pragma_Common_Object => 0,
29203 Pragma_Compile_Time_Error => -1,
29204 Pragma_Compile_Time_Warning => -1,
29205 Pragma_Compiler_Unit => -1,
29206 Pragma_Compiler_Unit_Warning => -1,
29207 Pragma_Complete_Representation => 0,
29208 Pragma_Complex_Representation => 0,
29209 Pragma_Component_Alignment => 0,
29210 Pragma_Constant_After_Elaboration => 0,
29211 Pragma_Contract_Cases => -1,
29212 Pragma_Controlled => 0,
29213 Pragma_Convention => 0,
29214 Pragma_Convention_Identifier => 0,
29215 Pragma_Deadline_Floor => -1,
29216 Pragma_Debug => -1,
29217 Pragma_Debug_Policy => 0,
29218 Pragma_Detect_Blocking => 0,
29219 Pragma_Default_Initial_Condition => -1,
29220 Pragma_Default_Scalar_Storage_Order => 0,
29221 Pragma_Default_Storage_Pool => 0,
29222 Pragma_Depends => -1,
29223 Pragma_Disable_Atomic_Synchronization => 0,
29224 Pragma_Discard_Names => 0,
29225 Pragma_Dispatching_Domain => -1,
29226 Pragma_Effective_Reads => 0,
29227 Pragma_Effective_Writes => 0,
29228 Pragma_Elaborate => 0,
29229 Pragma_Elaborate_All => 0,
29230 Pragma_Elaborate_Body => 0,
29231 Pragma_Elaboration_Checks => 0,
29232 Pragma_Eliminate => 0,
29233 Pragma_Enable_Atomic_Synchronization => 0,
29234 Pragma_Export => -1,
29235 Pragma_Export_Function => -1,
29236 Pragma_Export_Object => -1,
29237 Pragma_Export_Procedure => -1,
29238 Pragma_Export_Value => -1,
29239 Pragma_Export_Valued_Procedure => -1,
29240 Pragma_Extend_System => -1,
29241 Pragma_Extensions_Allowed => 0,
29242 Pragma_Extensions_Visible => 0,
29243 Pragma_External => -1,
29244 Pragma_Favor_Top_Level => 0,
29245 Pragma_External_Name_Casing => 0,
29246 Pragma_Fast_Math => 0,
29247 Pragma_Finalize_Storage_Only => 0,
29248 Pragma_Ghost => 0,
29249 Pragma_Global => -1,
29250 Pragma_Ident => -1,
29251 Pragma_Ignore_Pragma => 0,
29252 Pragma_Implementation_Defined => -1,
29253 Pragma_Implemented => -1,
29254 Pragma_Implicit_Packing => 0,
29255 Pragma_Import => 93,
29256 Pragma_Import_Function => 0,
29257 Pragma_Import_Object => 0,
29258 Pragma_Import_Procedure => 0,
29259 Pragma_Import_Valued_Procedure => 0,
29260 Pragma_Independent => 0,
29261 Pragma_Independent_Components => 0,
29262 Pragma_Initial_Condition => -1,
29263 Pragma_Initialize_Scalars => 0,
29264 Pragma_Initializes => -1,
29265 Pragma_Inline => 0,
29266 Pragma_Inline_Always => 0,
29267 Pragma_Inline_Generic => 0,
29268 Pragma_Inspection_Point => -1,
29269 Pragma_Interface => 92,
29270 Pragma_Interface_Name => 0,
29271 Pragma_Interrupt_Handler => -1,
29272 Pragma_Interrupt_Priority => -1,
29273 Pragma_Interrupt_State => -1,
29274 Pragma_Invariant => -1,
29275 Pragma_Keep_Names => 0,
29276 Pragma_License => 0,
29277 Pragma_Link_With => -1,
29278 Pragma_Linker_Alias => -1,
29279 Pragma_Linker_Constructor => -1,
29280 Pragma_Linker_Destructor => -1,
29281 Pragma_Linker_Options => -1,
29282 Pragma_Linker_Section => 0,
29283 Pragma_List => 0,
29284 Pragma_Lock_Free => 0,
29285 Pragma_Locking_Policy => 0,
29286 Pragma_Loop_Invariant => -1,
29287 Pragma_Loop_Optimize => 0,
29288 Pragma_Loop_Variant => -1,
29289 Pragma_Machine_Attribute => -1,
29290 Pragma_Main => -1,
29291 Pragma_Main_Storage => -1,
29292 Pragma_Max_Queue_Length => 0,
29293 Pragma_Memory_Size => 0,
29294 Pragma_No_Return => 0,
29295 Pragma_No_Body => 0,
29296 Pragma_No_Elaboration_Code_All => 0,
29297 Pragma_No_Heap_Finalization => 0,
29298 Pragma_No_Inline => 0,
29299 Pragma_No_Run_Time => -1,
29300 Pragma_No_Strict_Aliasing => -1,
29301 Pragma_No_Tagged_Streams => 0,
29302 Pragma_Normalize_Scalars => 0,
29303 Pragma_Obsolescent => 0,
29304 Pragma_Optimize => 0,
29305 Pragma_Optimize_Alignment => 0,
29306 Pragma_Overflow_Mode => 0,
29307 Pragma_Overriding_Renamings => 0,
29308 Pragma_Ordered => 0,
29309 Pragma_Pack => 0,
29310 Pragma_Page => 0,
29311 Pragma_Part_Of => 0,
29312 Pragma_Partition_Elaboration_Policy => 0,
29313 Pragma_Passive => 0,
29314 Pragma_Persistent_BSS => 0,
29315 Pragma_Polling => 0,
29316 Pragma_Prefix_Exception_Messages => 0,
29317 Pragma_Post => -1,
29318 Pragma_Postcondition => -1,
29319 Pragma_Post_Class => -1,
29320 Pragma_Pre => -1,
29321 Pragma_Precondition => -1,
29322 Pragma_Predicate => -1,
29323 Pragma_Predicate_Failure => -1,
29324 Pragma_Preelaborable_Initialization => -1,
29325 Pragma_Preelaborate => 0,
29326 Pragma_Pre_Class => -1,
29327 Pragma_Priority => -1,
29328 Pragma_Priority_Specific_Dispatching => 0,
29329 Pragma_Profile => 0,
29330 Pragma_Profile_Warnings => 0,
29331 Pragma_Propagate_Exceptions => 0,
29332 Pragma_Provide_Shift_Operators => 0,
29333 Pragma_Psect_Object => 0,
29334 Pragma_Pure => 0,
29335 Pragma_Pure_Function => 0,
29336 Pragma_Queuing_Policy => 0,
29337 Pragma_Rational => 0,
29338 Pragma_Ravenscar => 0,
29339 Pragma_Refined_Depends => -1,
29340 Pragma_Refined_Global => -1,
29341 Pragma_Refined_Post => -1,
29342 Pragma_Refined_State => -1,
29343 Pragma_Relative_Deadline => 0,
29344 Pragma_Rename_Pragma => 0,
29345 Pragma_Remote_Access_Type => -1,
29346 Pragma_Remote_Call_Interface => -1,
29347 Pragma_Remote_Types => -1,
29348 Pragma_Restricted_Run_Time => 0,
29349 Pragma_Restriction_Warnings => 0,
29350 Pragma_Restrictions => 0,
29351 Pragma_Reviewable => -1,
29352 Pragma_Secondary_Stack_Size => -1,
29353 Pragma_Short_Circuit_And_Or => 0,
29354 Pragma_Share_Generic => 0,
29355 Pragma_Shared => 0,
29356 Pragma_Shared_Passive => 0,
29357 Pragma_Short_Descriptors => 0,
29358 Pragma_Simple_Storage_Pool_Type => 0,
29359 Pragma_Source_File_Name => 0,
29360 Pragma_Source_File_Name_Project => 0,
29361 Pragma_Source_Reference => 0,
29362 Pragma_SPARK_Mode => 0,
29363 Pragma_Storage_Size => -1,
29364 Pragma_Storage_Unit => 0,
29365 Pragma_Static_Elaboration_Desired => 0,
29366 Pragma_Stream_Convert => 0,
29367 Pragma_Style_Checks => 0,
29368 Pragma_Subtitle => 0,
29369 Pragma_Suppress => 0,
29370 Pragma_Suppress_Exception_Locations => 0,
29371 Pragma_Suppress_All => 0,
29372 Pragma_Suppress_Debug_Info => 0,
29373 Pragma_Suppress_Initialization => 0,
29374 Pragma_System_Name => 0,
29375 Pragma_Task_Dispatching_Policy => 0,
29376 Pragma_Task_Info => -1,
29377 Pragma_Task_Name => -1,
29378 Pragma_Task_Storage => -1,
29379 Pragma_Test_Case => -1,
29380 Pragma_Thread_Local_Storage => -1,
29381 Pragma_Time_Slice => -1,
29382 Pragma_Title => 0,
29383 Pragma_Type_Invariant => -1,
29384 Pragma_Type_Invariant_Class => -1,
29385 Pragma_Unchecked_Union => 0,
29386 Pragma_Unevaluated_Use_Of_Old => 0,
29387 Pragma_Unimplemented_Unit => 0,
29388 Pragma_Universal_Aliasing => 0,
29389 Pragma_Universal_Data => 0,
29390 Pragma_Unmodified => 0,
29391 Pragma_Unreferenced => 0,
29392 Pragma_Unreferenced_Objects => 0,
29393 Pragma_Unreserve_All_Interrupts => 0,
29394 Pragma_Unsuppress => 0,
29395 Pragma_Unused => 0,
29396 Pragma_Use_VADS_Size => 0,
29397 Pragma_Validity_Checks => 0,
29398 Pragma_Volatile => 0,
29399 Pragma_Volatile_Components => 0,
29400 Pragma_Volatile_Full_Access => 0,
29401 Pragma_Volatile_Function => 0,
29402 Pragma_Warning_As_Error => 0,
29403 Pragma_Warnings => 0,
29404 Pragma_Weak_External => 0,
29405 Pragma_Wide_Character_Encoding => 0,
29406 Unknown_Pragma => 0);
29408 function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
29409 Id : Pragma_Id;
29410 P : Node_Id;
29411 C : Int;
29412 AN : Nat;
29414 function Arg_No return Nat;
29415 -- Returns an integer showing what argument we are in. A value of
29416 -- zero means we are not in any of the arguments.
29418 ------------
29419 -- Arg_No --
29420 ------------
29422 function Arg_No return Nat is
29423 A : Node_Id;
29424 N : Nat;
29426 begin
29427 A := First (Pragma_Argument_Associations (Parent (P)));
29428 N := 1;
29429 loop
29430 if No (A) then
29431 return 0;
29432 elsif A = P then
29433 return N;
29434 end if;
29436 Next (A);
29437 N := N + 1;
29438 end loop;
29439 end Arg_No;
29441 -- Start of processing for Non_Significant_Pragma_Reference
29443 begin
29444 P := Parent (N);
29446 if Nkind (P) /= N_Pragma_Argument_Association then
29447 return False;
29449 else
29450 Id := Get_Pragma_Id (Parent (P));
29451 C := Sig_Flags (Id);
29452 AN := Arg_No;
29454 if AN = 0 then
29455 return False;
29456 end if;
29458 case C is
29459 when -1 =>
29460 return False;
29462 when 0 =>
29463 return True;
29465 when 92 .. 99 =>
29466 return AN < (C - 90);
29468 when others =>
29469 return AN /= C;
29470 end case;
29471 end if;
29472 end Is_Non_Significant_Pragma_Reference;
29474 ------------------------------
29475 -- Is_Pragma_String_Literal --
29476 ------------------------------
29478 -- This function returns true if the corresponding pragma argument is a
29479 -- static string expression. These are the only cases in which string
29480 -- literals can appear as pragma arguments. We also allow a string literal
29481 -- as the first argument to pragma Assert (although it will of course
29482 -- always generate a type error).
29484 function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
29485 Pragn : constant Node_Id := Parent (Par);
29486 Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
29487 Pname : constant Name_Id := Pragma_Name (Pragn);
29488 Argn : Natural;
29489 N : Node_Id;
29491 begin
29492 Argn := 1;
29493 N := First (Assoc);
29494 loop
29495 exit when N = Par;
29496 Argn := Argn + 1;
29497 Next (N);
29498 end loop;
29500 if Pname = Name_Assert then
29501 return True;
29503 elsif Pname = Name_Export then
29504 return Argn > 2;
29506 elsif Pname = Name_Ident then
29507 return Argn = 1;
29509 elsif Pname = Name_Import then
29510 return Argn > 2;
29512 elsif Pname = Name_Interface_Name then
29513 return Argn > 1;
29515 elsif Pname = Name_Linker_Alias then
29516 return Argn = 2;
29518 elsif Pname = Name_Linker_Section then
29519 return Argn = 2;
29521 elsif Pname = Name_Machine_Attribute then
29522 return Argn = 2;
29524 elsif Pname = Name_Source_File_Name then
29525 return True;
29527 elsif Pname = Name_Source_Reference then
29528 return Argn = 2;
29530 elsif Pname = Name_Title then
29531 return True;
29533 elsif Pname = Name_Subtitle then
29534 return True;
29536 else
29537 return False;
29538 end if;
29539 end Is_Pragma_String_Literal;
29541 ---------------------------
29542 -- Is_Private_SPARK_Mode --
29543 ---------------------------
29545 function Is_Private_SPARK_Mode (N : Node_Id) return Boolean is
29546 begin
29547 pragma Assert
29548 (Nkind (N) = N_Pragma
29549 and then Pragma_Name (N) = Name_SPARK_Mode
29550 and then Is_List_Member (N));
29552 -- For pragma SPARK_Mode to be private, it has to appear in the private
29553 -- declarations of a package.
29555 return
29556 Present (Parent (N))
29557 and then Nkind (Parent (N)) = N_Package_Specification
29558 and then List_Containing (N) = Private_Declarations (Parent (N));
29559 end Is_Private_SPARK_Mode;
29561 -------------------------------------
29562 -- Is_Unconstrained_Or_Tagged_Item --
29563 -------------------------------------
29565 function Is_Unconstrained_Or_Tagged_Item
29566 (Item : Entity_Id) return Boolean
29568 function Has_Unconstrained_Component (Typ : Entity_Id) return Boolean;
29569 -- Determine whether record type Typ has at least one unconstrained
29570 -- component.
29572 ---------------------------------
29573 -- Has_Unconstrained_Component --
29574 ---------------------------------
29576 function Has_Unconstrained_Component (Typ : Entity_Id) return Boolean is
29577 Comp : Entity_Id;
29579 begin
29580 Comp := First_Component (Typ);
29581 while Present (Comp) loop
29582 if Is_Unconstrained_Or_Tagged_Item (Comp) then
29583 return True;
29584 end if;
29586 Next_Component (Comp);
29587 end loop;
29589 return False;
29590 end Has_Unconstrained_Component;
29592 -- Local variables
29594 Typ : constant Entity_Id := Etype (Item);
29596 -- Start of processing for Is_Unconstrained_Or_Tagged_Item
29598 begin
29599 if Is_Tagged_Type (Typ) then
29600 return True;
29602 elsif Is_Array_Type (Typ) and then not Is_Constrained (Typ) then
29603 return True;
29605 elsif Is_Record_Type (Typ) then
29606 if Has_Discriminants (Typ) and then not Is_Constrained (Typ) then
29607 return True;
29608 else
29609 return Has_Unconstrained_Component (Typ);
29610 end if;
29612 elsif Is_Private_Type (Typ) and then Has_Discriminants (Typ) then
29613 return True;
29615 else
29616 return False;
29617 end if;
29618 end Is_Unconstrained_Or_Tagged_Item;
29620 -----------------------------
29621 -- Is_Valid_Assertion_Kind --
29622 -----------------------------
29624 function Is_Valid_Assertion_Kind (Nam : Name_Id) return Boolean is
29625 begin
29626 case Nam is
29627 when
29628 -- RM defined
29630 Name_Assert
29631 | Name_Assertion_Policy
29632 | Name_Static_Predicate
29633 | Name_Dynamic_Predicate
29634 | Name_Pre
29635 | Name_uPre
29636 | Name_Post
29637 | Name_uPost
29638 | Name_Type_Invariant
29639 | Name_uType_Invariant
29641 -- Impl defined
29643 | Name_Assert_And_Cut
29644 | Name_Assume
29645 | Name_Contract_Cases
29646 | Name_Debug
29647 | Name_Default_Initial_Condition
29648 | Name_Ghost
29649 | Name_Initial_Condition
29650 | Name_Invariant
29651 | Name_uInvariant
29652 | Name_Loop_Invariant
29653 | Name_Loop_Variant
29654 | Name_Postcondition
29655 | Name_Precondition
29656 | Name_Predicate
29657 | Name_Refined_Post
29658 | Name_Statement_Assertions
29660 return True;
29662 when others =>
29663 return False;
29664 end case;
29665 end Is_Valid_Assertion_Kind;
29667 --------------------------------------
29668 -- Process_Compilation_Unit_Pragmas --
29669 --------------------------------------
29671 procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
29672 begin
29673 -- A special check for pragma Suppress_All, a very strange DEC pragma,
29674 -- strange because it comes at the end of the unit. Rational has the
29675 -- same name for a pragma, but treats it as a program unit pragma, In
29676 -- GNAT we just decide to allow it anywhere at all. If it appeared then
29677 -- the flag Has_Pragma_Suppress_All was set on the compilation unit
29678 -- node, and we insert a pragma Suppress (All_Checks) at the start of
29679 -- the context clause to ensure the correct processing.
29681 if Has_Pragma_Suppress_All (N) then
29682 Prepend_To (Context_Items (N),
29683 Make_Pragma (Sloc (N),
29684 Chars => Name_Suppress,
29685 Pragma_Argument_Associations => New_List (
29686 Make_Pragma_Argument_Association (Sloc (N),
29687 Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
29688 end if;
29690 -- Nothing else to do at the current time
29692 end Process_Compilation_Unit_Pragmas;
29694 -------------------------------------------
29695 -- Process_Compile_Time_Warning_Or_Error --
29696 -------------------------------------------
29698 procedure Process_Compile_Time_Warning_Or_Error
29699 (N : Node_Id;
29700 Eloc : Source_Ptr)
29702 Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
29703 Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
29704 Arg2 : constant Node_Id := Next (Arg1);
29706 begin
29707 Analyze_And_Resolve (Arg1x, Standard_Boolean);
29709 if Compile_Time_Known_Value (Arg1x) then
29710 if Is_True (Expr_Value (Arg1x)) then
29711 declare
29712 Cent : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
29713 Pname : constant Name_Id := Pragma_Name_Unmapped (N);
29714 Prag_Id : constant Pragma_Id := Get_Pragma_Id (Pname);
29715 Str : constant String_Id := Strval (Get_Pragma_Arg (Arg2));
29716 Str_Len : constant Nat := String_Length (Str);
29718 Force : constant Boolean :=
29719 Prag_Id = Pragma_Compile_Time_Warning
29720 and then Is_Spec_Name (Unit_Name (Current_Sem_Unit))
29721 and then (Ekind (Cent) /= E_Package
29722 or else not In_Private_Part (Cent));
29723 -- Set True if this is the warning case, and we are in the
29724 -- visible part of a package spec, or in a subprogram spec,
29725 -- in which case we want to force the client to see the
29726 -- warning, even though it is not in the main unit.
29728 C : Character;
29729 CC : Char_Code;
29730 Cont : Boolean;
29731 Ptr : Nat;
29733 begin
29734 -- Loop through segments of message separated by line feeds.
29735 -- We output these segments as separate messages with
29736 -- continuation marks for all but the first.
29738 Cont := False;
29739 Ptr := 1;
29740 loop
29741 Error_Msg_Strlen := 0;
29743 -- Loop to copy characters from argument to error message
29744 -- string buffer.
29746 loop
29747 exit when Ptr > Str_Len;
29748 CC := Get_String_Char (Str, Ptr);
29749 Ptr := Ptr + 1;
29751 -- Ignore wide chars ??? else store character
29753 if In_Character_Range (CC) then
29754 C := Get_Character (CC);
29755 exit when C = ASCII.LF;
29756 Error_Msg_Strlen := Error_Msg_Strlen + 1;
29757 Error_Msg_String (Error_Msg_Strlen) := C;
29758 end if;
29759 end loop;
29761 -- Here with one line ready to go
29763 Error_Msg_Warn := Prag_Id = Pragma_Compile_Time_Warning;
29765 -- If this is a warning in a spec, then we want clients
29766 -- to see the warning, so mark the message with the
29767 -- special sequence !! to force the warning. In the case
29768 -- of a package spec, we do not force this if we are in
29769 -- the private part of the spec.
29771 if Force then
29772 if Cont = False then
29773 Error_Msg ("<<~!!", Eloc);
29774 Cont := True;
29775 else
29776 Error_Msg ("\<<~!!", Eloc);
29777 end if;
29779 -- Error, rather than warning, or in a body, so we do not
29780 -- need to force visibility for client (error will be
29781 -- output in any case, and this is the situation in which
29782 -- we do not want a client to get a warning, since the
29783 -- warning is in the body or the spec private part).
29785 else
29786 if Cont = False then
29787 Error_Msg ("<<~", Eloc);
29788 Cont := True;
29789 else
29790 Error_Msg ("\<<~", Eloc);
29791 end if;
29792 end if;
29794 exit when Ptr > Str_Len;
29795 end loop;
29796 end;
29797 end if;
29798 end if;
29799 end Process_Compile_Time_Warning_Or_Error;
29801 ------------------------------------
29802 -- Record_Possible_Body_Reference --
29803 ------------------------------------
29805 procedure Record_Possible_Body_Reference
29806 (State_Id : Entity_Id;
29807 Ref : Node_Id)
29809 Context : Node_Id;
29810 Spec_Id : Entity_Id;
29812 begin
29813 -- Ensure that we are dealing with a reference to a state
29815 pragma Assert (Ekind (State_Id) = E_Abstract_State);
29817 -- Climb the tree starting from the reference looking for a package body
29818 -- whose spec declares the referenced state. This criteria automatically
29819 -- excludes references in package specs which are legal. Note that it is
29820 -- not wise to emit an error now as the package body may lack pragma
29821 -- Refined_State or the referenced state may not be mentioned in the
29822 -- refinement. This approach avoids the generation of misleading errors.
29824 Context := Ref;
29825 while Present (Context) loop
29826 if Nkind (Context) = N_Package_Body then
29827 Spec_Id := Corresponding_Spec (Context);
29829 if Present (Abstract_States (Spec_Id))
29830 and then Contains (Abstract_States (Spec_Id), State_Id)
29831 then
29832 if No (Body_References (State_Id)) then
29833 Set_Body_References (State_Id, New_Elmt_List);
29834 end if;
29836 Append_Elmt (Ref, To => Body_References (State_Id));
29837 exit;
29838 end if;
29839 end if;
29841 Context := Parent (Context);
29842 end loop;
29843 end Record_Possible_Body_Reference;
29845 ------------------------------------------
29846 -- Relocate_Pragmas_To_Anonymous_Object --
29847 ------------------------------------------
29849 procedure Relocate_Pragmas_To_Anonymous_Object
29850 (Typ_Decl : Node_Id;
29851 Obj_Decl : Node_Id)
29853 Decl : Node_Id;
29854 Def : Node_Id;
29855 Next_Decl : Node_Id;
29857 begin
29858 if Nkind (Typ_Decl) = N_Protected_Type_Declaration then
29859 Def := Protected_Definition (Typ_Decl);
29860 else
29861 pragma Assert (Nkind (Typ_Decl) = N_Task_Type_Declaration);
29862 Def := Task_Definition (Typ_Decl);
29863 end if;
29865 -- The concurrent definition has a visible declaration list. Inspect it
29866 -- and relocate all canidate pragmas.
29868 if Present (Def) and then Present (Visible_Declarations (Def)) then
29869 Decl := First (Visible_Declarations (Def));
29870 while Present (Decl) loop
29872 -- Preserve the following declaration for iteration purposes due
29873 -- to possible relocation of a pragma.
29875 Next_Decl := Next (Decl);
29877 if Nkind (Decl) = N_Pragma
29878 and then Pragma_On_Anonymous_Object_OK (Get_Pragma_Id (Decl))
29879 then
29880 Remove (Decl);
29881 Insert_After (Obj_Decl, Decl);
29883 -- Skip internally generated code
29885 elsif not Comes_From_Source (Decl) then
29886 null;
29888 -- No candidate pragmas are available for relocation
29890 else
29891 exit;
29892 end if;
29894 Decl := Next_Decl;
29895 end loop;
29896 end if;
29897 end Relocate_Pragmas_To_Anonymous_Object;
29899 ------------------------------
29900 -- Relocate_Pragmas_To_Body --
29901 ------------------------------
29903 procedure Relocate_Pragmas_To_Body
29904 (Subp_Body : Node_Id;
29905 Target_Body : Node_Id := Empty)
29907 procedure Relocate_Pragma (Prag : Node_Id);
29908 -- Remove a single pragma from its current list and add it to the
29909 -- declarations of the proper body (either Subp_Body or Target_Body).
29911 ---------------------
29912 -- Relocate_Pragma --
29913 ---------------------
29915 procedure Relocate_Pragma (Prag : Node_Id) is
29916 Decls : List_Id;
29917 Target : Node_Id;
29919 begin
29920 -- When subprogram stubs or expression functions are involves, the
29921 -- destination declaration list belongs to the proper body.
29923 if Present (Target_Body) then
29924 Target := Target_Body;
29925 else
29926 Target := Subp_Body;
29927 end if;
29929 Decls := Declarations (Target);
29931 if No (Decls) then
29932 Decls := New_List;
29933 Set_Declarations (Target, Decls);
29934 end if;
29936 -- Unhook the pragma from its current list
29938 Remove (Prag);
29939 Prepend (Prag, Decls);
29940 end Relocate_Pragma;
29942 -- Local variables
29944 Body_Id : constant Entity_Id :=
29945 Defining_Unit_Name (Specification (Subp_Body));
29946 Next_Stmt : Node_Id;
29947 Stmt : Node_Id;
29949 -- Start of processing for Relocate_Pragmas_To_Body
29951 begin
29952 -- Do not process a body that comes from a separate unit as no construct
29953 -- can possibly follow it.
29955 if not Is_List_Member (Subp_Body) then
29956 return;
29958 -- Do not relocate pragmas that follow a stub if the stub does not have
29959 -- a proper body.
29961 elsif Nkind (Subp_Body) = N_Subprogram_Body_Stub
29962 and then No (Target_Body)
29963 then
29964 return;
29966 -- Do not process internally generated routine _Postconditions
29968 elsif Ekind (Body_Id) = E_Procedure
29969 and then Chars (Body_Id) = Name_uPostconditions
29970 then
29971 return;
29972 end if;
29974 -- Look at what is following the body. We are interested in certain kind
29975 -- of pragmas (either from source or byproducts of expansion) that can
29976 -- apply to a body [stub].
29978 Stmt := Next (Subp_Body);
29979 while Present (Stmt) loop
29981 -- Preserve the following statement for iteration purposes due to a
29982 -- possible relocation of a pragma.
29984 Next_Stmt := Next (Stmt);
29986 -- Move a candidate pragma following the body to the declarations of
29987 -- the body.
29989 if Nkind (Stmt) = N_Pragma
29990 and then Pragma_On_Body_Or_Stub_OK (Get_Pragma_Id (Stmt))
29991 then
29993 -- If a source pragma Warnings follows the body, it applies to
29994 -- following statements and does not belong in the body.
29996 if Get_Pragma_Id (Stmt) = Pragma_Warnings
29997 and then Comes_From_Source (Stmt)
29998 then
29999 null;
30000 else
30001 Relocate_Pragma (Stmt);
30002 end if;
30004 -- Skip internally generated code
30006 elsif not Comes_From_Source (Stmt) then
30007 null;
30009 -- No candidate pragmas are available for relocation
30011 else
30012 exit;
30013 end if;
30015 Stmt := Next_Stmt;
30016 end loop;
30017 end Relocate_Pragmas_To_Body;
30019 -------------------
30020 -- Resolve_State --
30021 -------------------
30023 procedure Resolve_State (N : Node_Id) is
30024 Func : Entity_Id;
30025 State : Entity_Id;
30027 begin
30028 if Is_Entity_Name (N) and then Present (Entity (N)) then
30029 Func := Entity (N);
30031 -- Handle overloading of state names by functions. Traverse the
30032 -- homonym chain looking for an abstract state.
30034 if Ekind (Func) = E_Function and then Has_Homonym (Func) then
30035 State := Homonym (Func);
30036 while Present (State) loop
30038 -- Resolve the overloading by setting the proper entity of the
30039 -- reference to that of the state.
30041 if Ekind (State) = E_Abstract_State then
30042 Set_Etype (N, Standard_Void_Type);
30043 Set_Entity (N, State);
30044 Set_Associated_Node (N, State);
30045 return;
30046 end if;
30048 State := Homonym (State);
30049 end loop;
30051 -- A function can never act as a state. If the homonym chain does
30052 -- not contain a corresponding state, then something went wrong in
30053 -- the overloading mechanism.
30055 raise Program_Error;
30056 end if;
30057 end if;
30058 end Resolve_State;
30060 ----------------------------
30061 -- Rewrite_Assertion_Kind --
30062 ----------------------------
30064 procedure Rewrite_Assertion_Kind
30065 (N : Node_Id;
30066 From_Policy : Boolean := False)
30068 Nam : Name_Id;
30070 begin
30071 Nam := No_Name;
30072 if Nkind (N) = N_Attribute_Reference
30073 and then Attribute_Name (N) = Name_Class
30074 and then Nkind (Prefix (N)) = N_Identifier
30075 then
30076 case Chars (Prefix (N)) is
30077 when Name_Pre =>
30078 Nam := Name_uPre;
30080 when Name_Post =>
30081 Nam := Name_uPost;
30083 when Name_Type_Invariant =>
30084 Nam := Name_uType_Invariant;
30086 when Name_Invariant =>
30087 Nam := Name_uInvariant;
30089 when others =>
30090 return;
30091 end case;
30093 -- Recommend standard use of aspect names Pre/Post
30095 elsif Nkind (N) = N_Identifier
30096 and then From_Policy
30097 and then Serious_Errors_Detected = 0
30098 and then not ASIS_Mode
30099 then
30100 if Chars (N) = Name_Precondition
30101 or else Chars (N) = Name_Postcondition
30102 then
30103 Error_Msg_N ("Check_Policy is a non-standard pragma??", N);
30104 Error_Msg_N
30105 ("\use Assertion_Policy and aspect names Pre/Post for "
30106 & "Ada2012 conformance?", N);
30107 end if;
30109 return;
30110 end if;
30112 if Nam /= No_Name then
30113 Rewrite (N, Make_Identifier (Sloc (N), Chars => Nam));
30114 end if;
30115 end Rewrite_Assertion_Kind;
30117 --------
30118 -- rv --
30119 --------
30121 procedure rv is
30122 begin
30123 Dummy := Dummy + 1;
30124 end rv;
30126 --------------------------------
30127 -- Set_Encoded_Interface_Name --
30128 --------------------------------
30130 procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
30131 Str : constant String_Id := Strval (S);
30132 Len : constant Nat := String_Length (Str);
30133 CC : Char_Code;
30134 C : Character;
30135 J : Pos;
30137 Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
30139 procedure Encode;
30140 -- Stores encoded value of character code CC. The encoding we use an
30141 -- underscore followed by four lower case hex digits.
30143 ------------
30144 -- Encode --
30145 ------------
30147 procedure Encode is
30148 begin
30149 Store_String_Char (Get_Char_Code ('_'));
30150 Store_String_Char
30151 (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
30152 Store_String_Char
30153 (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
30154 Store_String_Char
30155 (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
30156 Store_String_Char
30157 (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
30158 end Encode;
30160 -- Start of processing for Set_Encoded_Interface_Name
30162 begin
30163 -- If first character is asterisk, this is a link name, and we leave it
30164 -- completely unmodified. We also ignore null strings (the latter case
30165 -- happens only in error cases).
30167 if Len = 0
30168 or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
30169 then
30170 Set_Interface_Name (E, S);
30172 else
30173 J := 1;
30174 loop
30175 CC := Get_String_Char (Str, J);
30177 exit when not In_Character_Range (CC);
30179 C := Get_Character (CC);
30181 exit when C /= '_' and then C /= '$'
30182 and then C not in '0' .. '9'
30183 and then C not in 'a' .. 'z'
30184 and then C not in 'A' .. 'Z';
30186 if J = Len then
30187 Set_Interface_Name (E, S);
30188 return;
30190 else
30191 J := J + 1;
30192 end if;
30193 end loop;
30195 -- Here we need to encode. The encoding we use as follows:
30196 -- three underscores + four hex digits (lower case)
30198 Start_String;
30200 for J in 1 .. String_Length (Str) loop
30201 CC := Get_String_Char (Str, J);
30203 if not In_Character_Range (CC) then
30204 Encode;
30205 else
30206 C := Get_Character (CC);
30208 if C = '_' or else C = '$'
30209 or else C in '0' .. '9'
30210 or else C in 'a' .. 'z'
30211 or else C in 'A' .. 'Z'
30212 then
30213 Store_String_Char (CC);
30214 else
30215 Encode;
30216 end if;
30217 end if;
30218 end loop;
30220 Set_Interface_Name (E,
30221 Make_String_Literal (Sloc (S),
30222 Strval => End_String));
30223 end if;
30224 end Set_Encoded_Interface_Name;
30226 ------------------------
30227 -- Set_Elab_Unit_Name --
30228 ------------------------
30230 procedure Set_Elab_Unit_Name (N : Node_Id; With_Item : Node_Id) is
30231 Pref : Node_Id;
30232 Scop : Entity_Id;
30234 begin
30235 if Nkind (N) = N_Identifier
30236 and then Nkind (With_Item) = N_Identifier
30237 then
30238 Set_Entity (N, Entity (With_Item));
30240 elsif Nkind (N) = N_Selected_Component then
30241 Change_Selected_Component_To_Expanded_Name (N);
30242 Set_Entity (N, Entity (With_Item));
30243 Set_Entity (Selector_Name (N), Entity (N));
30245 Pref := Prefix (N);
30246 Scop := Scope (Entity (N));
30247 while Nkind (Pref) = N_Selected_Component loop
30248 Change_Selected_Component_To_Expanded_Name (Pref);
30249 Set_Entity (Selector_Name (Pref), Scop);
30250 Set_Entity (Pref, Scop);
30251 Pref := Prefix (Pref);
30252 Scop := Scope (Scop);
30253 end loop;
30255 Set_Entity (Pref, Scop);
30256 end if;
30258 Generate_Reference (Entity (With_Item), N, Set_Ref => False);
30259 end Set_Elab_Unit_Name;
30261 -------------------
30262 -- Test_Case_Arg --
30263 -------------------
30265 function Test_Case_Arg
30266 (Prag : Node_Id;
30267 Arg_Nam : Name_Id;
30268 From_Aspect : Boolean := False) return Node_Id
30270 Aspect : constant Node_Id := Corresponding_Aspect (Prag);
30271 Arg : Node_Id;
30272 Args : Node_Id;
30274 begin
30275 pragma Assert (Nam_In (Arg_Nam, Name_Ensures,
30276 Name_Mode,
30277 Name_Name,
30278 Name_Requires));
30280 -- The caller requests the aspect argument
30282 if From_Aspect then
30283 if Present (Aspect)
30284 and then Nkind (Expression (Aspect)) = N_Aggregate
30285 then
30286 Args := Expression (Aspect);
30288 -- "Name" and "Mode" may appear without an identifier as a
30289 -- positional association.
30291 if Present (Expressions (Args)) then
30292 Arg := First (Expressions (Args));
30294 if Present (Arg) and then Arg_Nam = Name_Name then
30295 return Arg;
30296 end if;
30298 -- Skip "Name"
30300 Arg := Next (Arg);
30302 if Present (Arg) and then Arg_Nam = Name_Mode then
30303 return Arg;
30304 end if;
30305 end if;
30307 -- Some or all arguments may appear as component associatons
30309 if Present (Component_Associations (Args)) then
30310 Arg := First (Component_Associations (Args));
30311 while Present (Arg) loop
30312 if Chars (First (Choices (Arg))) = Arg_Nam then
30313 return Arg;
30314 end if;
30316 Next (Arg);
30317 end loop;
30318 end if;
30319 end if;
30321 -- Otherwise retrieve the argument directly from the pragma
30323 else
30324 Arg := First (Pragma_Argument_Associations (Prag));
30326 if Present (Arg) and then Arg_Nam = Name_Name then
30327 return Arg;
30328 end if;
30330 -- Skip argument "Name"
30332 Arg := Next (Arg);
30334 if Present (Arg) and then Arg_Nam = Name_Mode then
30335 return Arg;
30336 end if;
30338 -- Skip argument "Mode"
30340 Arg := Next (Arg);
30342 -- Arguments "Requires" and "Ensures" are optional and may not be
30343 -- present at all.
30345 while Present (Arg) loop
30346 if Chars (Arg) = Arg_Nam then
30347 return Arg;
30348 end if;
30350 Next (Arg);
30351 end loop;
30352 end if;
30354 return Empty;
30355 end Test_Case_Arg;
30357 end Sem_Prag;