c++: diagnose this specifier in requires expr [PR116798]
[official-gcc.git] / gcc / ada / sem_prag.adb
blob2d31c71f366e3ff15e4c37d14f53d211820d59a4
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-2024, 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 Einfo.Entities; use Einfo.Entities;
41 with Einfo.Utils; use Einfo.Utils;
42 with Elists; use Elists;
43 with Errout; use Errout;
44 with Exp_Dist; use Exp_Dist;
45 with Exp_Util; use Exp_Util;
46 with Expander; use Expander;
47 with Freeze; use Freeze;
48 with Ghost; use Ghost;
49 with GNAT_CUDA; use GNAT_CUDA;
50 with Gnatvsn; use Gnatvsn;
51 with Lib; use Lib;
52 with Lib.Writ; use Lib.Writ;
53 with Lib.Xref; use Lib.Xref;
54 with Namet.Sp; use Namet.Sp;
55 with Nlists; use Nlists;
56 with Nmake; use Nmake;
57 with Output; use Output;
58 with Par_SCO; use Par_SCO;
59 with Restrict; use Restrict;
60 with Rident; use Rident;
61 with Rtsfind; use Rtsfind;
62 with Sem; use Sem;
63 with Sem_Aux; use Sem_Aux;
64 with Sem_Ch3; use Sem_Ch3;
65 with Sem_Ch6; use Sem_Ch6;
66 with Sem_Ch7; use Sem_Ch7;
67 with Sem_Ch8; use Sem_Ch8;
68 with Sem_Ch12; use Sem_Ch12;
69 with Sem_Ch13; use Sem_Ch13;
70 with Sem_Disp; use Sem_Disp;
71 with Sem_Dist; use Sem_Dist;
72 with Sem_Elab; use Sem_Elab;
73 with Sem_Elim; use Sem_Elim;
74 with Sem_Eval; use Sem_Eval;
75 with Sem_Intr; use Sem_Intr;
76 with Sem_Mech; use Sem_Mech;
77 with Sem_Res; use Sem_Res;
78 with Sem_Type; use Sem_Type;
79 with Sem_Util; use Sem_Util;
80 with Sem_Warn; use Sem_Warn;
81 with Stand; use Stand;
82 with Sinfo; use Sinfo;
83 with Sinfo.Nodes; use Sinfo.Nodes;
84 with Sinfo.Utils; use Sinfo.Utils;
85 with Sinfo.CN; use Sinfo.CN;
86 with Sinput; use Sinput;
87 with Stringt; use Stringt;
88 with Strub; use Strub;
89 with Stylesw; use Stylesw;
90 with Table;
91 with Targparm; use Targparm;
92 with Tbuild; use Tbuild;
93 with Ttypes;
94 with Uintp; use Uintp;
95 with Uname; use Uname;
96 with Urealp; use Urealp;
97 with Validsw; use Validsw;
98 with Warnsw; use Warnsw;
100 with System.Case_Util;
102 package body Sem_Prag is
104 ----------------------------------------------
105 -- Common Handling of Import-Export Pragmas --
106 ----------------------------------------------
108 -- In the following section, a number of Import_xxx and Export_xxx pragmas
109 -- are defined by GNAT. These are compatible with the DEC pragmas of the
110 -- same name, and all have the following common form and processing:
112 -- pragma Export_xxx
113 -- [Internal =>] LOCAL_NAME
114 -- [, [External =>] EXTERNAL_SYMBOL]
115 -- [, other optional parameters ]);
117 -- pragma Import_xxx
118 -- [Internal =>] LOCAL_NAME
119 -- [, [External =>] EXTERNAL_SYMBOL]
120 -- [, other optional parameters ]);
122 -- EXTERNAL_SYMBOL ::=
123 -- IDENTIFIER
124 -- | static_string_EXPRESSION
126 -- The internal LOCAL_NAME designates the entity that is imported or
127 -- exported, and must refer to an entity in the current declarative
128 -- part (as required by the rules for LOCAL_NAME).
130 -- The external linker name is designated by the External parameter if
131 -- given, or the Internal parameter if not (if there is no External
132 -- parameter, the External parameter is a copy of the Internal name).
134 -- If the External parameter is given as a string, then this string is
135 -- treated as an external name (exactly as though it had been given as an
136 -- External_Name parameter for a normal Import pragma).
138 -- If the External parameter is given as an identifier (or there is no
139 -- External parameter, so that the Internal identifier is used), then
140 -- the external name is the characters of the identifier, translated
141 -- to all lower case letters.
143 -- Note: the external name specified or implied by any of these special
144 -- Import_xxx or Export_xxx pragmas override an external or link name
145 -- specified in a previous Import or Export pragma.
147 -- Note: these and all other DEC-compatible GNAT pragmas allow full use of
148 -- named notation, following the standard rules for subprogram calls, i.e.
149 -- parameters can be given in any order if named notation is used, and
150 -- positional and named notation can be mixed, subject to the rule that all
151 -- positional parameters must appear first.
153 -- Note: All these pragmas are implemented exactly following the DEC design
154 -- and implementation and are intended to be fully compatible with the use
155 -- of these pragmas in the DEC Ada compiler.
157 --------------------------------------------
158 -- Checking for Duplicated External Names --
159 --------------------------------------------
161 -- It is suspicious if two separate Export pragmas use the same external
162 -- name. The following table is used to diagnose this situation so that
163 -- an appropriate warning can be issued.
165 -- The Node_Id stored is for the N_String_Literal node created to hold
166 -- the value of the external name. The Sloc of this node is used to
167 -- cross-reference the location of the duplication.
169 package Externals is new Table.Table (
170 Table_Component_Type => Node_Id,
171 Table_Index_Type => Int,
172 Table_Low_Bound => 0,
173 Table_Initial => 100,
174 Table_Increment => 100,
175 Table_Name => "Name_Externals");
177 -------------------------------------
178 -- Local Subprograms and Variables --
179 -------------------------------------
181 function Adjust_External_Name_Case (N : Node_Id) return Node_Id;
182 -- This routine is used for possible casing adjustment of an explicit
183 -- external name supplied as a string literal (the node N), according to
184 -- the casing requirement of Opt.External_Name_Casing. If this is set to
185 -- As_Is, then the string literal is returned unchanged, but if it is set
186 -- to Uppercase or Lowercase, then a new string literal with appropriate
187 -- casing is constructed.
189 procedure Analyze_If_Present_Internal
190 (N : Node_Id;
191 Id : Pragma_Id;
192 Included : Boolean);
193 -- Inspect the remainder of the list containing pragma N and look for a
194 -- pragma that matches Id. If found, analyze the pragma. If Included is
195 -- True, N is included in the search.
197 procedure Analyze_Part_Of
198 (Indic : Node_Id;
199 Item_Id : Entity_Id;
200 Encap : Node_Id;
201 Encap_Id : out Entity_Id;
202 Legal : out Boolean);
203 -- Subsidiary to Analyze_Part_Of_In_Decl_Part, Analyze_Part_Of_Option and
204 -- Analyze_Pragma. Perform full analysis of indicator Part_Of. Indic is the
205 -- Part_Of indicator. Item_Id is the entity of an abstract state, object or
206 -- package instantiation. Encap denotes the encapsulating state or single
207 -- concurrent type. Encap_Id is the entity of Encap. Flag Legal is set when
208 -- the indicator is legal.
210 function Appears_In (List : Elist_Id; Item_Id : Entity_Id) return Boolean;
211 -- Subsidiary to analysis of pragmas Depends, Global and Refined_Depends.
212 -- Query whether a particular item appears in a mixed list of nodes and
213 -- entities. It is assumed that all nodes in the list have entities.
215 procedure Check_Postcondition_Use_In_Inlined_Subprogram
216 (Prag : Node_Id;
217 Spec_Id : Entity_Id);
218 -- Subsidiary to the analysis of pragmas Contract_Cases, Postcondition,
219 -- Precondition, Refined_Post, Subprogram_Variant, and Test_Case. Emit a
220 -- warning when pragma Prag is associated with subprogram Spec_Id subject
221 -- to Inline_Always, assertions are enabled and inling is done in the
222 -- frontend.
224 procedure Check_State_And_Constituent_Use
225 (States : Elist_Id;
226 Constits : Elist_Id;
227 Context : Node_Id);
228 -- Subsidiary to the analysis of pragmas [Refined_]Depends, [Refined_]
229 -- Global and Initializes. Determine whether a state from list States and a
230 -- corresponding constituent from list Constits (if any) appear in the same
231 -- context denoted by Context. If this is the case, emit an error.
233 procedure Contract_Freeze_Error
234 (Contract_Id : Entity_Id;
235 Freeze_Id : Entity_Id);
236 -- Subsidiary to the analysis of pragmas Contract_Cases, Exceptional_Cases,
237 -- Part_Of, Post, Pre and Subprogram_Variant. Emit a freezing-related error
238 -- message where Freeze_Id is the entity of a body which caused contract
239 -- freezing and Contract_Id denotes the entity of the affected contstruct.
241 procedure Duplication_Error (Prag : Node_Id; Prev : Node_Id);
242 -- Subsidiary to all Find_Related_xxx routines. Emit an error on pragma
243 -- Prag that duplicates previous pragma Prev.
245 function Find_Encapsulating_State
246 (States : Elist_Id;
247 Constit_Id : Entity_Id) return Entity_Id;
248 -- Given the entity of a constituent Constit_Id, find the corresponding
249 -- encapsulating state which appears in States. The routine returns Empty
250 -- if no such state is found.
252 function Find_Related_Context
253 (Prag : Node_Id;
254 Do_Checks : Boolean := False) return Node_Id;
255 -- Subsidiary to the analysis of pragmas
256 -- Async_Readers
257 -- Async_Writers
258 -- Constant_After_Elaboration
259 -- Effective_Reads
260 -- Effective_Writers
261 -- No_Caching
262 -- Part_Of
263 -- Find the first source declaration or statement found while traversing
264 -- the previous node chain starting from pragma Prag. If flag Do_Checks is
265 -- set, the routine reports duplicate pragmas. The routine returns Empty
266 -- when reaching the start of the node chain.
268 function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id;
269 -- If Def_Id refers to a renamed subprogram, then the base subprogram (the
270 -- original one, following the renaming chain) is returned. Otherwise the
271 -- entity is returned unchanged. Should be in Einfo???
273 function Get_SPARK_Mode_Type (N : Name_Id) return SPARK_Mode_Type;
274 -- Subsidiary to the analysis of pragma SPARK_Mode as well as subprogram
275 -- Get_SPARK_Mode_From_Annotation. Convert a name into a corresponding
276 -- value of type SPARK_Mode_Type.
278 function Has_Extra_Parentheses (Clause : Node_Id) return Boolean;
279 -- Subsidiary to the analysis of pragmas Depends and Refined_Depends.
280 -- Determine whether dependency clause Clause is surrounded by extra
281 -- parentheses. If this is the case, issue an error message.
283 procedure Record_Possible_Body_Reference
284 (State_Id : Entity_Id;
285 Ref : Node_Id);
286 -- Subsidiary to the analysis of pragmas [Refined_]Depends and [Refined_]
287 -- Global. Given an abstract state denoted by State_Id and a reference Ref
288 -- to it, determine whether the reference appears in a package body that
289 -- will eventually refine the state. If this is the case, record the
290 -- reference for future checks (see Analyze_Refined_State_In_Decls).
292 procedure Resolve_State (N : Node_Id);
293 -- Handle the overloading of state names by functions. When N denotes a
294 -- function, this routine finds the corresponding state and sets the entity
295 -- of N to that of the state.
297 procedure Rewrite_Assertion_Kind
298 (N : Node_Id;
299 From_Policy : Boolean := False);
300 -- If N is Pre'Class, Post'Class, Invariant'Class, or Type_Invariant'Class,
301 -- then it is rewritten as an identifier with the corresponding special
302 -- name _Pre, _Post, _Invariant, or _Type_Invariant. Used by pragmas Check
303 -- and Check_Policy. If the names are Precondition or Postcondition, this
304 -- combination is deprecated in favor of Assertion_Policy and Ada2012
305 -- Aspect names. The parameter From_Policy indicates that the pragma
306 -- is the old non-standard Check_Policy and not a rewritten pragma.
308 procedure Set_Elab_Unit_Name (N : Node_Id; With_Item : Node_Id);
309 -- Place semantic information on the argument of an Elaborate/Elaborate_All
310 -- pragma. Entity name for unit and its parents is taken from item in
311 -- previous with_clause that mentions the unit.
313 procedure Validate_Compile_Time_Warning_Or_Error
314 (N : Node_Id;
315 Eloc : Source_Ptr);
316 -- Common processing for Compile_Time_Error and Compile_Time_Warning of
317 -- pragma N. Called when the pragma is processed as part of its regular
318 -- analysis but also called after calling the back end to validate these
319 -- pragmas for size and alignment appropriateness.
321 procedure Defer_Compile_Time_Warning_Error_To_BE (N : Node_Id);
322 -- N is a pragma Compile_Time_Error or Compile_Warning_Error whose boolean
323 -- expression is not known at compile time during the front end. This
324 -- procedure makes an entry in a table. The actual checking is performed by
325 -- Validate_Compile_Time_Warning_Errors, which is invoked after calling the
326 -- back end.
328 Dummy : Integer := 0;
329 pragma Volatile (Dummy);
330 -- Dummy volatile integer used in bodies of ip/rv to prevent optimization
332 procedure ip;
333 pragma No_Inline (ip);
334 -- A dummy procedure called when pragma Inspection_Point is analyzed. This
335 -- is just to help debugging the front end. If a pragma Inspection_Point
336 -- is added to a source program, then breaking on ip will get you to that
337 -- point in the program.
339 procedure rv;
340 pragma No_Inline (rv);
341 -- This is a dummy function called by the processing for pragma Reviewable.
342 -- It is there for assisting front end debugging. By placing a Reviewable
343 -- pragma in the source program, a breakpoint on rv catches this place in
344 -- the source, allowing convenient stepping to the point of interest.
346 ------------------------------------------------------
347 -- Table for Defer_Compile_Time_Warning_Error_To_BE --
348 ------------------------------------------------------
350 -- The following table collects pragmas Compile_Time_Error and Compile_
351 -- Time_Warning for validation. Entries are made by calls to subprogram
352 -- Defer_Compile_Time_Warning_Error_To_BE, and the call to the procedure
353 -- Validate_Compile_Time_Warning_Errors does the actual error checking
354 -- and posting of warning and error messages. The reason for this delayed
355 -- processing is to take advantage of back-annotations of attributes size
356 -- and alignment values performed by the back end.
358 -- Note: the reason we store a Source_Ptr value instead of a Node_Id is
359 -- that by the time Validate_Compile_Time_Warning_Errors is called, Sprint
360 -- will already have modified all Sloc values if the -gnatD option is set.
362 type CTWE_Entry is record
363 Eloc : Source_Ptr;
364 -- Source location used in warnings and error messages
366 Prag : Node_Id;
367 -- Pragma Compile_Time_Error or Compile_Time_Warning
369 Scope : Node_Id;
370 -- The scope which encloses the pragma
371 end record;
373 package Compile_Time_Warnings_Errors is new Table.Table (
374 Table_Component_Type => CTWE_Entry,
375 Table_Index_Type => Int,
376 Table_Low_Bound => 1,
377 Table_Initial => 50,
378 Table_Increment => 200,
379 Table_Name => "Compile_Time_Warnings_Errors");
381 -------------------------------
382 -- Adjust_External_Name_Case --
383 -------------------------------
385 function Adjust_External_Name_Case (N : Node_Id) return Node_Id is
386 CC : Char_Code;
388 begin
389 -- Adjust case of literal if required
391 if Opt.External_Name_Exp_Casing = As_Is then
392 return N;
394 else
395 -- Copy existing string
397 Start_String;
399 -- Set proper casing
401 for J in 1 .. String_Length (Strval (N)) loop
402 CC := Get_String_Char (Strval (N), J);
404 if Opt.External_Name_Exp_Casing = Uppercase
405 and then CC in Get_Char_Code ('a') .. Get_Char_Code ('z')
406 then
407 Store_String_Char (CC - 32);
409 elsif Opt.External_Name_Exp_Casing = Lowercase
410 and then CC in Get_Char_Code ('A') .. Get_Char_Code ('Z')
411 then
412 Store_String_Char (CC + 32);
414 else
415 Store_String_Char (CC);
416 end if;
417 end loop;
419 return
420 Make_String_Literal (Sloc (N),
421 Strval => End_String);
422 end if;
423 end Adjust_External_Name_Case;
425 --------------------------------------------
426 -- Analyze_Always_Terminates_In_Decl_Part --
427 --------------------------------------------
429 procedure Analyze_Always_Terminates_In_Decl_Part
430 (N : Node_Id;
431 Freeze_Id : Entity_Id := Empty)
433 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
434 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
435 Arg1 : constant Node_Id :=
436 First (Pragma_Argument_Associations (N));
438 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
439 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
440 -- Save the Ghost-related attributes to restore on exit
442 Errors : Nat;
443 Restore_Scope : Boolean := False;
445 begin
446 -- Do not analyze the pragma multiple times
448 if Is_Analyzed_Pragma (N) then
449 return;
450 end if;
452 if Present (Arg1) then
454 -- Set the Ghost mode in effect from the pragma. Due to the delayed
455 -- analysis of the pragma, the Ghost mode at point of declaration and
456 -- point of analysis may not necessarily be the same. Use the mode in
457 -- effect at the point of declaration.
459 Set_Ghost_Mode (N);
461 -- Ensure that the subprogram and its formals are visible when
462 -- analyzing the expression of the pragma.
464 if not In_Open_Scopes (Spec_Id) then
465 Restore_Scope := True;
467 if Is_Generic_Subprogram (Spec_Id) then
468 Push_Scope (Spec_Id);
469 Install_Generic_Formals (Spec_Id);
470 else
471 Push_Scope (Spec_Id);
472 Install_Formals (Spec_Id);
473 end if;
474 end if;
476 Errors := Serious_Errors_Detected;
477 Preanalyze_Assert_Expression (Expression (Arg1), Standard_Boolean);
479 -- Emit a clarification message when the expression contains at least
480 -- one undefined reference, possibly due to contract freezing.
482 if Errors /= Serious_Errors_Detected
483 and then Present (Freeze_Id)
484 and then Has_Undefined_Reference (Expression (Arg1))
485 then
486 Contract_Freeze_Error (Spec_Id, Freeze_Id);
487 end if;
489 if Restore_Scope then
490 End_Scope;
491 end if;
493 Restore_Ghost_Region (Saved_GM, Saved_IGR);
494 end if;
496 Set_Is_Analyzed_Pragma (N);
498 end Analyze_Always_Terminates_In_Decl_Part;
500 -----------------------------------------
501 -- Analyze_Contract_Cases_In_Decl_Part --
502 -----------------------------------------
504 -- WARNING: This routine manages Ghost regions. Return statements must be
505 -- replaced by gotos which jump to the end of the routine and restore the
506 -- Ghost mode.
508 procedure Analyze_Contract_Cases_In_Decl_Part
509 (N : Node_Id;
510 Freeze_Id : Entity_Id := Empty)
512 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
513 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
515 Others_Seen : Boolean := False;
516 -- This flag is set when an "others" choice is encountered. It is used
517 -- to detect multiple illegal occurrences of "others".
519 procedure Analyze_Contract_Case (CCase : Node_Id);
520 -- Verify the legality of a single contract case
522 ---------------------------
523 -- Analyze_Contract_Case --
524 ---------------------------
526 procedure Analyze_Contract_Case (CCase : Node_Id) is
527 Case_Guard : Node_Id;
528 Conseq : Node_Id;
529 Errors : Nat;
530 Extra_Guard : Node_Id;
532 begin
533 if Nkind (CCase) = N_Component_Association then
534 Case_Guard := First (Choices (CCase));
535 Conseq := Expression (CCase);
537 -- Each contract case must have exactly one case guard
539 Extra_Guard := Next (Case_Guard);
541 if Present (Extra_Guard) then
542 Error_Msg_N
543 ("contract case must have exactly one case guard",
544 Extra_Guard);
545 end if;
547 -- Check placement of OTHERS if available (SPARK RM 6.1.3(1))
549 if Nkind (Case_Guard) = N_Others_Choice then
550 if Others_Seen then
551 Error_Msg_N
552 ("only one OTHERS choice allowed in contract cases",
553 Case_Guard);
554 else
555 Others_Seen := True;
556 end if;
558 elsif Others_Seen then
559 Error_Msg_N
560 ("OTHERS must be the last choice in contract cases", N);
561 end if;
563 -- Preanalyze the case guard and consequence
565 if Nkind (Case_Guard) /= N_Others_Choice then
566 Errors := Serious_Errors_Detected;
567 Preanalyze_Assert_Expression (Case_Guard, Standard_Boolean);
569 -- Emit a clarification message when the case guard contains
570 -- at least one undefined reference, possibly due to contract
571 -- freezing.
573 if Errors /= Serious_Errors_Detected
574 and then Present (Freeze_Id)
575 and then Has_Undefined_Reference (Case_Guard)
576 then
577 Contract_Freeze_Error (Spec_Id, Freeze_Id);
578 end if;
579 end if;
581 Errors := Serious_Errors_Detected;
582 Preanalyze_Assert_Expression (Conseq, Standard_Boolean);
584 -- Emit a clarification message when the consequence contains
585 -- at least one undefined reference, possibly due to contract
586 -- freezing.
588 if Errors /= Serious_Errors_Detected
589 and then Present (Freeze_Id)
590 and then Has_Undefined_Reference (Conseq)
591 then
592 Contract_Freeze_Error (Spec_Id, Freeze_Id);
593 end if;
595 -- The contract case is malformed
597 else
598 Error_Msg_N ("wrong syntax in contract case", CCase);
599 end if;
600 end Analyze_Contract_Case;
602 -- Local variables
604 CCases : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
606 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
607 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
608 -- Save the Ghost-related attributes to restore on exit
610 CCase : Node_Id;
611 Restore_Scope : Boolean := False;
613 -- Start of processing for Analyze_Contract_Cases_In_Decl_Part
615 begin
616 -- Do not analyze the pragma multiple times
618 if Is_Analyzed_Pragma (N) then
619 return;
620 end if;
622 -- Set the Ghost mode in effect from the pragma. Due to the delayed
623 -- analysis of the pragma, the Ghost mode at point of declaration and
624 -- point of analysis may not necessarily be the same. Use the mode in
625 -- effect at the point of declaration.
627 Set_Ghost_Mode (N);
629 -- Single and multiple contract cases must appear in aggregate form. If
630 -- this is not the case, then either the parser or the analysis of the
631 -- pragma failed to produce an aggregate, e.g. when the contract is
632 -- "null" or a "(null record)".
634 pragma Assert
635 (if Nkind (CCases) = N_Aggregate
636 then Null_Record_Present (CCases)
637 xor (Present (Component_Associations (CCases))
639 Present (Expressions (CCases)))
640 else Nkind (CCases) = N_Null);
642 -- Only CASE_GUARD => CONSEQUENCE clauses are allowed
644 if Nkind (CCases) = N_Aggregate
645 and then Present (Component_Associations (CCases))
646 and then No (Expressions (CCases))
647 then
649 -- Check that the expression is a proper aggregate (no parentheses)
651 if Paren_Count (CCases) /= 0 then
652 Error_Msg_F -- CODEFIX
653 ("redundant parentheses", CCases);
654 end if;
656 -- Ensure that the formal parameters are visible when analyzing all
657 -- clauses. This falls out of the general rule of aspects pertaining
658 -- to subprogram declarations.
660 if not In_Open_Scopes (Spec_Id) then
661 Restore_Scope := True;
662 Push_Scope (Spec_Id);
664 if Is_Generic_Subprogram (Spec_Id) then
665 Install_Generic_Formals (Spec_Id);
666 else
667 Install_Formals (Spec_Id);
668 end if;
669 end if;
671 CCase := First (Component_Associations (CCases));
672 while Present (CCase) loop
673 Analyze_Contract_Case (CCase);
674 Next (CCase);
675 end loop;
677 if Restore_Scope then
678 End_Scope;
679 end if;
681 -- Currently it is not possible to inline pre/postconditions on a
682 -- subprogram subject to pragma Inline_Always.
684 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
686 -- Otherwise the pragma is illegal
688 else
689 Error_Msg_N ("wrong syntax for contract cases", N);
690 end if;
692 Set_Is_Analyzed_Pragma (N);
694 Restore_Ghost_Region (Saved_GM, Saved_IGR);
695 end Analyze_Contract_Cases_In_Decl_Part;
697 ----------------------------------
698 -- Analyze_Depends_In_Decl_Part --
699 ----------------------------------
701 procedure Analyze_Depends_In_Decl_Part (N : Node_Id) is
702 Loc : constant Source_Ptr := Sloc (N);
703 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
704 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
706 All_Inputs_Seen : Elist_Id := No_Elist;
707 -- A list containing the entities of all the inputs processed so far.
708 -- The list is populated with unique entities because the same input
709 -- may appear in multiple input lists.
711 All_Outputs_Seen : Elist_Id := No_Elist;
712 -- A list containing the entities of all the outputs processed so far.
713 -- The list is populated with unique entities because output items are
714 -- unique in a dependence relation.
716 Constits_Seen : Elist_Id := No_Elist;
717 -- A list containing the entities of all constituents processed so far.
718 -- It aids in detecting illegal usage of a state and a corresponding
719 -- constituent in pragma [Refinde_]Depends.
721 Global_Seen : Boolean := False;
722 -- A flag set when pragma Global has been processed
724 Null_Output_Seen : Boolean := False;
725 -- A flag used to track the legality of a null output
727 Result_Seen : Boolean := False;
728 -- A flag set when Spec_Id'Result is processed
730 States_Seen : Elist_Id := No_Elist;
731 -- A list containing the entities of all states processed so far. It
732 -- helps in detecting illegal usage of a state and a corresponding
733 -- constituent in pragma [Refined_]Depends.
735 Subp_Inputs : Elist_Id := No_Elist;
736 Subp_Outputs : Elist_Id := No_Elist;
737 -- Two lists containing the full set of inputs and output of the related
738 -- subprograms. Note that these lists contain both nodes and entities.
740 Task_Input_Seen : Boolean := False;
741 Task_Output_Seen : Boolean := False;
742 -- Flags used to track the implicit dependence of a task unit on itself
744 procedure Add_Item_To_Name_Buffer (Item_Id : Entity_Id);
745 -- Subsidiary routine to Check_Role and Check_Usage. Add the item kind
746 -- to the name buffer. The individual kinds are as follows:
747 -- E_Abstract_State - "state"
748 -- E_Constant - "constant"
749 -- E_Generic_In_Out_Parameter - "generic parameter"
750 -- E_Generic_In_Parameter - "generic parameter"
751 -- E_In_Parameter - "parameter"
752 -- E_In_Out_Parameter - "parameter"
753 -- E_Loop_Parameter - "loop parameter"
754 -- E_Out_Parameter - "parameter"
755 -- E_Protected_Type - "current instance of protected type"
756 -- E_Task_Type - "current instance of task type"
757 -- E_Variable - "global"
759 procedure Analyze_Dependency_Clause
760 (Clause : Node_Id;
761 Is_Last : Boolean);
762 -- Verify the legality of a single dependency clause. Flag Is_Last
763 -- denotes whether Clause is the last clause in the relation.
765 procedure Check_Function_Return;
766 -- Verify that Funtion'Result appears as one of the outputs
767 -- (SPARK RM 6.1.5(10)).
769 procedure Check_Role
770 (Item : Node_Id;
771 Item_Id : Entity_Id;
772 Is_Input : Boolean;
773 Self_Ref : Boolean);
774 -- Ensure that an item fulfills its designated input and/or output role
775 -- as specified by pragma Global (if any) or the enclosing context. If
776 -- this is not the case, emit an error. Item and Item_Id denote the
777 -- attributes of an item. Flag Is_Input should be set when item comes
778 -- from an input list. Flag Self_Ref should be set when the item is an
779 -- output and the dependency clause has operator "+".
781 procedure Check_Usage
782 (Subp_Items : Elist_Id;
783 Used_Items : Elist_Id;
784 Is_Input : Boolean);
785 -- Verify that all items from Subp_Items appear in Used_Items. Emit an
786 -- error if this is not the case.
788 procedure Normalize_Clause (Clause : Node_Id);
789 -- Remove a self-dependency "+" from the input list of a clause
791 -----------------------------
792 -- Add_Item_To_Name_Buffer --
793 -----------------------------
795 procedure Add_Item_To_Name_Buffer (Item_Id : Entity_Id) is
796 begin
797 if Ekind (Item_Id) = E_Abstract_State then
798 Add_Str_To_Name_Buffer ("state");
800 elsif Ekind (Item_Id) = E_Constant then
801 Add_Str_To_Name_Buffer ("constant");
803 elsif Is_Formal_Object (Item_Id) then
804 Add_Str_To_Name_Buffer ("generic parameter");
806 elsif Is_Formal (Item_Id) then
807 Add_Str_To_Name_Buffer ("parameter");
809 elsif Ekind (Item_Id) = E_Loop_Parameter then
810 Add_Str_To_Name_Buffer ("loop parameter");
812 elsif Ekind (Item_Id) = E_Protected_Type
813 or else Is_Single_Protected_Object (Item_Id)
814 then
815 Add_Str_To_Name_Buffer ("current instance of protected type");
817 elsif Ekind (Item_Id) = E_Task_Type
818 or else Is_Single_Task_Object (Item_Id)
819 then
820 Add_Str_To_Name_Buffer ("current instance of task type");
822 elsif Ekind (Item_Id) = E_Variable then
823 Add_Str_To_Name_Buffer ("global");
825 -- The routine should not be called with non-SPARK items
827 else
828 raise Program_Error;
829 end if;
830 end Add_Item_To_Name_Buffer;
832 -------------------------------
833 -- Analyze_Dependency_Clause --
834 -------------------------------
836 procedure Analyze_Dependency_Clause
837 (Clause : Node_Id;
838 Is_Last : Boolean)
840 procedure Analyze_Input_List (Inputs : Node_Id);
841 -- Verify the legality of a single input list
843 procedure Analyze_Input_Output
844 (Item : Node_Id;
845 Is_Input : Boolean;
846 Self_Ref : Boolean;
847 Top_Level : Boolean;
848 Seen : in out Elist_Id;
849 Null_Seen : in out Boolean;
850 Non_Null_Seen : in out Boolean);
851 -- Verify the legality of a single input or output item. Flag
852 -- Is_Input should be set whenever Item is an input, False when it
853 -- denotes an output. Flag Self_Ref should be set when the item is an
854 -- output and the dependency clause has a "+". Flag Top_Level should
855 -- be set whenever Item appears immediately within an input or output
856 -- list. Seen is a collection of all abstract states, objects and
857 -- formals processed so far. Flag Null_Seen denotes whether a null
858 -- input or output has been encountered. Flag Non_Null_Seen denotes
859 -- whether a non-null input or output has been encountered.
861 ------------------------
862 -- Analyze_Input_List --
863 ------------------------
865 procedure Analyze_Input_List (Inputs : Node_Id) is
866 Inputs_Seen : Elist_Id := No_Elist;
867 -- A list containing the entities of all inputs that appear in the
868 -- current input list.
870 Non_Null_Input_Seen : Boolean := False;
871 Null_Input_Seen : Boolean := False;
872 -- Flags used to check the legality of an input list
874 Input : Node_Id;
876 begin
877 -- Multiple inputs appear as an aggregate
879 if Nkind (Inputs) = N_Aggregate then
880 if Present (Component_Associations (Inputs)) then
881 SPARK_Msg_N
882 ("nested dependency relations not allowed", Inputs);
884 elsif Present (Expressions (Inputs)) then
885 Input := First (Expressions (Inputs));
886 while Present (Input) loop
887 Analyze_Input_Output
888 (Item => Input,
889 Is_Input => True,
890 Self_Ref => False,
891 Top_Level => False,
892 Seen => Inputs_Seen,
893 Null_Seen => Null_Input_Seen,
894 Non_Null_Seen => Non_Null_Input_Seen);
896 Next (Input);
897 end loop;
899 -- Syntax error, always report
901 else
902 Error_Msg_N ("malformed input dependency list", Inputs);
903 end if;
905 -- Process a solitary input
907 else
908 Analyze_Input_Output
909 (Item => Inputs,
910 Is_Input => True,
911 Self_Ref => False,
912 Top_Level => False,
913 Seen => Inputs_Seen,
914 Null_Seen => Null_Input_Seen,
915 Non_Null_Seen => Non_Null_Input_Seen);
916 end if;
918 -- Detect an illegal dependency clause of the form
920 -- (null =>[+] null)
922 if Null_Output_Seen and then Null_Input_Seen then
923 SPARK_Msg_N
924 ("null dependency clause cannot have a null input list",
925 Inputs);
926 end if;
927 end Analyze_Input_List;
929 --------------------------
930 -- Analyze_Input_Output --
931 --------------------------
933 procedure Analyze_Input_Output
934 (Item : Node_Id;
935 Is_Input : Boolean;
936 Self_Ref : Boolean;
937 Top_Level : Boolean;
938 Seen : in out Elist_Id;
939 Null_Seen : in out Boolean;
940 Non_Null_Seen : in out Boolean)
942 procedure Current_Task_Instance_Seen;
943 -- Set the appropriate global flag when the current instance of a
944 -- task unit is encountered.
946 --------------------------------
947 -- Current_Task_Instance_Seen --
948 --------------------------------
950 procedure Current_Task_Instance_Seen is
951 begin
952 if Is_Input then
953 Task_Input_Seen := True;
954 else
955 Task_Output_Seen := True;
956 end if;
957 end Current_Task_Instance_Seen;
959 -- Local variables
961 Is_Output : constant Boolean := not Is_Input;
962 Grouped : Node_Id;
963 Item_Id : Entity_Id;
965 -- Start of processing for Analyze_Input_Output
967 begin
968 -- Multiple input or output items appear as an aggregate
970 if Nkind (Item) = N_Aggregate then
971 if not Top_Level then
972 SPARK_Msg_N ("nested grouping of items not allowed", Item);
974 elsif Present (Component_Associations (Item)) then
975 SPARK_Msg_N
976 ("nested dependency relations not allowed", Item);
978 -- Recursively analyze the grouped items
980 elsif Present (Expressions (Item)) then
981 Grouped := First (Expressions (Item));
982 while Present (Grouped) loop
983 Analyze_Input_Output
984 (Item => Grouped,
985 Is_Input => Is_Input,
986 Self_Ref => Self_Ref,
987 Top_Level => False,
988 Seen => Seen,
989 Null_Seen => Null_Seen,
990 Non_Null_Seen => Non_Null_Seen);
992 Next (Grouped);
993 end loop;
995 -- Syntax error, always report
997 else
998 Error_Msg_N ("malformed dependency list", Item);
999 end if;
1001 -- Process attribute 'Result in the context of a dependency clause
1003 elsif Is_Attribute_Result (Item) then
1004 Non_Null_Seen := True;
1006 Analyze (Item);
1008 -- Attribute 'Result is allowed to appear on the output side of
1009 -- a dependency clause (SPARK RM 6.1.5(6)).
1011 if Is_Input then
1012 SPARK_Msg_N ("function result cannot act as input", Item);
1014 elsif Null_Seen then
1015 SPARK_Msg_N
1016 ("cannot mix null and non-null dependency items", Item);
1018 else
1019 Result_Seen := True;
1020 end if;
1022 -- Detect multiple uses of null in a single dependency list or
1023 -- throughout the whole relation. Verify the placement of a null
1024 -- output list relative to the other clauses (SPARK RM 6.1.5(12)).
1026 elsif Nkind (Item) = N_Null then
1027 if Null_Seen then
1028 SPARK_Msg_N
1029 ("multiple null dependency relations not allowed", Item);
1031 elsif Non_Null_Seen then
1032 SPARK_Msg_N
1033 ("cannot mix null and non-null dependency items", Item);
1035 else
1036 Null_Seen := True;
1038 if Is_Output then
1039 if not Is_Last then
1040 SPARK_Msg_N
1041 ("null output list must be the last clause in a "
1042 & "dependency relation", Item);
1044 -- Catch a useless dependence of the form:
1045 -- null =>+ ...
1047 elsif Self_Ref then
1048 SPARK_Msg_N
1049 ("useless dependence, null depends on itself", Item);
1050 end if;
1051 end if;
1052 end if;
1054 -- Default case
1056 else
1057 Non_Null_Seen := True;
1059 if Null_Seen then
1060 SPARK_Msg_N ("cannot mix null and non-null items", Item);
1061 end if;
1063 Analyze (Item);
1064 Resolve_State (Item);
1066 -- Find the entity of the item. If this is a renaming, climb
1067 -- the renaming chain to reach the root object. Renamings of
1068 -- non-entire objects do not yield an entity (Empty).
1070 Item_Id := Entity_Of (Item);
1072 if Present (Item_Id) then
1074 -- Constants
1076 if Ekind (Item_Id) in E_Constant | E_Loop_Parameter
1077 or else
1079 -- Current instances of concurrent types
1081 Ekind (Item_Id) in E_Protected_Type | E_Task_Type
1082 or else
1084 -- Formal parameters
1086 Ekind (Item_Id) in E_Generic_In_Out_Parameter
1087 | E_Generic_In_Parameter
1088 | E_In_Parameter
1089 | E_In_Out_Parameter
1090 | E_Out_Parameter
1091 or else
1093 -- States, variables
1095 Ekind (Item_Id) in E_Abstract_State | E_Variable
1096 then
1097 -- A [generic] function is not allowed to have Output
1098 -- items in its dependency relations. Note that "null"
1099 -- and attribute 'Result are still valid items.
1101 if Ekind (Spec_Id) in E_Function | E_Generic_Function
1102 and then not Is_Function_With_Side_Effects (Spec_Id)
1103 and then not Is_Input
1104 then
1105 Error_Msg_Code :=
1106 GEC_Output_In_Function_Global_Or_Depends;
1107 SPARK_Msg_N
1108 ("output item is not applicable to function '[[]']",
1109 Item);
1110 end if;
1112 -- The item denotes a concurrent type. Note that single
1113 -- protected/task types are not considered here because
1114 -- they behave as objects in the context of pragma
1115 -- [Refined_]Depends.
1117 if Ekind (Item_Id) in E_Protected_Type | E_Task_Type then
1119 -- This use is legal as long as the concurrent type is
1120 -- the current instance of an enclosing type.
1122 if Is_CCT_Instance (Item_Id, Spec_Id) then
1124 -- The dependence of a task unit on itself is
1125 -- implicit and may or may not be explicitly
1126 -- specified (SPARK RM 6.1.4).
1128 if Ekind (Item_Id) = E_Task_Type then
1129 Current_Task_Instance_Seen;
1130 end if;
1132 -- Otherwise this is not the current instance
1134 else
1135 SPARK_Msg_N
1136 ("invalid use of subtype mark in dependency "
1137 & "relation", Item);
1138 end if;
1140 -- The dependency of a task unit on itself is implicit
1141 -- and may or may not be explicitly specified
1142 -- (SPARK RM 6.1.4).
1144 elsif Is_Single_Task_Object (Item_Id)
1145 and then Is_CCT_Instance (Etype (Item_Id), Spec_Id)
1146 then
1147 Current_Task_Instance_Seen;
1148 end if;
1150 -- Ensure that the item fulfills its role as input and/or
1151 -- output as specified by pragma Global or the enclosing
1152 -- context.
1154 Check_Role (Item, Item_Id, Is_Input, Self_Ref);
1156 -- Detect multiple uses of the same state, variable or
1157 -- formal parameter. If this is not the case, add the
1158 -- item to the list of processed relations.
1160 if Contains (Seen, Item_Id) then
1161 SPARK_Msg_NE
1162 ("duplicate use of item &", Item, Item_Id);
1163 else
1164 Append_New_Elmt (Item_Id, Seen);
1165 end if;
1167 -- Detect illegal use of an input related to a null
1168 -- output. Such input items cannot appear in other
1169 -- input lists (SPARK RM 6.1.5(13)).
1171 if Is_Input
1172 and then Null_Output_Seen
1173 and then Contains (All_Inputs_Seen, Item_Id)
1174 then
1175 SPARK_Msg_N
1176 ("input of a null output list cannot appear in "
1177 & "multiple input lists", Item);
1178 end if;
1180 -- Add an input or a self-referential output to the list
1181 -- of all processed inputs.
1183 if Is_Input or else Self_Ref then
1184 Append_New_Elmt (Item_Id, All_Inputs_Seen);
1185 end if;
1187 -- State related checks (SPARK RM 6.1.5(3))
1189 if Ekind (Item_Id) = E_Abstract_State then
1191 -- Package and subprogram bodies are instantiated
1192 -- individually in a separate compiler pass. Due to
1193 -- this mode of instantiation, the refinement of a
1194 -- state may no longer be visible when a subprogram
1195 -- body contract is instantiated. Since the generic
1196 -- template is legal, do not perform this check in
1197 -- the instance to circumvent this oddity.
1199 if In_Instance then
1200 null;
1202 -- An abstract state with visible refinement cannot
1203 -- appear in pragma [Refined_]Depends as its place
1204 -- must be taken by some of its constituents
1205 -- (SPARK RM 6.1.4(7)).
1207 elsif Has_Visible_Refinement (Item_Id) then
1208 SPARK_Msg_NE
1209 ("cannot mention state & in dependence relation",
1210 Item, Item_Id);
1211 SPARK_Msg_N ("\use its constituents instead", Item);
1212 return;
1214 -- If the reference to the abstract state appears in
1215 -- an enclosing package body that will eventually
1216 -- refine the state, record the reference for future
1217 -- checks.
1219 else
1220 Record_Possible_Body_Reference
1221 (State_Id => Item_Id,
1222 Ref => Item);
1223 end if;
1225 elsif Ekind (Item_Id) in E_Constant | E_Variable
1226 and then Present (Ultimate_Overlaid_Entity (Item_Id))
1227 then
1228 SPARK_Msg_NE
1229 ("overlaying object & cannot appear in Depends",
1230 Item, Item_Id);
1231 SPARK_Msg_NE
1232 ("\use the overlaid object & instead",
1233 Item, Ultimate_Overlaid_Entity (Item_Id));
1234 return;
1235 end if;
1237 -- When the item renames an entire object, replace the
1238 -- item with a reference to the object.
1240 if Entity (Item) /= Item_Id then
1241 Rewrite (Item,
1242 New_Occurrence_Of (Item_Id, Sloc (Item)));
1243 Analyze (Item);
1244 end if;
1246 -- Add the entity of the current item to the list of
1247 -- processed items.
1249 if Ekind (Item_Id) = E_Abstract_State then
1250 Append_New_Elmt (Item_Id, States_Seen);
1252 -- The variable may eventually become a constituent of a
1253 -- single protected/task type. Record the reference now
1254 -- and verify its legality when analyzing the contract of
1255 -- the variable (SPARK RM 9.3).
1257 elsif Ekind (Item_Id) = E_Variable then
1258 Record_Possible_Part_Of_Reference
1259 (Var_Id => Item_Id,
1260 Ref => Item);
1261 end if;
1263 if Ekind (Item_Id) in E_Abstract_State
1264 | E_Constant
1265 | E_Variable
1266 and then Present (Encapsulating_State (Item_Id))
1267 then
1268 Append_New_Elmt (Item_Id, Constits_Seen);
1269 end if;
1271 -- All other input/output items are illegal
1272 -- (SPARK RM 6.1.5(1)).
1274 else
1275 SPARK_Msg_N
1276 ("item must denote parameter, variable, state or "
1277 & "current instance of concurrent type", Item);
1278 end if;
1280 -- All other input/output items are illegal
1281 -- (SPARK RM 6.1.5(1)). This is a syntax error, always report.
1283 else
1284 Error_Msg_N
1285 ("item must denote parameter, variable, state or current "
1286 & "instance of concurrent type", Item);
1287 end if;
1288 end if;
1289 end Analyze_Input_Output;
1291 -- Local variables
1293 Inputs : Node_Id;
1294 Output : Node_Id;
1295 Self_Ref : Boolean;
1297 Non_Null_Output_Seen : Boolean := False;
1298 -- Flag used to check the legality of an output list
1300 -- Start of processing for Analyze_Dependency_Clause
1302 begin
1303 Inputs := Expression (Clause);
1304 Self_Ref := False;
1306 -- An input list with a self-dependency appears as operator "+" where
1307 -- the actuals inputs are the right operand.
1309 if Nkind (Inputs) = N_Op_Plus then
1310 Inputs := Right_Opnd (Inputs);
1311 Self_Ref := True;
1312 end if;
1314 -- Process the output_list of a dependency_clause
1316 Output := First (Choices (Clause));
1317 while Present (Output) loop
1318 Analyze_Input_Output
1319 (Item => Output,
1320 Is_Input => False,
1321 Self_Ref => Self_Ref,
1322 Top_Level => True,
1323 Seen => All_Outputs_Seen,
1324 Null_Seen => Null_Output_Seen,
1325 Non_Null_Seen => Non_Null_Output_Seen);
1327 Next (Output);
1328 end loop;
1330 -- Process the input_list of a dependency_clause
1332 Analyze_Input_List (Inputs);
1333 end Analyze_Dependency_Clause;
1335 ---------------------------
1336 -- Check_Function_Return --
1337 ---------------------------
1339 procedure Check_Function_Return is
1340 begin
1341 if Ekind (Spec_Id) in E_Function | E_Generic_Function
1342 and then not Result_Seen
1343 then
1344 SPARK_Msg_NE
1345 ("result of & must appear in exactly one output list",
1346 N, Spec_Id);
1347 end if;
1348 end Check_Function_Return;
1350 ----------------
1351 -- Check_Role --
1352 ----------------
1354 procedure Check_Role
1355 (Item : Node_Id;
1356 Item_Id : Entity_Id;
1357 Is_Input : Boolean;
1358 Self_Ref : Boolean)
1360 procedure Find_Role
1361 (Item_Is_Input : out Boolean;
1362 Item_Is_Output : out Boolean);
1363 -- Find the input/output role of Item_Id. Flags Item_Is_Input and
1364 -- Item_Is_Output are set depending on the role.
1366 procedure Role_Error
1367 (Item_Is_Input : Boolean;
1368 Item_Is_Output : Boolean);
1369 -- Emit an error message concerning the incorrect use of Item in
1370 -- pragma [Refined_]Depends. Flags Item_Is_Input and Item_Is_Output
1371 -- denote whether the item is an input and/or an output.
1373 ---------------
1374 -- Find_Role --
1375 ---------------
1377 procedure Find_Role
1378 (Item_Is_Input : out Boolean;
1379 Item_Is_Output : out Boolean)
1381 -- A constant or an IN parameter of a protected entry, procedure,
1382 -- or function with side-effects, if it is of an
1383 -- access-to-variable type, should be handled like a variable, as
1384 -- the underlying memory pointed-to can be modified. Use
1385 -- Adjusted_Kind to do this adjustment.
1387 Adjusted_Kind : Entity_Kind := Ekind (Item_Id);
1389 begin
1390 if (Ekind (Item_Id) in E_Constant | E_Generic_In_Parameter
1391 or else
1392 (Ekind (Item_Id) = E_In_Parameter
1393 and then
1394 (Ekind (Scope (Item_Id)) not in E_Function
1395 | E_Generic_Function
1396 or else
1397 Is_Function_With_Side_Effects (Scope (Item_Id)))))
1398 and then Is_Access_Variable (Etype (Item_Id))
1399 and then (Ekind (Spec_Id) not in E_Function
1400 | E_Generic_Function
1401 or else Is_Function_With_Side_Effects (Spec_Id))
1402 then
1403 Adjusted_Kind := E_Variable;
1404 end if;
1406 case Adjusted_Kind is
1408 -- Abstract states
1410 when E_Abstract_State =>
1412 -- When pragma Global is present it determines the mode of
1413 -- the abstract state.
1415 if Global_Seen then
1416 Item_Is_Input := Appears_In (Subp_Inputs, Item_Id);
1417 Item_Is_Output := Appears_In (Subp_Outputs, Item_Id);
1419 -- Otherwise the state has a default IN OUT mode, because it
1420 -- behaves as a variable.
1422 else
1423 Item_Is_Input := True;
1424 Item_Is_Output := True;
1425 end if;
1427 -- Constants and IN parameters
1429 when E_Constant
1430 | E_Generic_In_Parameter
1431 | E_In_Parameter
1432 | E_Loop_Parameter
1434 -- When pragma Global is present it determines the mode
1435 -- of constant objects as inputs (and such objects cannot
1436 -- appear as outputs in the Global contract).
1438 if Global_Seen then
1439 Item_Is_Input := Appears_In (Subp_Inputs, Item_Id);
1440 else
1441 Item_Is_Input := True;
1442 end if;
1444 Item_Is_Output := False;
1446 -- Variables and IN OUT parameters, as well as constants and
1447 -- IN parameters of access type which are handled like
1448 -- variables.
1450 when E_Generic_In_Out_Parameter
1451 | E_In_Out_Parameter
1452 | E_Out_Parameter
1453 | E_Variable
1455 -- An OUT parameter of the related subprogram; it cannot
1456 -- appear in Global.
1458 if Adjusted_Kind = E_Out_Parameter
1459 and then Scope (Item_Id) = Spec_Id
1460 then
1462 -- The parameter has mode IN if its type is unconstrained
1463 -- or tagged because array bounds, discriminants or tags
1464 -- can be read.
1466 Item_Is_Input :=
1467 Is_Unconstrained_Or_Tagged_Item (Item_Id);
1469 Item_Is_Output := True;
1471 -- A parameter of an enclosing subprogram; it can appear
1472 -- in Global and behaves as a read-write variable.
1474 else
1475 -- When pragma Global is present it determines the mode
1476 -- of the object.
1478 if Global_Seen then
1480 -- A variable has mode IN when its type is
1481 -- unconstrained or tagged because array bounds,
1482 -- discriminants, or tags can be read.
1484 Item_Is_Input :=
1485 Appears_In (Subp_Inputs, Item_Id)
1486 or else Is_Unconstrained_Or_Tagged_Item (Item_Id);
1488 Item_Is_Output := Appears_In (Subp_Outputs, Item_Id);
1490 -- Otherwise the variable has a default IN OUT mode
1492 else
1493 Item_Is_Input := True;
1494 Item_Is_Output := True;
1495 end if;
1496 end if;
1498 -- Protected types
1500 when E_Protected_Type =>
1501 if Global_Seen then
1503 -- A variable has mode IN when its type is unconstrained
1504 -- or tagged because array bounds, discriminants or tags
1505 -- can be read.
1507 Item_Is_Input :=
1508 Appears_In (Subp_Inputs, Item_Id)
1509 or else Is_Unconstrained_Or_Tagged_Item (Item_Id);
1511 Item_Is_Output := Appears_In (Subp_Outputs, Item_Id);
1513 else
1514 -- A protected type acts as a formal parameter of mode IN
1515 -- when it applies to a protected function.
1517 if Ekind (Spec_Id) = E_Function then
1518 Item_Is_Input := True;
1519 Item_Is_Output := False;
1521 -- Otherwise the protected type acts as a formal of mode
1522 -- IN OUT.
1524 else
1525 Item_Is_Input := True;
1526 Item_Is_Output := True;
1527 end if;
1528 end if;
1530 -- Task types
1532 when E_Task_Type =>
1534 -- When pragma Global is present it determines the mode of
1535 -- the object.
1537 if Global_Seen then
1538 Item_Is_Input :=
1539 Appears_In (Subp_Inputs, Item_Id)
1540 or else Is_Unconstrained_Or_Tagged_Item (Item_Id);
1542 Item_Is_Output := Appears_In (Subp_Outputs, Item_Id);
1544 -- Otherwise task types act as IN OUT parameters
1546 else
1547 Item_Is_Input := True;
1548 Item_Is_Output := True;
1549 end if;
1551 when others =>
1552 raise Program_Error;
1553 end case;
1554 end Find_Role;
1556 ----------------
1557 -- Role_Error --
1558 ----------------
1560 procedure Role_Error
1561 (Item_Is_Input : Boolean;
1562 Item_Is_Output : Boolean)
1564 begin
1565 Name_Len := 0;
1567 -- When the item is not part of the input and the output set of
1568 -- the related subprogram, then it appears as extra in pragma
1569 -- [Refined_]Depends.
1571 if not Item_Is_Input and then not Item_Is_Output then
1572 Add_Item_To_Name_Buffer (Item_Id);
1573 Add_Str_To_Name_Buffer
1574 (" & cannot appear in dependence relation");
1576 SPARK_Msg_NE (To_String (Global_Name_Buffer), Item, Item_Id);
1578 Error_Msg_Name_1 := Chars (Spec_Id);
1579 SPARK_Msg_NE
1580 (Fix_Msg (Spec_Id, "\& is not part of the input or output "
1581 & "set of subprogram %"), Item, Item_Id);
1583 -- The mode of the item and its role in pragma [Refined_]Depends
1584 -- are in conflict. Construct a detailed message explaining the
1585 -- illegality (SPARK RM 6.1.5(5-6)).
1587 else
1588 if Item_Is_Input then
1589 Add_Str_To_Name_Buffer ("read-only");
1590 else
1591 Add_Str_To_Name_Buffer ("write-only");
1592 end if;
1594 Add_Char_To_Name_Buffer (' ');
1595 Add_Item_To_Name_Buffer (Item_Id);
1596 Add_Str_To_Name_Buffer (" & cannot appear as ");
1598 if Item_Is_Input then
1599 Add_Str_To_Name_Buffer ("output");
1600 else
1601 Add_Str_To_Name_Buffer ("input");
1602 end if;
1604 Add_Str_To_Name_Buffer (" in dependence relation");
1606 SPARK_Msg_NE (To_String (Global_Name_Buffer), Item, Item_Id);
1607 end if;
1608 end Role_Error;
1610 -- Local variables
1612 Item_Is_Input : Boolean;
1613 Item_Is_Output : Boolean;
1615 -- Start of processing for Check_Role
1617 begin
1618 Find_Role (Item_Is_Input, Item_Is_Output);
1620 -- Input item
1622 if Is_Input then
1623 if not Item_Is_Input then
1624 Role_Error (Item_Is_Input, Item_Is_Output);
1625 end if;
1627 -- Self-referential item
1629 elsif Self_Ref then
1630 if not Item_Is_Input or else not Item_Is_Output then
1631 Role_Error (Item_Is_Input, Item_Is_Output);
1632 end if;
1634 -- Output item
1636 elsif not Item_Is_Output then
1637 Role_Error (Item_Is_Input, Item_Is_Output);
1638 end if;
1639 end Check_Role;
1641 -----------------
1642 -- Check_Usage --
1643 -----------------
1645 procedure Check_Usage
1646 (Subp_Items : Elist_Id;
1647 Used_Items : Elist_Id;
1648 Is_Input : Boolean)
1650 procedure Usage_Error (Item_Id : Entity_Id);
1651 -- Emit an error concerning the illegal usage of an item
1653 -----------------
1654 -- Usage_Error --
1655 -----------------
1657 procedure Usage_Error (Item_Id : Entity_Id) is
1658 begin
1659 -- Input case
1661 if Is_Input then
1663 -- Unconstrained and tagged items are not part of the explicit
1664 -- input set of the related subprogram, they do not have to be
1665 -- present in a dependence relation and should not be flagged
1666 -- (SPARK RM 6.1.5(5)).
1668 if not Is_Unconstrained_Or_Tagged_Item (Item_Id) then
1669 Name_Len := 0;
1671 Add_Item_To_Name_Buffer (Item_Id);
1672 Add_Str_To_Name_Buffer
1673 (" & is missing from input dependence list");
1675 SPARK_Msg_NE (To_String (Global_Name_Buffer), N, Item_Id);
1676 SPARK_Msg_NE
1677 ("\add `null ='> &` dependency to ignore this input",
1678 N, Item_Id);
1679 end if;
1681 -- Output case (SPARK RM 6.1.5(10))
1683 else
1684 Name_Len := 0;
1686 Add_Item_To_Name_Buffer (Item_Id);
1687 Add_Str_To_Name_Buffer
1688 (" & is missing from output dependence list");
1690 SPARK_Msg_NE (To_String (Global_Name_Buffer), N, Item_Id);
1691 end if;
1692 end Usage_Error;
1694 -- Local variables
1696 Elmt : Elmt_Id;
1697 Item : Node_Id;
1698 Item_Id : Entity_Id;
1700 -- Start of processing for Check_Usage
1702 begin
1703 if No (Subp_Items) then
1704 return;
1705 end if;
1707 -- Each input or output of the subprogram must appear in a dependency
1708 -- relation.
1710 Elmt := First_Elmt (Subp_Items);
1711 while Present (Elmt) loop
1712 Item := Node (Elmt);
1714 if Nkind (Item) = N_Defining_Identifier then
1715 Item_Id := Item;
1716 else
1717 Item_Id := Entity_Of (Item);
1718 end if;
1720 -- The item does not appear in a dependency
1722 if Present (Item_Id)
1723 and then not Contains (Used_Items, Item_Id)
1724 then
1725 if Is_Formal (Item_Id) then
1726 Usage_Error (Item_Id);
1728 -- The current instance of a protected type behaves as a formal
1729 -- parameter (SPARK RM 6.1.4).
1731 elsif Ekind (Item_Id) = E_Protected_Type
1732 or else Is_Single_Protected_Object (Item_Id)
1733 then
1734 Usage_Error (Item_Id);
1736 -- The current instance of a task type behaves as a formal
1737 -- parameter (SPARK RM 6.1.4).
1739 elsif Ekind (Item_Id) = E_Task_Type
1740 or else Is_Single_Task_Object (Item_Id)
1741 then
1742 -- The dependence of a task unit on itself is implicit and
1743 -- may or may not be explicitly specified (SPARK RM 6.1.4).
1744 -- Emit an error if only one input/output is present.
1746 if Task_Input_Seen /= Task_Output_Seen then
1747 Usage_Error (Item_Id);
1748 end if;
1750 -- States and global objects are not used properly only when
1751 -- the subprogram is subject to pragma Global.
1753 elsif Global_Seen
1754 and then Ekind (Item_Id) in E_Abstract_State
1755 | E_Constant
1756 | E_Loop_Parameter
1757 | E_Protected_Type
1758 | E_Task_Type
1759 | E_Variable
1760 | Formal_Kind
1761 then
1762 Usage_Error (Item_Id);
1763 end if;
1764 end if;
1766 Next_Elmt (Elmt);
1767 end loop;
1768 end Check_Usage;
1770 ----------------------
1771 -- Normalize_Clause --
1772 ----------------------
1774 procedure Normalize_Clause (Clause : Node_Id) is
1775 procedure Create_Or_Modify_Clause
1776 (Output : Node_Id;
1777 Outputs : Node_Id;
1778 Inputs : Node_Id;
1779 After : Node_Id;
1780 In_Place : Boolean;
1781 Multiple : Boolean);
1782 -- Create a brand new clause to represent the self-reference or
1783 -- modify the input and/or output lists of an existing clause. Output
1784 -- denotes a self-referencial output. Outputs is the output list of a
1785 -- clause. Inputs is the input list of a clause. After denotes the
1786 -- clause after which the new clause is to be inserted. Flag In_Place
1787 -- should be set when normalizing the last output of an output list.
1788 -- Flag Multiple should be set when Output comes from a list with
1789 -- multiple items.
1791 -----------------------------
1792 -- Create_Or_Modify_Clause --
1793 -----------------------------
1795 procedure Create_Or_Modify_Clause
1796 (Output : Node_Id;
1797 Outputs : Node_Id;
1798 Inputs : Node_Id;
1799 After : Node_Id;
1800 In_Place : Boolean;
1801 Multiple : Boolean)
1803 procedure Propagate_Output
1804 (Output : Node_Id;
1805 Inputs : Node_Id);
1806 -- Handle the various cases of output propagation to the input
1807 -- list. Output denotes a self-referencial output item. Inputs
1808 -- is the input list of a clause.
1810 ----------------------
1811 -- Propagate_Output --
1812 ----------------------
1814 procedure Propagate_Output
1815 (Output : Node_Id;
1816 Inputs : Node_Id)
1818 function In_Input_List
1819 (Item : Entity_Id;
1820 Inputs : List_Id) return Boolean;
1821 -- Determine whether a particulat item appears in the input
1822 -- list of a clause.
1824 -------------------
1825 -- In_Input_List --
1826 -------------------
1828 function In_Input_List
1829 (Item : Entity_Id;
1830 Inputs : List_Id) return Boolean
1832 Elmt : Node_Id;
1834 begin
1835 Elmt := First (Inputs);
1836 while Present (Elmt) loop
1837 if Entity_Of (Elmt) = Item then
1838 return True;
1839 end if;
1841 Next (Elmt);
1842 end loop;
1844 return False;
1845 end In_Input_List;
1847 -- Local variables
1849 Output_Id : constant Entity_Id := Entity_Of (Output);
1850 Grouped : List_Id;
1852 -- Start of processing for Propagate_Output
1854 begin
1855 -- The clause is of the form:
1857 -- (Output =>+ null)
1859 -- Remove null input and replace it with a copy of the output:
1861 -- (Output => Output)
1863 if Nkind (Inputs) = N_Null then
1864 Rewrite (Inputs, New_Copy_Tree (Output));
1866 -- The clause is of the form:
1868 -- (Output =>+ (Input1, ..., InputN))
1870 -- Determine whether the output is not already mentioned in the
1871 -- input list and if not, add it to the list of inputs:
1873 -- (Output => (Output, Input1, ..., InputN))
1875 elsif Nkind (Inputs) = N_Aggregate then
1876 Grouped := Expressions (Inputs);
1878 if not In_Input_List
1879 (Item => Output_Id,
1880 Inputs => Grouped)
1881 then
1882 Prepend_To (Grouped, New_Copy_Tree (Output));
1883 end if;
1885 -- The clause is of the form:
1887 -- (Output =>+ Input)
1889 -- If the input does not mention the output, group the two
1890 -- together:
1892 -- (Output => (Output, Input))
1894 elsif Entity_Of (Inputs) /= Output_Id then
1895 Rewrite (Inputs,
1896 Make_Aggregate (Loc,
1897 Expressions => New_List (
1898 New_Copy_Tree (Output),
1899 New_Copy_Tree (Inputs))));
1900 end if;
1901 end Propagate_Output;
1903 -- Local variables
1905 Loc : constant Source_Ptr := Sloc (Clause);
1906 New_Clause : Node_Id;
1908 -- Start of processing for Create_Or_Modify_Clause
1910 begin
1911 -- A null output depending on itself does not require any
1912 -- normalization.
1914 if Nkind (Output) = N_Null then
1915 return;
1917 -- A function result cannot depend on itself because it cannot
1918 -- appear in the input list of a relation (SPARK RM 6.1.5(10)).
1920 elsif Is_Attribute_Result (Output) then
1921 SPARK_Msg_N ("function result cannot depend on itself", Output);
1922 return;
1923 end if;
1925 -- When performing the transformation in place, simply add the
1926 -- output to the list of inputs (if not already there). This
1927 -- case arises when dealing with the last output of an output
1928 -- list. Perform the normalization in place to avoid generating
1929 -- a malformed tree.
1931 if In_Place then
1932 Propagate_Output (Output, Inputs);
1934 -- A list with multiple outputs is slowly trimmed until only
1935 -- one element remains. When this happens, replace aggregate
1936 -- with the element itself.
1938 if Multiple then
1939 Remove (Output);
1940 Rewrite (Outputs, Output);
1941 end if;
1943 -- Default case
1945 else
1946 -- Unchain the output from its output list as it will appear in
1947 -- a new clause. Note that we cannot simply rewrite the output
1948 -- as null because this will violate the semantics of pragma
1949 -- Depends.
1951 Remove (Output);
1953 -- Generate a new clause of the form:
1954 -- (Output => Inputs)
1956 New_Clause :=
1957 Make_Component_Association (Loc,
1958 Choices => New_List (Output),
1959 Expression => New_Copy_Tree (Inputs));
1961 -- The new clause contains replicated content that has already
1962 -- been analyzed. There is not need to reanalyze or renormalize
1963 -- it again.
1965 Set_Analyzed (New_Clause);
1967 Propagate_Output
1968 (Output => First (Choices (New_Clause)),
1969 Inputs => Expression (New_Clause));
1971 Insert_After (After, New_Clause);
1972 end if;
1973 end Create_Or_Modify_Clause;
1975 -- Local variables
1977 Outputs : constant Node_Id := First (Choices (Clause));
1978 Inputs : Node_Id;
1979 Last_Output : Node_Id;
1980 Next_Output : Node_Id;
1981 Output : Node_Id;
1983 -- Start of processing for Normalize_Clause
1985 begin
1986 -- A self-dependency appears as operator "+". Remove the "+" from the
1987 -- tree by moving the real inputs to their proper place.
1989 if Nkind (Expression (Clause)) = N_Op_Plus then
1990 Rewrite (Expression (Clause), Right_Opnd (Expression (Clause)));
1991 Inputs := Expression (Clause);
1993 -- Multiple outputs appear as an aggregate
1995 if Nkind (Outputs) = N_Aggregate then
1996 Last_Output := Last (Expressions (Outputs));
1998 Output := First (Expressions (Outputs));
1999 while Present (Output) loop
2001 -- Normalization may remove an output from its list,
2002 -- preserve the subsequent output now.
2004 Next_Output := Next (Output);
2006 Create_Or_Modify_Clause
2007 (Output => Output,
2008 Outputs => Outputs,
2009 Inputs => Inputs,
2010 After => Clause,
2011 In_Place => Output = Last_Output,
2012 Multiple => True);
2014 Output := Next_Output;
2015 end loop;
2017 -- Solitary output
2019 else
2020 Create_Or_Modify_Clause
2021 (Output => Outputs,
2022 Outputs => Empty,
2023 Inputs => Inputs,
2024 After => Empty,
2025 In_Place => True,
2026 Multiple => False);
2027 end if;
2028 end if;
2029 end Normalize_Clause;
2031 -- Local variables
2033 Deps : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
2034 Subp_Id : constant Entity_Id := Defining_Entity (Subp_Decl);
2036 Clause : Node_Id;
2037 Errors : Nat;
2038 Last_Clause : Node_Id;
2039 Restore_Scope : Boolean := False;
2041 -- Start of processing for Analyze_Depends_In_Decl_Part
2043 begin
2044 -- Do not analyze the pragma multiple times
2046 if Is_Analyzed_Pragma (N) then
2047 return;
2048 end if;
2050 -- Empty dependency list
2052 if Nkind (Deps) = N_Null then
2054 -- Gather all states, objects and formal parameters that the
2055 -- subprogram may depend on. These items are obtained from the
2056 -- parameter profile or pragma [Refined_]Global (if available).
2058 Collect_Subprogram_Inputs_Outputs
2059 (Subp_Id => Subp_Id,
2060 Subp_Inputs => Subp_Inputs,
2061 Subp_Outputs => Subp_Outputs,
2062 Global_Seen => Global_Seen);
2064 -- Verify that every input or output of the subprogram appear in a
2065 -- dependency.
2067 Check_Usage (Subp_Inputs, All_Inputs_Seen, True);
2068 Check_Usage (Subp_Outputs, All_Outputs_Seen, False);
2069 Check_Function_Return;
2071 -- Dependency clauses appear as component associations of an aggregate
2073 elsif Nkind (Deps) = N_Aggregate then
2075 -- Do not attempt to perform analysis of a syntactically illegal
2076 -- clause as this will lead to misleading errors.
2078 if Has_Extra_Parentheses (Deps) then
2079 goto Leave;
2080 end if;
2082 if Present (Component_Associations (Deps)) then
2083 Last_Clause := Last (Component_Associations (Deps));
2085 -- Gather all states, objects and formal parameters that the
2086 -- subprogram may depend on. These items are obtained from the
2087 -- parameter profile or pragma [Refined_]Global (if available).
2089 Collect_Subprogram_Inputs_Outputs
2090 (Subp_Id => Subp_Id,
2091 Subp_Inputs => Subp_Inputs,
2092 Subp_Outputs => Subp_Outputs,
2093 Global_Seen => Global_Seen);
2095 -- When pragma [Refined_]Depends appears on a single concurrent
2096 -- type, it is relocated to the anonymous object.
2098 if Is_Single_Concurrent_Object (Spec_Id) then
2099 null;
2101 -- Ensure that the formal parameters are visible when analyzing
2102 -- all clauses. This falls out of the general rule of aspects
2103 -- pertaining to subprogram declarations.
2105 elsif not In_Open_Scopes (Spec_Id) then
2106 Restore_Scope := True;
2107 Push_Scope (Spec_Id);
2109 if Ekind (Spec_Id) = E_Task_Type then
2111 -- Task discriminants cannot appear in the [Refined_]Depends
2112 -- contract, but must be present for the analysis so that we
2113 -- can reject them with an informative error message.
2115 if Has_Discriminants (Spec_Id) then
2116 Install_Discriminants (Spec_Id);
2117 end if;
2119 elsif Is_Generic_Subprogram (Spec_Id) then
2120 Install_Generic_Formals (Spec_Id);
2122 else
2123 Install_Formals (Spec_Id);
2124 end if;
2125 end if;
2127 Clause := First (Component_Associations (Deps));
2128 while Present (Clause) loop
2129 Errors := Serious_Errors_Detected;
2131 -- The normalization mechanism may create extra clauses that
2132 -- contain replicated input and output names. There is no need
2133 -- to reanalyze them.
2135 if not Analyzed (Clause) then
2136 Set_Analyzed (Clause);
2138 Analyze_Dependency_Clause
2139 (Clause => Clause,
2140 Is_Last => Clause = Last_Clause);
2141 end if;
2143 -- Do not normalize a clause if errors were detected (count
2144 -- of Serious_Errors has increased) because the inputs and/or
2145 -- outputs may denote illegal items.
2147 if Serious_Errors_Detected = Errors then
2148 Normalize_Clause (Clause);
2149 end if;
2151 Next (Clause);
2152 end loop;
2154 if Restore_Scope then
2155 End_Scope;
2156 end if;
2158 -- Verify that every input or output of the subprogram appear in a
2159 -- dependency.
2161 Check_Usage (Subp_Inputs, All_Inputs_Seen, True);
2162 Check_Usage (Subp_Outputs, All_Outputs_Seen, False);
2163 Check_Function_Return;
2165 -- The dependency list is malformed. This is a syntax error, always
2166 -- report.
2168 else
2169 Error_Msg_N ("malformed dependency relation", Deps);
2170 goto Leave;
2171 end if;
2173 -- The top level dependency relation is malformed. This is a syntax
2174 -- error, always report.
2176 else
2177 Error_Msg_N ("malformed dependency relation", Deps);
2178 goto Leave;
2179 end if;
2181 -- Ensure that a state and a corresponding constituent do not appear
2182 -- together in pragma [Refined_]Depends.
2184 Check_State_And_Constituent_Use
2185 (States => States_Seen,
2186 Constits => Constits_Seen,
2187 Context => N);
2189 <<Leave>>
2190 Set_Is_Analyzed_Pragma (N);
2191 end Analyze_Depends_In_Decl_Part;
2193 --------------------------------------------
2194 -- Analyze_Exceptional_Cases_In_Decl_Part --
2195 --------------------------------------------
2197 -- WARNING: This routine manages Ghost regions. Return statements must be
2198 -- replaced by gotos which jump to the end of the routine and restore the
2199 -- Ghost mode.
2201 procedure Analyze_Exceptional_Cases_In_Decl_Part
2202 (N : Node_Id;
2203 Freeze_Id : Entity_Id := Empty)
2205 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
2206 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
2208 procedure Analyze_Exceptional_Contract (Exceptional_Contract : Node_Id);
2209 -- Verify the legality of a single exceptional contract
2211 procedure Check_Duplication (Id : Node_Id; Contracts : List_Id);
2212 -- Iterate through the identifiers in each contract to find duplicates
2214 ----------------------------------
2215 -- Analyze_Exceptional_Contract --
2216 ----------------------------------
2218 procedure Analyze_Exceptional_Contract (Exceptional_Contract : Node_Id)
2220 Exception_Choice : Node_Id;
2221 Consequence : Node_Id;
2222 Errors : Nat;
2224 begin
2225 if Nkind (Exceptional_Contract) /= N_Component_Association then
2226 Error_Msg_N
2227 ("wrong syntax in exceptional contract", Exceptional_Contract);
2228 return;
2229 end if;
2231 Exception_Choice := First (Choices (Exceptional_Contract));
2232 Consequence := Expression (Exceptional_Contract);
2234 while Present (Exception_Choice) loop
2235 if Nkind (Exception_Choice) = N_Others_Choice then
2236 if Present (Next (Exception_Choice))
2237 or else Present (Next (Exceptional_Contract))
2238 or else Present (Prev (Exception_Choice))
2239 then
2240 Error_Msg_N
2241 ("OTHERS must appear alone and last", Exception_Choice);
2242 end if;
2244 else
2245 Analyze (Exception_Choice);
2247 if Is_Entity_Name (Exception_Choice)
2248 and then Ekind (Entity (Exception_Choice)) = E_Exception
2249 then
2250 if Present (Renamed_Entity (Entity (Exception_Choice)))
2251 and then Entity (Exception_Choice) = Standard_Numeric_Error
2252 then
2253 Check_Restriction
2254 (No_Obsolescent_Features, Exception_Choice);
2256 if Warn_On_Obsolescent_Feature then
2257 Error_Msg_N
2258 ("Numeric_Error is an obsolescent feature " &
2259 "(RM J.6(1))?j?",
2260 Exception_Choice);
2261 Error_Msg_N
2262 ("\use Constraint_Error instead?j?",
2263 Exception_Choice);
2264 end if;
2265 end if;
2267 Check_Duplication
2268 (Exception_Choice, List_Containing (Exceptional_Contract));
2270 -- Check for exception declared within generic formal
2271 -- package (which is illegal, see RM 11.2(8)).
2273 declare
2274 Ent : Entity_Id := Entity (Exception_Choice);
2275 Scop : Entity_Id;
2277 begin
2278 if Present (Renamed_Entity (Ent)) then
2279 Ent := Renamed_Entity (Ent);
2280 end if;
2282 Scop := Scope (Ent);
2283 while Scop /= Standard_Standard
2284 and then Ekind (Scop) = E_Package
2285 loop
2286 if Nkind (Declaration_Node (Scop)) =
2287 N_Package_Specification
2288 and then
2289 Nkind (Original_Node (Parent
2290 (Declaration_Node (Scop)))) =
2291 N_Formal_Package_Declaration
2292 then
2293 Error_Msg_NE
2294 ("exception& is declared in generic formal "
2295 & "package", Exception_Choice, Ent);
2296 Error_Msg_N
2297 ("\and therefore cannot appear in contract "
2298 & "(RM 11.2(8))", Exception_Choice);
2299 exit;
2301 -- If the exception is declared in an inner instance,
2302 -- nothing else to check.
2304 elsif Is_Generic_Instance (Scop) then
2305 exit;
2306 end if;
2308 Scop := Scope (Scop);
2309 end loop;
2310 end;
2311 else
2312 Error_Msg_N ("exception name expected", Exception_Choice);
2313 end if;
2314 end if;
2316 Next (Exception_Choice);
2317 end loop;
2319 -- Now analyze the expressions of this contract
2321 Errors := Serious_Errors_Detected;
2323 -- Preanalyze_Assert_Expression, but without enforcing any of the two
2324 -- acceptable types.
2326 Preanalyze_Assert_Expression (Consequence, Any_Boolean);
2328 -- Emit a clarification message when the consequence contains at
2329 -- least one undefined reference, possibly due to contract freezing.
2331 if Errors /= Serious_Errors_Detected
2332 and then Present (Freeze_Id)
2333 and then Has_Undefined_Reference (Consequence)
2334 then
2335 Contract_Freeze_Error (Spec_Id, Freeze_Id);
2336 end if;
2337 end Analyze_Exceptional_Contract;
2339 -----------------------
2340 -- Check_Duplication --
2341 -----------------------
2343 procedure Check_Duplication (Id : Node_Id; Contracts : List_Id) is
2344 Contract : Node_Id;
2345 Id1 : Node_Id;
2346 Id_Entity : Entity_Id := Entity (Id);
2348 begin
2349 if Present (Renamed_Entity (Id_Entity)) then
2350 Id_Entity := Renamed_Entity (Id_Entity);
2351 end if;
2353 Contract := First (Contracts);
2354 while Present (Contract) loop
2355 Id1 := First (Choices (Contract));
2356 while Present (Id1) loop
2358 -- Only check against the exception choices which precede
2359 -- Id in the contract, since the ones that follow Id have not
2360 -- been analyzed yet and will be checked in a subsequent call.
2362 if Id = Id1 then
2363 return;
2365 -- Duplication both simple and via a renaming across different
2366 -- exceptional contracts is illegal.
2368 elsif Nkind (Id1) /= N_Others_Choice
2369 and then
2370 (Id_Entity = Entity (Id1)
2371 or else Id_Entity = Renamed_Entity (Entity (Id1)))
2372 and then Contract /= Parent (Id)
2373 then
2374 Error_Msg_Sloc := Sloc (Id1);
2375 Error_Msg_NE ("exception choice duplicates &#", Id, Id1);
2376 end if;
2378 Next (Id1);
2379 end loop;
2381 Next (Contract);
2382 end loop;
2383 end Check_Duplication;
2385 -- Local variables
2387 Exceptional_Contracts : constant Node_Id :=
2388 Expression (Get_Argument (N, Spec_Id));
2390 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
2391 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
2392 -- Save the Ghost-related attributes to restore on exit
2394 Exceptional_Contract : Node_Id;
2395 Restore_Scope : Boolean := False;
2397 -- Start of processing for Analyze_Subprogram_Variant_In_Decl_Part
2399 begin
2400 -- Do not analyze the pragma multiple times
2402 if Is_Analyzed_Pragma (N) then
2403 return;
2404 end if;
2406 -- Set the Ghost mode in effect from the pragma. Due to the delayed
2407 -- analysis of the pragma, the Ghost mode at point of declaration and
2408 -- point of analysis may not necessarily be the same. Use the mode in
2409 -- effect at the point of declaration.
2411 Set_Ghost_Mode (N);
2413 -- Single and multiple contracts must appear in aggregate form. If this
2414 -- is not the case, then either the parser of the analysis of the pragma
2415 -- failed to produce an aggregate, e.g. when the contract is "null" or a
2416 -- "(null record)".
2418 pragma Assert
2419 (if Nkind (Exceptional_Contracts) = N_Aggregate
2420 then Null_Record_Present (Exceptional_Contracts)
2421 xor (Present (Component_Associations (Exceptional_Contracts))
2423 Present (Expressions (Exceptional_Contracts)))
2424 else Nkind (Exceptional_Contracts) = N_Null);
2426 -- Only clauses of the following form are allowed:
2428 -- exceptional_contract ::=
2429 -- [choice_parameter_specification:]
2430 -- exception_choice {'|' exception_choice} => consequence
2432 -- where
2434 -- consequence ::= Boolean_expression
2436 if Nkind (Exceptional_Contracts) = N_Aggregate
2437 and then Present (Component_Associations (Exceptional_Contracts))
2438 and then No (Expressions (Exceptional_Contracts))
2439 then
2441 -- Check that the expression is a proper aggregate (no parentheses)
2443 if Paren_Count (Exceptional_Contracts) /= 0 then
2444 Error_Msg_F -- CODEFIX
2445 ("redundant parentheses", Exceptional_Contracts);
2446 end if;
2448 -- Ensure that the formal parameters are visible when analyzing all
2449 -- clauses. This falls out of the general rule of aspects pertaining
2450 -- to subprogram declarations.
2452 if not In_Open_Scopes (Spec_Id) then
2453 Restore_Scope := True;
2454 Push_Scope (Spec_Id);
2456 if Is_Generic_Subprogram (Spec_Id) then
2457 Install_Generic_Formals (Spec_Id);
2458 else
2459 Install_Formals (Spec_Id);
2460 end if;
2461 end if;
2463 Exceptional_Contract :=
2464 First (Component_Associations (Exceptional_Contracts));
2465 while Present (Exceptional_Contract) loop
2466 Analyze_Exceptional_Contract (Exceptional_Contract);
2467 Next (Exceptional_Contract);
2468 end loop;
2470 if Restore_Scope then
2471 End_Scope;
2472 end if;
2474 -- Otherwise the pragma is illegal
2476 else
2477 Error_Msg_N ("wrong syntax for exceptional cases", N);
2478 end if;
2480 Set_Is_Analyzed_Pragma (N);
2482 Restore_Ghost_Region (Saved_GM, Saved_IGR);
2483 end Analyze_Exceptional_Cases_In_Decl_Part;
2485 --------------------------------------------
2486 -- Analyze_External_Property_In_Decl_Part --
2487 --------------------------------------------
2489 procedure Analyze_External_Property_In_Decl_Part
2490 (N : Node_Id;
2491 Expr_Val : out Boolean)
2493 Prag_Id : constant Pragma_Id := Get_Pragma_Id (Pragma_Name (N));
2494 Arg1 : constant Node_Id :=
2495 First (Pragma_Argument_Associations (N));
2496 Obj_Decl : constant Node_Id := Find_Related_Context (N);
2497 Obj_Id : constant Entity_Id := Defining_Entity (Obj_Decl);
2498 Obj_Typ : Entity_Id;
2499 Expr : Node_Id;
2501 begin
2502 if Is_Type (Obj_Id) then
2503 Obj_Typ := Obj_Id;
2504 else
2505 Obj_Typ := Etype (Obj_Id);
2506 end if;
2508 -- Ensure that the Boolean expression (if present) is static. A missing
2509 -- argument defaults the value to True (SPARK RM 7.1.2(5)).
2511 Expr_Val := True;
2513 if Present (Arg1) then
2514 Expr := Get_Pragma_Arg (Arg1);
2516 if Is_OK_Static_Expression (Expr) then
2517 Expr_Val := Is_True (Expr_Value (Expr));
2518 end if;
2519 end if;
2521 -- The output parameter was set to the argument specified by the pragma.
2522 -- Do not analyze the pragma multiple times.
2524 if Is_Analyzed_Pragma (N) then
2525 return;
2526 end if;
2528 Error_Msg_Name_1 := Pragma_Name (N);
2530 -- An external property pragma must apply to an effectively volatile
2531 -- object other than a formal subprogram parameter (SPARK RM 7.1.3(2)).
2532 -- The check is performed at the end of the declarative region due to a
2533 -- possible out-of-order arrangement of pragmas:
2535 -- Obj : ...;
2536 -- pragma Async_Readers (Obj);
2537 -- pragma Volatile (Obj);
2539 if Prag_Id /= Pragma_No_Caching
2540 and then not Is_Effectively_Volatile (Obj_Id)
2541 then
2542 if No_Caching_Enabled (Obj_Id) then
2543 if Expr_Val then -- Confirming value of False is allowed
2544 SPARK_Msg_N
2545 ("illegal combination of external property % and property "
2546 & """No_Caching"" (SPARK RM 7.1.2(6))", N);
2547 end if;
2548 else
2549 SPARK_Msg_N
2550 ("external property % must apply to a volatile type or object",
2552 end if;
2554 -- Pragma No_Caching should only apply to volatile types or variables of
2555 -- a non-effectively volatile type (SPARK RM 7.1.2).
2557 elsif Prag_Id = Pragma_No_Caching then
2558 if Is_Effectively_Volatile (Obj_Typ) then
2559 SPARK_Msg_N ("property % must not apply to a type or object of "
2560 & "an effectively volatile type", N);
2561 elsif not Is_Volatile (Obj_Id) then
2562 SPARK_Msg_N
2563 ("property % must apply to a volatile type or object", N);
2564 end if;
2565 end if;
2567 Set_Is_Analyzed_Pragma (N);
2568 end Analyze_External_Property_In_Decl_Part;
2570 ---------------------------------
2571 -- Analyze_Global_In_Decl_Part --
2572 ---------------------------------
2574 procedure Analyze_Global_In_Decl_Part (N : Node_Id) is
2575 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
2576 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
2577 Subp_Id : constant Entity_Id := Defining_Entity (Subp_Decl);
2579 Constits_Seen : Elist_Id := No_Elist;
2580 -- A list containing the entities of all constituents processed so far.
2581 -- It aids in detecting illegal usage of a state and a corresponding
2582 -- constituent in pragma [Refinde_]Global.
2584 Seen : Elist_Id := No_Elist;
2585 -- A list containing the entities of all the items processed so far. It
2586 -- plays a role in detecting distinct entities.
2588 States_Seen : Elist_Id := No_Elist;
2589 -- A list containing the entities of all states processed so far. It
2590 -- helps in detecting illegal usage of a state and a corresponding
2591 -- constituent in pragma [Refined_]Global.
2593 In_Out_Seen : Boolean := False;
2594 Input_Seen : Boolean := False;
2595 Output_Seen : Boolean := False;
2596 Proof_Seen : Boolean := False;
2597 -- Flags used to verify the consistency of modes
2599 procedure Analyze_Global_List
2600 (List : Node_Id;
2601 Global_Mode : Name_Id := Name_Input);
2602 -- Verify the legality of a single global list declaration. Global_Mode
2603 -- denotes the current mode in effect.
2605 -------------------------
2606 -- Analyze_Global_List --
2607 -------------------------
2609 procedure Analyze_Global_List
2610 (List : Node_Id;
2611 Global_Mode : Name_Id := Name_Input)
2613 procedure Analyze_Global_Item
2614 (Item : Node_Id;
2615 Global_Mode : Name_Id);
2616 -- Verify the legality of a single global item declaration denoted by
2617 -- Item. Global_Mode denotes the current mode in effect.
2619 procedure Check_Duplicate_Mode
2620 (Mode : Node_Id;
2621 Status : in out Boolean);
2622 -- Flag Status denotes whether a particular mode has been seen while
2623 -- processing a global list. This routine verifies that Mode is not a
2624 -- duplicate mode and sets the flag Status (SPARK RM 6.1.4(9)).
2626 procedure Check_Mode_Restriction_In_Enclosing_Context
2627 (Item : Node_Id;
2628 Item_Id : Entity_Id);
2629 -- Verify that an item of mode In_Out or Output does not appear as
2630 -- an input in the Global aspect of an enclosing subprogram or task
2631 -- unit. If this is the case, emit an error. Item and Item_Id are
2632 -- respectively the item and its entity.
2634 procedure Check_Mode_Restriction_In_Function (Mode : Node_Id);
2635 -- Mode denotes either In_Out or Output. Depending on the kind of the
2636 -- related subprogram, emit an error if those two modes apply to a
2637 -- function (SPARK RM 6.1.4(10)).
2639 -------------------------
2640 -- Analyze_Global_Item --
2641 -------------------------
2643 procedure Analyze_Global_Item
2644 (Item : Node_Id;
2645 Global_Mode : Name_Id)
2647 Item_Id : Entity_Id;
2649 begin
2650 -- Detect one of the following cases
2652 -- with Global => (null, Name)
2653 -- with Global => (Name_1, null, Name_2)
2654 -- with Global => (Name, null)
2656 if Nkind (Item) = N_Null then
2657 SPARK_Msg_N ("cannot mix null and non-null global items", Item);
2658 return;
2659 end if;
2661 Analyze (Item);
2662 Resolve_State (Item);
2664 -- Find the entity of the item. If this is a renaming, climb the
2665 -- renaming chain to reach the root object. Renamings of non-
2666 -- entire objects do not yield an entity (Empty).
2668 Item_Id := Entity_Of (Item);
2670 if Present (Item_Id) then
2672 -- A global item may denote a formal parameter of an enclosing
2673 -- subprogram (SPARK RM 6.1.4(6)). Do this check first to
2674 -- provide a better error diagnostic.
2676 if Is_Formal (Item_Id) then
2677 if Scope (Item_Id) = Spec_Id then
2678 SPARK_Msg_NE
2679 (Fix_Msg (Spec_Id, "global item cannot reference "
2680 & "parameter of subprogram &"), Item, Spec_Id);
2681 return;
2682 end if;
2684 -- A global item may denote a concurrent type as long as it is
2685 -- the current instance of an enclosing protected or task type
2686 -- (SPARK RM 6.1.4).
2688 elsif Ekind (Item_Id) in E_Protected_Type | E_Task_Type then
2689 if Is_CCT_Instance (Item_Id, Spec_Id) then
2691 -- Pragma [Refined_]Global associated with a protected
2692 -- subprogram cannot mention the current instance of a
2693 -- protected type because the instance behaves as a
2694 -- formal parameter.
2696 if Ekind (Item_Id) = E_Protected_Type then
2697 if Scope (Spec_Id) = Item_Id then
2698 Error_Msg_Name_1 := Chars (Item_Id);
2699 SPARK_Msg_NE
2700 (Fix_Msg (Spec_Id, "global item of subprogram & "
2701 & "cannot reference current instance of "
2702 & "protected type %"), Item, Spec_Id);
2703 return;
2704 end if;
2706 -- Pragma [Refined_]Global associated with a task type
2707 -- cannot mention the current instance of a task type
2708 -- because the instance behaves as a formal parameter.
2710 else pragma Assert (Ekind (Item_Id) = E_Task_Type);
2711 if Spec_Id = Item_Id then
2712 Error_Msg_Name_1 := Chars (Item_Id);
2713 SPARK_Msg_NE
2714 (Fix_Msg (Spec_Id, "global item of subprogram & "
2715 & "cannot reference current instance of task "
2716 & "type %"), Item, Spec_Id);
2717 return;
2718 end if;
2719 end if;
2721 -- Otherwise the global item denotes a subtype mark that is
2722 -- not a current instance.
2724 else
2725 SPARK_Msg_N
2726 ("invalid use of subtype mark in global list", Item);
2727 return;
2728 end if;
2730 -- A global item may denote the anonymous object created for a
2731 -- single protected/task type as long as the current instance
2732 -- is the same single type (SPARK RM 6.1.4).
2734 elsif Is_Single_Concurrent_Object (Item_Id)
2735 and then Is_CCT_Instance (Etype (Item_Id), Spec_Id)
2736 then
2737 -- Pragma [Refined_]Global associated with a protected
2738 -- subprogram cannot mention the current instance of a
2739 -- protected type because the instance behaves as a formal
2740 -- parameter.
2742 if Is_Single_Protected_Object (Item_Id) then
2743 if Scope (Spec_Id) = Etype (Item_Id) then
2744 Error_Msg_Name_1 := Chars (Item_Id);
2745 SPARK_Msg_NE
2746 (Fix_Msg (Spec_Id, "global item of subprogram & "
2747 & "cannot reference current instance of protected "
2748 & "type %"), Item, Spec_Id);
2749 return;
2750 end if;
2752 -- Pragma [Refined_]Global associated with a task type
2753 -- cannot mention the current instance of a task type
2754 -- because the instance behaves as a formal parameter.
2756 else pragma Assert (Is_Single_Task_Object (Item_Id));
2757 if Spec_Id = Item_Id then
2758 Error_Msg_Name_1 := Chars (Item_Id);
2759 SPARK_Msg_NE
2760 (Fix_Msg (Spec_Id, "global item of subprogram & "
2761 & "cannot reference current instance of task "
2762 & "type %"), Item, Spec_Id);
2763 return;
2764 end if;
2765 end if;
2767 -- A formal object may act as a global item inside a generic
2769 elsif Is_Formal_Object (Item_Id) then
2770 null;
2772 elsif Ekind (Item_Id) in E_Constant | E_Variable
2773 and then Present (Ultimate_Overlaid_Entity (Item_Id))
2774 then
2775 SPARK_Msg_NE
2776 ("overlaying object & cannot appear in Global",
2777 Item, Item_Id);
2778 SPARK_Msg_NE
2779 ("\use the overlaid object & instead",
2780 Item, Ultimate_Overlaid_Entity (Item_Id));
2781 return;
2783 -- The only legal references are those to abstract states,
2784 -- objects and various kinds of constants (SPARK RM 6.1.4(4)).
2786 elsif Ekind (Item_Id) not in E_Abstract_State
2787 | E_Constant
2788 | E_Loop_Parameter
2789 | E_Variable
2790 then
2791 SPARK_Msg_N
2792 ("global item must denote object, state or current "
2793 & "instance of concurrent type", Item);
2795 if Is_Named_Number (Item_Id) then
2796 SPARK_Msg_NE
2797 ("\named number & is not an object", Item, Item_Id);
2798 end if;
2800 return;
2801 end if;
2803 -- State related checks
2805 if Ekind (Item_Id) = E_Abstract_State then
2807 -- Package and subprogram bodies are instantiated
2808 -- individually in a separate compiler pass. Due to this
2809 -- mode of instantiation, the refinement of a state may
2810 -- no longer be visible when a subprogram body contract
2811 -- is instantiated. Since the generic template is legal,
2812 -- do not perform this check in the instance to circumvent
2813 -- this oddity.
2815 if In_Instance then
2816 null;
2818 -- An abstract state with visible refinement cannot appear
2819 -- in pragma [Refined_]Global as its place must be taken by
2820 -- some of its constituents (SPARK RM 6.1.4(7)).
2822 elsif Has_Visible_Refinement (Item_Id) then
2823 SPARK_Msg_NE
2824 ("cannot mention state & in global refinement",
2825 Item, Item_Id);
2826 SPARK_Msg_N ("\use its constituents instead", Item);
2827 return;
2829 -- If the reference to the abstract state appears in an
2830 -- enclosing package body that will eventually refine the
2831 -- state, record the reference for future checks.
2833 else
2834 Record_Possible_Body_Reference
2835 (State_Id => Item_Id,
2836 Ref => Item);
2837 end if;
2839 -- Constant related checks
2841 elsif Ekind (Item_Id) = E_Constant then
2843 -- Constant is a read-only item, therefore it cannot act as
2844 -- an output.
2846 if Global_Mode in Name_In_Out | Name_Output then
2848 -- Constant of an access-to-variable type is a read-write
2849 -- item in procedures, generic procedures, protected
2850 -- entries and tasks.
2852 if Is_Access_Variable (Etype (Item_Id))
2853 and then (Ekind (Spec_Id) in E_Entry
2854 | E_Entry_Family
2855 | E_Procedure
2856 | E_Generic_Procedure
2857 | E_Task_Type
2858 or else Is_Single_Task_Object (Spec_Id)
2859 or else
2860 Is_Function_With_Side_Effects (Spec_Id))
2861 then
2862 null;
2863 else
2864 SPARK_Msg_NE
2865 ("constant & cannot act as output", Item, Item_Id);
2866 return;
2867 end if;
2868 end if;
2870 -- Loop parameter related checks
2872 elsif Ekind (Item_Id) = E_Loop_Parameter then
2874 -- A loop parameter is a read-only item, therefore it cannot
2875 -- act as an output.
2877 if Global_Mode in Name_In_Out | Name_Output then
2878 SPARK_Msg_NE
2879 ("loop parameter & cannot act as output",
2880 Item, Item_Id);
2881 return;
2882 end if;
2883 end if;
2885 -- When the item renames an entire object, replace the item
2886 -- with a reference to the object.
2888 if Entity (Item) /= Item_Id then
2889 Rewrite (Item, New_Occurrence_Of (Item_Id, Sloc (Item)));
2890 Analyze (Item);
2891 end if;
2893 -- Some form of illegal construct masquerading as a name
2894 -- (SPARK RM 6.1.4(4)).
2896 else
2897 Error_Msg_N
2898 ("global item must denote object, state or current instance "
2899 & "of concurrent type", Item);
2900 return;
2901 end if;
2903 -- Verify that an output does not appear as an input in an
2904 -- enclosing subprogram.
2906 if Global_Mode in Name_In_Out | Name_Output then
2907 Check_Mode_Restriction_In_Enclosing_Context (Item, Item_Id);
2908 end if;
2910 -- The same entity might be referenced through various way.
2911 -- Check the entity of the item rather than the item itself
2912 -- (SPARK RM 6.1.4(10)).
2914 if Contains (Seen, Item_Id) then
2915 SPARK_Msg_N ("duplicate global item", Item);
2917 -- Add the entity of the current item to the list of processed
2918 -- items.
2920 else
2921 Append_New_Elmt (Item_Id, Seen);
2923 if Ekind (Item_Id) = E_Abstract_State then
2924 Append_New_Elmt (Item_Id, States_Seen);
2926 -- The variable may eventually become a constituent of a single
2927 -- protected/task type. Record the reference now and verify its
2928 -- legality when analyzing the contract of the variable
2929 -- (SPARK RM 9.3).
2931 elsif Ekind (Item_Id) = E_Variable then
2932 Record_Possible_Part_Of_Reference
2933 (Var_Id => Item_Id,
2934 Ref => Item);
2935 end if;
2937 if Ekind (Item_Id) in E_Abstract_State | E_Constant | E_Variable
2938 and then Present (Encapsulating_State (Item_Id))
2939 then
2940 Append_New_Elmt (Item_Id, Constits_Seen);
2941 end if;
2942 end if;
2943 end Analyze_Global_Item;
2945 --------------------------
2946 -- Check_Duplicate_Mode --
2947 --------------------------
2949 procedure Check_Duplicate_Mode
2950 (Mode : Node_Id;
2951 Status : in out Boolean)
2953 begin
2954 if Status then
2955 SPARK_Msg_N ("duplicate global mode", Mode);
2956 end if;
2958 Status := True;
2959 end Check_Duplicate_Mode;
2961 -------------------------------------------------
2962 -- Check_Mode_Restriction_In_Enclosing_Context --
2963 -------------------------------------------------
2965 procedure Check_Mode_Restriction_In_Enclosing_Context
2966 (Item : Node_Id;
2967 Item_Id : Entity_Id)
2969 Context : Entity_Id;
2970 Dummy : Boolean;
2971 Item_View : Entity_Id;
2972 Inputs : Elist_Id := No_Elist;
2973 Outputs : Elist_Id := No_Elist;
2975 begin
2976 -- Traverse the scope stack looking for enclosing subprograms or
2977 -- tasks subject to pragma [Refined_]Global.
2979 Context := Scope (Subp_Id);
2980 Check_Context :
2981 while Present (Context) and then Context /= Standard_Standard loop
2983 -- For a single task type, retrieve the corresponding object to
2984 -- which pragma [Refined_]Global is attached.
2986 if Ekind (Context) = E_Task_Type
2987 and then Is_Single_Concurrent_Type (Context)
2988 then
2989 Context := Anonymous_Object (Context);
2990 end if;
2992 if Is_Subprogram_Or_Entry (Context)
2993 or else Ekind (Context) = E_Task_Type
2994 or else Is_Single_Task_Object (Context)
2995 then
2996 Collect_Subprogram_Inputs_Outputs
2997 (Subp_Id => Context,
2998 Subp_Inputs => Inputs,
2999 Subp_Outputs => Outputs,
3000 Global_Seen => Dummy);
3002 -- If the item is a constituent, we must check not just the
3003 -- item itself, but also its encapsulating abstract states.
3005 Item_View := Item_Id;
3007 Check_View : loop
3008 -- The item is classified as In_Out or Output but appears
3009 -- as an Input or a formal parameter of mode IN in
3010 -- an enclosing subprogram or task unit (SPARK RM
3011 -- 6.1.4(13)).
3013 if Appears_In (Inputs, Item_View)
3014 and then not Appears_In (Outputs, Item_View)
3015 then
3016 if Item_View = Item_Id then
3017 SPARK_Msg_NE
3018 ("global item & " &
3019 "cannot have mode In_Out or Output",
3020 Item, Item_Id);
3021 else
3022 Error_Msg_Node_2 := Item_View;
3023 SPARK_Msg_NE
3024 ("global constituent & of & " &
3025 "cannot have mode In_Out or Output",
3026 Item, Item_Id);
3027 end if;
3029 if Is_Subprogram_Or_Entry (Context) then
3030 SPARK_Msg_NE
3031 (Fix_Msg (Subp_Id, "\item already appears "
3032 & "as input of subprogram &"), Item, Context);
3033 else
3034 SPARK_Msg_NE
3035 (Fix_Msg (Subp_Id, "\item already appears "
3036 & "as input of task &"), Item, Context);
3037 end if;
3039 -- Stop the traversal once an error has been detected
3041 exit Check_Context;
3042 end if;
3044 if Ekind (Item_View) in E_Abstract_State
3045 | E_Constant
3046 | E_Variable
3047 then
3048 Item_View := Encapsulating_State (Item_View);
3050 exit Check_View when No (Item_View);
3051 else
3052 exit Check_View;
3053 end if;
3054 end loop Check_View;
3056 end if;
3058 Context := Scope (Context);
3059 end loop Check_Context;
3060 end Check_Mode_Restriction_In_Enclosing_Context;
3062 ----------------------------------------
3063 -- Check_Mode_Restriction_In_Function --
3064 ----------------------------------------
3066 procedure Check_Mode_Restriction_In_Function (Mode : Node_Id) is
3067 begin
3068 if Ekind (Spec_Id) in E_Function | E_Generic_Function
3069 and then not Is_Function_With_Side_Effects (Spec_Id)
3070 then
3071 Error_Msg_Code := GEC_Output_In_Function_Global_Or_Depends;
3072 SPARK_Msg_N
3073 ("global mode & is not applicable to function '[[]']", Mode);
3074 end if;
3075 end Check_Mode_Restriction_In_Function;
3077 -- Local variables
3079 Assoc : Node_Id;
3080 Item : Node_Id;
3081 Mode : Node_Id;
3083 -- Start of processing for Analyze_Global_List
3085 begin
3086 if Nkind (List) = N_Null then
3087 Set_Analyzed (List);
3089 -- Single global item declaration
3091 elsif Nkind (List) in N_Expanded_Name
3092 | N_Identifier
3093 | N_Selected_Component
3094 then
3095 Analyze_Global_Item (List, Global_Mode);
3097 -- Simple global list or moded global list declaration
3099 elsif Nkind (List) = N_Aggregate then
3100 Set_Analyzed (List);
3102 -- The declaration of a simple global list appear as a collection
3103 -- of expressions.
3105 if Present (Expressions (List)) then
3106 if Present (Component_Associations (List)) then
3107 SPARK_Msg_N
3108 ("cannot mix moded and non-moded global lists", List);
3109 end if;
3111 Item := First (Expressions (List));
3112 while Present (Item) loop
3113 Analyze_Global_Item (Item, Global_Mode);
3114 Next (Item);
3115 end loop;
3117 -- The declaration of a moded global list appears as a collection
3118 -- of component associations where individual choices denote
3119 -- modes.
3121 elsif Present (Component_Associations (List)) then
3122 if Present (Expressions (List)) then
3123 SPARK_Msg_N
3124 ("cannot mix moded and non-moded global lists", List);
3125 end if;
3127 Assoc := First (Component_Associations (List));
3128 while Present (Assoc) loop
3129 Mode := First (Choices (Assoc));
3131 if Nkind (Mode) = N_Identifier then
3132 if Chars (Mode) = Name_In_Out then
3133 Check_Duplicate_Mode (Mode, In_Out_Seen);
3134 Check_Mode_Restriction_In_Function (Mode);
3136 elsif Chars (Mode) = Name_Input then
3137 Check_Duplicate_Mode (Mode, Input_Seen);
3139 elsif Chars (Mode) = Name_Output then
3140 Check_Duplicate_Mode (Mode, Output_Seen);
3141 Check_Mode_Restriction_In_Function (Mode);
3143 elsif Chars (Mode) = Name_Proof_In then
3144 Check_Duplicate_Mode (Mode, Proof_Seen);
3146 else
3147 SPARK_Msg_N ("invalid mode selector", Mode);
3148 end if;
3150 else
3151 SPARK_Msg_N ("invalid mode selector", Mode);
3152 end if;
3154 -- Items in a moded list appear as a collection of
3155 -- expressions. Reuse the existing machinery to analyze
3156 -- them.
3158 Analyze_Global_List
3159 (List => Expression (Assoc),
3160 Global_Mode => Chars (Mode));
3162 Next (Assoc);
3163 end loop;
3165 -- Invalid tree
3167 else
3168 raise Program_Error;
3169 end if;
3171 -- Any other attempt to declare a global item is illegal. This is a
3172 -- syntax error, always report.
3174 else
3175 Error_Msg_N ("malformed global list", List);
3176 end if;
3177 end Analyze_Global_List;
3179 -- Local variables
3181 Items : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
3183 Restore_Scope : Boolean := False;
3185 -- Start of processing for Analyze_Global_In_Decl_Part
3187 begin
3188 -- Do not analyze the pragma multiple times
3190 if Is_Analyzed_Pragma (N) then
3191 return;
3192 end if;
3194 -- There is nothing to be done for a null global list
3196 if Nkind (Items) = N_Null then
3197 Set_Analyzed (Items);
3199 -- Analyze the various forms of global lists and items. Note that some
3200 -- of these may be malformed in which case the analysis emits error
3201 -- messages.
3203 else
3204 -- When pragma [Refined_]Global appears on a single concurrent type,
3205 -- it is relocated to the anonymous object.
3207 if Is_Single_Concurrent_Object (Spec_Id) then
3208 null;
3210 -- Ensure that the formal parameters are visible when processing an
3211 -- item. This falls out of the general rule of aspects pertaining to
3212 -- subprogram declarations.
3214 elsif not In_Open_Scopes (Spec_Id) then
3215 Restore_Scope := True;
3216 Push_Scope (Spec_Id);
3218 if Ekind (Spec_Id) = E_Task_Type then
3220 -- Task discriminants cannot appear in the [Refined_]Global
3221 -- contract, but must be present for the analysis so that we
3222 -- can reject them with an informative error message.
3224 if Has_Discriminants (Spec_Id) then
3225 Install_Discriminants (Spec_Id);
3226 end if;
3228 elsif Is_Generic_Subprogram (Spec_Id) then
3229 Install_Generic_Formals (Spec_Id);
3231 else
3232 Install_Formals (Spec_Id);
3233 end if;
3234 end if;
3236 Analyze_Global_List (Items);
3238 if Restore_Scope then
3239 End_Scope;
3240 end if;
3241 end if;
3243 -- Ensure that a state and a corresponding constituent do not appear
3244 -- together in pragma [Refined_]Global.
3246 Check_State_And_Constituent_Use
3247 (States => States_Seen,
3248 Constits => Constits_Seen,
3249 Context => N);
3251 Set_Is_Analyzed_Pragma (N);
3252 end Analyze_Global_In_Decl_Part;
3254 ---------------------------------
3255 -- Analyze_If_Present_Internal --
3256 ---------------------------------
3258 procedure Analyze_If_Present_Internal
3259 (N : Node_Id;
3260 Id : Pragma_Id;
3261 Included : Boolean)
3263 Stmt : Node_Id;
3265 begin
3266 pragma Assert (Is_List_Member (N));
3268 -- Inspect the declarations or statements following pragma N looking
3269 -- for another pragma whose Id matches the caller's request. If it is
3270 -- available, analyze it.
3272 if Included then
3273 Stmt := N;
3274 else
3275 Stmt := Next (N);
3276 end if;
3278 while Present (Stmt) loop
3279 if Nkind (Stmt) = N_Pragma and then Get_Pragma_Id (Stmt) = Id then
3280 Analyze_Pragma (Stmt);
3281 exit;
3283 -- The first source declaration or statement immediately following
3284 -- N ends the region where a pragma may appear.
3286 elsif Comes_From_Source (Stmt) then
3287 exit;
3288 end if;
3290 Next (Stmt);
3291 end loop;
3292 end Analyze_If_Present_Internal;
3294 --------------------------------------------
3295 -- Analyze_Initial_Condition_In_Decl_Part --
3296 --------------------------------------------
3298 -- WARNING: This routine manages Ghost regions. Return statements must be
3299 -- replaced by gotos which jump to the end of the routine and restore the
3300 -- Ghost mode.
3302 procedure Analyze_Initial_Condition_In_Decl_Part (N : Node_Id) is
3303 Pack_Decl : constant Node_Id := Find_Related_Package_Or_Body (N);
3304 Pack_Id : constant Entity_Id := Defining_Entity (Pack_Decl);
3305 Expr : constant Node_Id := Expression (Get_Argument (N, Pack_Id));
3307 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
3308 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
3309 -- Save the Ghost-related attributes to restore on exit
3311 begin
3312 -- Do not analyze the pragma multiple times
3314 if Is_Analyzed_Pragma (N) then
3315 return;
3316 end if;
3318 -- Set the Ghost mode in effect from the pragma. Due to the delayed
3319 -- analysis of the pragma, the Ghost mode at point of declaration and
3320 -- point of analysis may not necessarily be the same. Use the mode in
3321 -- effect at the point of declaration.
3323 Set_Ghost_Mode (N);
3325 -- The expression is preanalyzed because it has not been moved to its
3326 -- final place yet. A direct analysis may generate side effects and this
3327 -- is not desired at this point.
3329 Preanalyze_Assert_Expression (Expr, Standard_Boolean);
3330 Set_Is_Analyzed_Pragma (N);
3332 Restore_Ghost_Region (Saved_GM, Saved_IGR);
3333 end Analyze_Initial_Condition_In_Decl_Part;
3335 --------------------------------------
3336 -- Analyze_Initializes_In_Decl_Part --
3337 --------------------------------------
3339 procedure Analyze_Initializes_In_Decl_Part (N : Node_Id) is
3340 Pack_Decl : constant Node_Id := Find_Related_Package_Or_Body (N);
3341 Pack_Id : constant Entity_Id := Defining_Entity (Pack_Decl);
3343 Constits_Seen : Elist_Id := No_Elist;
3344 -- A list containing the entities of all constituents processed so far.
3345 -- It aids in detecting illegal usage of a state and a corresponding
3346 -- constituent in pragma Initializes.
3348 Items_Seen : Elist_Id := No_Elist;
3349 -- A list of all initialization items processed so far. This list is
3350 -- used to detect duplicate items.
3352 States_And_Objs : Elist_Id := No_Elist;
3353 -- A list of all abstract states and objects declared in the visible
3354 -- declarations of the related package. This list is used to detect the
3355 -- legality of initialization items.
3357 States_Seen : Elist_Id := No_Elist;
3358 -- A list containing the entities of all states processed so far. It
3359 -- helps in detecting illegal usage of a state and a corresponding
3360 -- constituent in pragma Initializes.
3362 procedure Analyze_Initialization_Item (Item : Node_Id);
3363 -- Verify the legality of a single initialization item
3365 procedure Analyze_Initialization_Item_With_Inputs (Item : Node_Id);
3366 -- Verify the legality of a single initialization item followed by a
3367 -- list of input items.
3369 procedure Collect_States_And_Objects (Pack_Decl : Node_Id);
3370 -- Inspect the visible declarations of the related package and gather
3371 -- the entities of all abstract states and objects in States_And_Objs.
3373 ---------------------------------
3374 -- Analyze_Initialization_Item --
3375 ---------------------------------
3377 procedure Analyze_Initialization_Item (Item : Node_Id) is
3378 Item_Id : Entity_Id;
3380 begin
3381 Analyze (Item);
3382 Resolve_State (Item);
3384 if Is_Entity_Name (Item) then
3385 Item_Id := Entity_Of (Item);
3387 if Present (Item_Id)
3388 and then Ekind (Item_Id) in
3389 E_Abstract_State | E_Constant | E_Variable
3390 then
3391 -- When the initialization item is undefined, it appears as
3392 -- Any_Id. Do not continue with the analysis of the item.
3394 if Item_Id = Any_Id then
3395 null;
3397 elsif Ekind (Item_Id) in E_Constant | E_Variable
3398 and then Present (Ultimate_Overlaid_Entity (Item_Id))
3399 then
3400 SPARK_Msg_NE
3401 ("overlaying object & cannot appear in Initializes",
3402 Item, Item_Id);
3403 SPARK_Msg_NE
3404 ("\use the overlaid object & instead",
3405 Item, Ultimate_Overlaid_Entity (Item_Id));
3407 -- The state or variable must be declared in the visible
3408 -- declarations of the package (SPARK RM 7.1.5(7)).
3410 elsif not Contains (States_And_Objs, Item_Id) then
3411 Error_Msg_Name_1 := Chars (Pack_Id);
3412 SPARK_Msg_NE
3413 ("initialization item & must appear in the visible "
3414 & "declarations of package %", Item, Item_Id);
3416 -- Detect a duplicate use of the same initialization item
3417 -- (SPARK RM 7.1.5(5)).
3419 elsif Contains (Items_Seen, Item_Id) then
3420 SPARK_Msg_N ("duplicate initialization item", Item);
3422 -- The item is legal, add it to the list of processed states
3423 -- and variables.
3425 else
3426 Append_New_Elmt (Item_Id, Items_Seen);
3428 if Ekind (Item_Id) = E_Abstract_State then
3429 Append_New_Elmt (Item_Id, States_Seen);
3430 end if;
3432 if Present (Encapsulating_State (Item_Id)) then
3433 Append_New_Elmt (Item_Id, Constits_Seen);
3434 end if;
3435 end if;
3437 -- The item references something that is not a state or object
3438 -- (SPARK RM 7.1.5(3)).
3440 else
3441 SPARK_Msg_N
3442 ("initialization item must denote object or state", Item);
3443 end if;
3445 -- Some form of illegal construct masquerading as a name
3446 -- (SPARK RM 7.1.5(3)). This is a syntax error, always report.
3448 else
3449 Error_Msg_N
3450 ("initialization item must denote object or state", Item);
3451 end if;
3452 end Analyze_Initialization_Item;
3454 ---------------------------------------------
3455 -- Analyze_Initialization_Item_With_Inputs --
3456 ---------------------------------------------
3458 procedure Analyze_Initialization_Item_With_Inputs (Item : Node_Id) is
3459 Inputs_Seen : Elist_Id := No_Elist;
3460 -- A list of all inputs processed so far. This list is used to detect
3461 -- duplicate uses of an input.
3463 Non_Null_Seen : Boolean := False;
3464 Null_Seen : Boolean := False;
3465 -- Flags used to check the legality of an input list
3467 procedure Analyze_Input_Item (Input : Node_Id);
3468 -- Verify the legality of a single input item
3470 ------------------------
3471 -- Analyze_Input_Item --
3472 ------------------------
3474 procedure Analyze_Input_Item (Input : Node_Id) is
3475 Input_Id : Entity_Id;
3477 begin
3478 -- Null input list
3480 if Nkind (Input) = N_Null then
3481 if Null_Seen then
3482 SPARK_Msg_N
3483 ("multiple null initializations not allowed", Item);
3485 elsif Non_Null_Seen then
3486 SPARK_Msg_N
3487 ("cannot mix null and non-null initialization item", Item);
3488 else
3489 Null_Seen := True;
3490 end if;
3492 -- Input item
3494 else
3495 Non_Null_Seen := True;
3497 if Null_Seen then
3498 SPARK_Msg_N
3499 ("cannot mix null and non-null initialization item", Item);
3500 end if;
3502 Analyze (Input);
3503 Resolve_State (Input);
3505 if Is_Entity_Name (Input) then
3506 Input_Id := Entity_Of (Input);
3508 if Present (Input_Id)
3509 and then Ekind (Input_Id) in E_Abstract_State
3510 | E_Constant
3511 | E_Generic_In_Out_Parameter
3512 | E_Generic_In_Parameter
3513 | E_In_Parameter
3514 | E_In_Out_Parameter
3515 | E_Out_Parameter
3516 | E_Protected_Type
3517 | E_Task_Type
3518 | E_Variable
3519 then
3520 -- The input cannot denote states or objects declared
3521 -- within the related package (SPARK RM 7.1.5(4)).
3523 if Within_Scope (Input_Id, Current_Scope) then
3525 -- Do not consider generic formal parameters or their
3526 -- respective mappings to generic formals. Even though
3527 -- the formals appear within the scope of the package,
3528 -- it is allowed for an initialization item to depend
3529 -- on an input item.
3531 if Is_Formal_Object (Input_Id) then
3532 null;
3534 elsif Ekind (Input_Id) in E_Constant | E_Variable
3535 and then Present (Corresponding_Generic_Association
3536 (Declaration_Node (Input_Id)))
3537 then
3538 null;
3540 else
3541 Error_Msg_Name_1 := Chars (Pack_Id);
3542 SPARK_Msg_NE
3543 ("input item & cannot denote a visible object or "
3544 & "state of package %", Input, Input_Id);
3545 return;
3546 end if;
3547 end if;
3549 if Ekind (Input_Id) in E_Constant | E_Variable
3550 and then Present (Ultimate_Overlaid_Entity (Input_Id))
3551 then
3552 SPARK_Msg_NE
3553 ("overlaying object & cannot appear in Initializes",
3554 Input, Input_Id);
3555 SPARK_Msg_NE
3556 ("\use the overlaid object & instead",
3557 Input, Ultimate_Overlaid_Entity (Input_Id));
3558 return;
3559 end if;
3561 -- Detect a duplicate use of the same input item
3562 -- (SPARK RM 7.1.5(5)).
3564 if Contains (Inputs_Seen, Input_Id) then
3565 SPARK_Msg_N ("duplicate input item", Input);
3566 return;
3567 end if;
3569 -- At this point it is known that the input is legal. Add
3570 -- it to the list of processed inputs.
3572 Append_New_Elmt (Input_Id, Inputs_Seen);
3574 if Ekind (Input_Id) = E_Abstract_State then
3575 Append_New_Elmt (Input_Id, States_Seen);
3576 end if;
3578 if Ekind (Input_Id) in E_Abstract_State
3579 | E_Constant
3580 | E_Variable
3581 and then Present (Encapsulating_State (Input_Id))
3582 then
3583 Append_New_Elmt (Input_Id, Constits_Seen);
3584 end if;
3586 -- The input references something that is not a state or an
3587 -- object (SPARK RM 7.1.5(3)).
3589 else
3590 SPARK_Msg_N
3591 ("input item must denote object or state", Input);
3592 end if;
3594 -- Some form of illegal construct masquerading as a name
3595 -- (SPARK RM 7.1.5(3)). This is a syntax error, always report.
3597 else
3598 Error_Msg_N
3599 ("input item must denote object or state", Input);
3600 end if;
3601 end if;
3602 end Analyze_Input_Item;
3604 -- Local variables
3606 Inputs : constant Node_Id := Expression (Item);
3607 Elmt : Node_Id;
3608 Input : Node_Id;
3610 Name_Seen : Boolean := False;
3611 -- A flag used to detect multiple item names
3613 -- Start of processing for Analyze_Initialization_Item_With_Inputs
3615 begin
3616 -- Inspect the name of an item with inputs
3618 Elmt := First (Choices (Item));
3619 while Present (Elmt) loop
3620 if Name_Seen then
3621 SPARK_Msg_N ("only one item allowed in initialization", Elmt);
3622 else
3623 Name_Seen := True;
3624 Analyze_Initialization_Item (Elmt);
3625 end if;
3627 Next (Elmt);
3628 end loop;
3630 -- Multiple input items appear as an aggregate
3632 if Nkind (Inputs) = N_Aggregate then
3633 if Present (Expressions (Inputs)) then
3634 Input := First (Expressions (Inputs));
3635 while Present (Input) loop
3636 Analyze_Input_Item (Input);
3637 Next (Input);
3638 end loop;
3639 end if;
3641 if Present (Component_Associations (Inputs)) then
3642 SPARK_Msg_N
3643 ("inputs must appear in named association form", Inputs);
3644 end if;
3646 -- Single input item
3648 else
3649 Analyze_Input_Item (Inputs);
3650 end if;
3651 end Analyze_Initialization_Item_With_Inputs;
3653 --------------------------------
3654 -- Collect_States_And_Objects --
3655 --------------------------------
3657 procedure Collect_States_And_Objects (Pack_Decl : Node_Id) is
3658 Pack_Spec : constant Node_Id := Specification (Pack_Decl);
3659 Pack_Id : constant Entity_Id := Defining_Entity (Pack_Decl);
3660 Decl : Node_Id;
3661 State_Elmt : Elmt_Id;
3663 begin
3664 -- Collect the abstract states defined in the package (if any)
3666 if Has_Non_Null_Abstract_State (Pack_Id) then
3667 State_Elmt := First_Elmt (Abstract_States (Pack_Id));
3668 while Present (State_Elmt) loop
3669 Append_New_Elmt (Node (State_Elmt), States_And_Objs);
3670 Next_Elmt (State_Elmt);
3671 end loop;
3672 end if;
3674 -- Collect all objects that appear in the visible declarations of the
3675 -- related package.
3677 Decl := First (Visible_Declarations (Pack_Spec));
3678 while Present (Decl) loop
3679 if Comes_From_Source (Decl)
3680 and then Nkind (Decl) in N_Object_Declaration
3681 | N_Object_Renaming_Declaration
3682 then
3683 Append_New_Elmt (Defining_Entity (Decl), States_And_Objs);
3685 elsif Nkind (Decl) = N_Package_Declaration then
3686 Collect_States_And_Objects (Decl);
3688 elsif Is_Single_Concurrent_Type_Declaration (Decl) then
3689 Append_New_Elmt
3690 (Anonymous_Object (Defining_Entity (Decl)),
3691 States_And_Objs);
3692 end if;
3694 Next (Decl);
3695 end loop;
3696 end Collect_States_And_Objects;
3698 -- Local variables
3700 Inits : constant Node_Id := Expression (Get_Argument (N, Pack_Id));
3701 Init : Node_Id;
3703 -- Start of processing for Analyze_Initializes_In_Decl_Part
3705 begin
3706 -- Do not analyze the pragma multiple times
3708 if Is_Analyzed_Pragma (N) then
3709 return;
3710 end if;
3712 -- Nothing to do when the initialization list is empty
3714 if Nkind (Inits) = N_Null then
3715 return;
3716 end if;
3718 -- Single and multiple initialization clauses appear as an aggregate. If
3719 -- this is not the case, then either the parser or the analysis of the
3720 -- pragma failed to produce an aggregate.
3722 pragma Assert (Nkind (Inits) = N_Aggregate);
3724 -- Initialize the various lists used during analysis
3726 Collect_States_And_Objects (Pack_Decl);
3728 if Present (Expressions (Inits)) then
3729 Init := First (Expressions (Inits));
3730 while Present (Init) loop
3731 Analyze_Initialization_Item (Init);
3732 Next (Init);
3733 end loop;
3734 end if;
3736 if Present (Component_Associations (Inits)) then
3737 Init := First (Component_Associations (Inits));
3738 while Present (Init) loop
3739 Analyze_Initialization_Item_With_Inputs (Init);
3740 Next (Init);
3741 end loop;
3742 end if;
3744 -- Ensure that a state and a corresponding constituent do not appear
3745 -- together in pragma Initializes.
3747 Check_State_And_Constituent_Use
3748 (States => States_Seen,
3749 Constits => Constits_Seen,
3750 Context => N);
3752 Set_Is_Analyzed_Pragma (N);
3753 end Analyze_Initializes_In_Decl_Part;
3755 ---------------------
3756 -- Analyze_Part_Of --
3757 ---------------------
3759 procedure Analyze_Part_Of
3760 (Indic : Node_Id;
3761 Item_Id : Entity_Id;
3762 Encap : Node_Id;
3763 Encap_Id : out Entity_Id;
3764 Legal : out Boolean)
3766 procedure Check_Part_Of_Abstract_State;
3767 pragma Inline (Check_Part_Of_Abstract_State);
3768 -- Verify the legality of indicator Part_Of when the encapsulator is an
3769 -- abstract state.
3771 procedure Check_Part_Of_Concurrent_Type;
3772 pragma Inline (Check_Part_Of_Concurrent_Type);
3773 -- Verify the legality of indicator Part_Of when the encapsulator is a
3774 -- single concurrent type.
3776 ----------------------------------
3777 -- Check_Part_Of_Abstract_State --
3778 ----------------------------------
3780 procedure Check_Part_Of_Abstract_State is
3781 Pack_Id : Entity_Id;
3782 Placement : State_Space_Kind;
3783 Parent_Unit : Entity_Id;
3785 begin
3786 -- Determine where the object, package instantiation or state lives
3787 -- with respect to the enclosing packages or package bodies.
3789 Find_Placement_In_State_Space
3790 (Item_Id => Item_Id,
3791 Placement => Placement,
3792 Pack_Id => Pack_Id);
3794 -- The item appears in a non-package construct with a declarative
3795 -- part (subprogram, block, etc). As such, the item is not allowed
3796 -- to be a part of an encapsulating state because the item is not
3797 -- visible.
3799 if Placement = Not_In_Package then
3800 SPARK_Msg_N
3801 ("indicator Part_Of cannot appear in this context "
3802 & "(SPARK RM 7.2.6(5))", Indic);
3804 Error_Msg_Name_1 := Chars (Scope (Encap_Id));
3805 SPARK_Msg_NE
3806 ("\& is not part of the hidden state of package %",
3807 Indic, Item_Id);
3808 return;
3810 -- The item appears in the visible state space of some package. In
3811 -- general this scenario does not warrant Part_Of except when the
3812 -- package is a nongeneric private child unit and the encapsulating
3813 -- state is declared in a parent unit or a public descendant of that
3814 -- parent unit.
3816 elsif Placement = Visible_State_Space then
3817 if Is_Child_Unit (Pack_Id)
3818 and then not Is_Generic_Unit (Pack_Id)
3819 and then Is_Private_Descendant (Pack_Id)
3820 then
3821 -- A variable or state abstraction which is part of the visible
3822 -- state of a nongeneric private child unit or its public
3823 -- descendants must have its Part_Of indicator specified. The
3824 -- Part_Of indicator must denote a state declared by either the
3825 -- parent unit of the private unit or by a public descendant of
3826 -- that parent unit.
3828 -- Find the nearest private ancestor (which can be the current
3829 -- unit itself).
3831 Parent_Unit := Pack_Id;
3832 while Present (Parent_Unit) loop
3833 exit when Is_Private_Library_Unit (Parent_Unit);
3834 Parent_Unit := Scope (Parent_Unit);
3835 end loop;
3837 Parent_Unit := Scope (Parent_Unit);
3839 if not Is_Child_Or_Sibling (Pack_Id, Scope (Encap_Id)) then
3840 SPARK_Msg_NE
3841 ("indicator Part_Of must denote abstract state of & or of "
3842 & "its public descendant (SPARK RM 7.2.6(3))",
3843 Indic, Parent_Unit);
3844 return;
3846 elsif Scope (Encap_Id) = Parent_Unit
3847 or else
3848 (Is_Ancestor_Package (Parent_Unit, Scope (Encap_Id))
3849 and then not Is_Private_Descendant (Scope (Encap_Id)))
3850 then
3851 null;
3853 else
3854 SPARK_Msg_NE
3855 ("indicator Part_Of must denote abstract state of & or of "
3856 & "its public descendant (SPARK RM 7.2.6(3))",
3857 Indic, Parent_Unit);
3858 return;
3859 end if;
3861 -- Indicator Part_Of is not needed when the related package is
3862 -- not a nongeneric private child unit or a public descendant
3863 -- thereof.
3865 else
3866 SPARK_Msg_N
3867 ("indicator Part_Of cannot appear in this context "
3868 & "(SPARK RM 7.2.6(5))", Indic);
3870 Error_Msg_Name_1 := Chars (Pack_Id);
3871 SPARK_Msg_NE
3872 ("\& is declared in the visible part of package %",
3873 Indic, Item_Id);
3874 return;
3875 end if;
3877 -- When the item appears in the private state space of a package, the
3878 -- encapsulating state must be declared in the same package.
3880 elsif Placement = Private_State_Space then
3882 -- In the case of the abstract state of a nongeneric private
3883 -- child package, it may be encapsulated in the state of a
3884 -- public descendant of its parent package.
3886 declare
3887 function Is_Public_Descendant
3888 (Child, Ancestor : Entity_Id)
3889 return Boolean;
3890 -- Return True if Child is a public descendant of Pack
3892 --------------------------
3893 -- Is_Public_Descendant --
3894 --------------------------
3896 function Is_Public_Descendant
3897 (Child, Ancestor : Entity_Id)
3898 return Boolean
3900 P : Entity_Id := Child;
3901 begin
3902 while Is_Child_Unit (P)
3903 and then not Is_Private_Library_Unit (P)
3904 loop
3905 if Scope (P) = Ancestor then
3906 return True;
3907 end if;
3909 P := Scope (P);
3910 end loop;
3912 return False;
3913 end Is_Public_Descendant;
3915 -- Local variables
3917 Immediate_Pack_Id : constant Entity_Id := Scope (Item_Id);
3919 Is_State_Of_Private_Child : constant Boolean :=
3920 Is_Child_Unit (Immediate_Pack_Id)
3921 and then not Is_Generic_Unit (Immediate_Pack_Id)
3922 and then Is_Private_Descendant (Immediate_Pack_Id);
3924 Is_OK_Through_Sibling : Boolean := False;
3926 begin
3927 if Ekind (Item_Id) = E_Abstract_State
3928 and then Is_State_Of_Private_Child
3929 and then Is_Public_Descendant (Scope (Encap_Id), Pack_Id)
3930 then
3931 Is_OK_Through_Sibling := True;
3932 end if;
3934 if Scope (Encap_Id) /= Pack_Id
3935 and then not Is_OK_Through_Sibling
3936 then
3937 if Is_State_Of_Private_Child then
3938 SPARK_Msg_NE
3939 ("indicator Part_Of must denote abstract state of & "
3940 & "or of its public descendant "
3941 & "(SPARK RM 7.2.6(3))", Indic, Pack_Id);
3942 else
3943 SPARK_Msg_NE
3944 ("indicator Part_Of must denote an abstract state of "
3945 & "package & (SPARK RM 7.2.6(2))", Indic, Pack_Id);
3946 end if;
3948 Error_Msg_Name_1 := Chars (Pack_Id);
3949 SPARK_Msg_NE
3950 ("\& is declared in the private part of package %",
3951 Indic, Item_Id);
3952 return;
3953 end if;
3954 end;
3956 -- Items declared in the body state space of a package do not need
3957 -- Part_Of indicators as the refinement has already been seen.
3959 else
3960 SPARK_Msg_N
3961 ("indicator Part_Of cannot appear in this context "
3962 & "(SPARK RM 7.2.6(5))", Indic);
3964 if Scope (Encap_Id) = Pack_Id then
3965 Error_Msg_Name_1 := Chars (Pack_Id);
3966 SPARK_Msg_NE
3967 ("\& is declared in the body of package %", Indic, Item_Id);
3968 end if;
3970 return;
3971 end if;
3973 -- In the case of state in a (descendant of a private) child which
3974 -- is Part_Of the state of another package, the package defining the
3975 -- encapsulating abstract state should have a body, to ensure that it
3976 -- has a state refinement (SPARK RM 7.1.4(4)).
3978 if Enclosing_Comp_Unit_Node (Encap_Id) /=
3979 Enclosing_Comp_Unit_Node (Item_Id)
3980 and then not Unit_Requires_Body (Scope (Encap_Id))
3981 then
3982 SPARK_Msg_N
3983 ("indicator Part_Of must denote abstract state of package "
3984 & "with a body (SPARK RM 7.1.4(4))", Indic);
3985 return;
3986 end if;
3988 -- At this point it is known that the Part_Of indicator is legal
3990 Legal := True;
3991 end Check_Part_Of_Abstract_State;
3993 -----------------------------------
3994 -- Check_Part_Of_Concurrent_Type --
3995 -----------------------------------
3997 procedure Check_Part_Of_Concurrent_Type is
3998 function In_Proper_Order
3999 (First : Node_Id;
4000 Second : Node_Id) return Boolean;
4001 pragma Inline (In_Proper_Order);
4002 -- Determine whether node First precedes node Second
4004 procedure Placement_Error;
4005 pragma Inline (Placement_Error);
4006 -- Emit an error concerning the illegal placement of the item with
4007 -- respect to the single concurrent type.
4009 ---------------------
4010 -- In_Proper_Order --
4011 ---------------------
4013 function In_Proper_Order
4014 (First : Node_Id;
4015 Second : Node_Id) return Boolean
4017 N : Node_Id;
4019 begin
4020 if List_Containing (First) = List_Containing (Second) then
4021 N := First;
4022 while Present (N) loop
4023 if N = Second then
4024 return True;
4025 end if;
4027 Next (N);
4028 end loop;
4029 end if;
4031 return False;
4032 end In_Proper_Order;
4034 ---------------------
4035 -- Placement_Error --
4036 ---------------------
4038 procedure Placement_Error is
4039 begin
4040 SPARK_Msg_N
4041 ("indicator Part_Of must denote a previously declared single "
4042 & "protected type or single task type", Encap);
4043 end Placement_Error;
4045 -- Local variables
4047 Conc_Typ : constant Entity_Id := Etype (Encap_Id);
4048 Encap_Decl : constant Node_Id := Declaration_Node (Encap_Id);
4049 Encap_Context : constant Node_Id := Parent (Encap_Decl);
4051 Item_Context : Node_Id;
4052 Item_Decl : Node_Id;
4053 Prv_Decls : List_Id;
4054 Vis_Decls : List_Id;
4056 -- Start of processing for Check_Part_Of_Concurrent_Type
4058 begin
4059 -- Only abstract states and variables can act as constituents of an
4060 -- encapsulating single concurrent type.
4062 if Ekind (Item_Id) in E_Abstract_State | E_Variable then
4063 null;
4065 -- The constituent is a constant
4067 elsif Ekind (Item_Id) = E_Constant then
4068 Error_Msg_Name_1 := Chars (Encap_Id);
4069 SPARK_Msg_NE
4070 (Fix_Msg (Conc_Typ, "constant & cannot act as constituent of "
4071 & "single protected type %"), Indic, Item_Id);
4072 return;
4074 -- The constituent is a package instantiation
4076 else
4077 Error_Msg_Name_1 := Chars (Encap_Id);
4078 SPARK_Msg_NE
4079 (Fix_Msg (Conc_Typ, "package instantiation & cannot act as "
4080 & "constituent of single protected type %"), Indic, Item_Id);
4081 return;
4082 end if;
4084 -- When the item denotes an abstract state of a nested package, use
4085 -- the declaration of the package to detect proper placement.
4087 -- package Pack is
4088 -- task T;
4089 -- package Nested
4090 -- with Abstract_State => (State with Part_Of => T)
4092 if Ekind (Item_Id) = E_Abstract_State then
4093 Item_Decl := Unit_Declaration_Node (Scope (Item_Id));
4094 else
4095 Item_Decl := Declaration_Node (Item_Id);
4096 end if;
4098 Item_Context := Parent (Item_Decl);
4100 -- The item and the single concurrent type must appear in the same
4101 -- declarative region, with the item following the declaration of
4102 -- the single concurrent type (SPARK RM 9(3)).
4104 if Item_Context = Encap_Context then
4105 if Nkind (Item_Context) in N_Package_Specification
4106 | N_Protected_Definition
4107 | N_Task_Definition
4108 then
4109 Prv_Decls := Private_Declarations (Item_Context);
4110 Vis_Decls := Visible_Declarations (Item_Context);
4112 -- The placement is OK when the single concurrent type appears
4113 -- within the visible declarations and the item in the private
4114 -- declarations.
4116 -- package Pack is
4117 -- protected PO ...
4118 -- private
4119 -- Constit : ... with Part_Of => PO;
4120 -- end Pack;
4122 if List_Containing (Encap_Decl) = Vis_Decls
4123 and then List_Containing (Item_Decl) = Prv_Decls
4124 then
4125 null;
4127 -- The placement is illegal when the item appears within the
4128 -- visible declarations and the single concurrent type is in
4129 -- the private declarations.
4131 -- package Pack is
4132 -- Constit : ... with Part_Of => PO;
4133 -- private
4134 -- protected PO ...
4135 -- end Pack;
4137 elsif List_Containing (Item_Decl) = Vis_Decls
4138 and then List_Containing (Encap_Decl) = Prv_Decls
4139 then
4140 Placement_Error;
4141 return;
4143 -- Otherwise both the item and the single concurrent type are
4144 -- in the same list. Ensure that the declaration of the single
4145 -- concurrent type precedes that of the item.
4147 elsif not In_Proper_Order
4148 (First => Encap_Decl,
4149 Second => Item_Decl)
4150 then
4151 Placement_Error;
4152 return;
4153 end if;
4155 -- Otherwise both the item and the single concurrent type are
4156 -- in the same list. Ensure that the declaration of the single
4157 -- concurrent type precedes that of the item.
4159 elsif not In_Proper_Order
4160 (First => Encap_Decl,
4161 Second => Item_Decl)
4162 then
4163 Placement_Error;
4164 return;
4165 end if;
4167 -- Otherwise the item and the single concurrent type reside within
4168 -- unrelated regions.
4170 else
4171 Error_Msg_Name_1 := Chars (Encap_Id);
4172 SPARK_Msg_NE
4173 (Fix_Msg (Conc_Typ, "constituent & must be declared "
4174 & "immediately within the same region as single protected "
4175 & "type %"), Indic, Item_Id);
4176 return;
4177 end if;
4179 -- At this point it is known that the Part_Of indicator is legal
4181 Legal := True;
4182 end Check_Part_Of_Concurrent_Type;
4184 -- Start of processing for Analyze_Part_Of
4186 begin
4187 -- Assume that the indicator is illegal
4189 Encap_Id := Empty;
4190 Legal := False;
4192 if Nkind (Encap) in
4193 N_Expanded_Name | N_Identifier | N_Selected_Component
4194 then
4195 Analyze (Encap);
4196 Resolve_State (Encap);
4198 Encap_Id := Entity (Encap);
4200 -- The encapsulator is an abstract state
4202 if Ekind (Encap_Id) = E_Abstract_State then
4203 null;
4205 -- The encapsulator is a single concurrent type (SPARK RM 9.3)
4207 elsif Is_Single_Concurrent_Object (Encap_Id) then
4208 null;
4210 -- Otherwise the encapsulator is not a legal choice
4212 else
4213 SPARK_Msg_N
4214 ("indicator Part_Of must denote abstract state, single "
4215 & "protected type or single task type", Encap);
4216 return;
4217 end if;
4219 -- This is a syntax error, always report
4221 else
4222 Error_Msg_N
4223 ("indicator Part_Of must denote abstract state, single protected "
4224 & "type or single task type", Encap);
4225 return;
4226 end if;
4228 -- Catch a case where indicator Part_Of denotes the abstract view of a
4229 -- variable which appears as an abstract state (SPARK RM 10.1.2 2).
4231 if From_Limited_With (Encap_Id)
4232 and then Present (Non_Limited_View (Encap_Id))
4233 and then Ekind (Non_Limited_View (Encap_Id)) = E_Variable
4234 then
4235 SPARK_Msg_N ("indicator Part_Of must denote abstract state", Encap);
4236 SPARK_Msg_N ("\& denotes abstract view of object", Encap);
4237 return;
4238 end if;
4240 -- The encapsulator is an abstract state
4242 if Ekind (Encap_Id) = E_Abstract_State then
4243 Check_Part_Of_Abstract_State;
4245 -- The encapsulator is a single concurrent type
4247 else
4248 Check_Part_Of_Concurrent_Type;
4249 end if;
4250 end Analyze_Part_Of;
4252 ----------------------------------
4253 -- Analyze_Part_Of_In_Decl_Part --
4254 ----------------------------------
4256 procedure Analyze_Part_Of_In_Decl_Part
4257 (N : Node_Id;
4258 Freeze_Id : Entity_Id := Empty)
4260 Encap : constant Node_Id :=
4261 Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
4262 Errors : constant Nat := Serious_Errors_Detected;
4263 Var_Decl : constant Node_Id := Find_Related_Context (N);
4264 Var_Id : constant Entity_Id := Defining_Entity (Var_Decl);
4265 Constits : Elist_Id;
4266 Encap_Id : Entity_Id;
4267 Legal : Boolean;
4269 begin
4270 -- Detect any discrepancies between the placement of the variable with
4271 -- respect to general state space and the encapsulating state or single
4272 -- concurrent type.
4274 Analyze_Part_Of
4275 (Indic => N,
4276 Item_Id => Var_Id,
4277 Encap => Encap,
4278 Encap_Id => Encap_Id,
4279 Legal => Legal);
4281 -- The Part_Of indicator turns the variable into a constituent of the
4282 -- encapsulating state or single concurrent type.
4284 if Legal then
4285 pragma Assert (Present (Encap_Id));
4286 Constits := Part_Of_Constituents (Encap_Id);
4288 if No (Constits) then
4289 Constits := New_Elmt_List;
4290 Set_Part_Of_Constituents (Encap_Id, Constits);
4291 end if;
4293 Append_Elmt (Var_Id, Constits);
4294 Set_Encapsulating_State (Var_Id, Encap_Id);
4296 -- A Part_Of constituent partially refines an abstract state. This
4297 -- property does not apply to protected or task units.
4299 if Ekind (Encap_Id) = E_Abstract_State then
4300 Set_Has_Partial_Visible_Refinement (Encap_Id);
4301 end if;
4302 end if;
4304 -- Emit a clarification message when the encapsulator is undefined,
4305 -- possibly due to contract freezing.
4307 if Errors /= Serious_Errors_Detected
4308 and then Present (Freeze_Id)
4309 and then Has_Undefined_Reference (Encap)
4310 then
4311 Contract_Freeze_Error (Var_Id, Freeze_Id);
4312 end if;
4313 end Analyze_Part_Of_In_Decl_Part;
4315 --------------------
4316 -- Analyze_Pragma --
4317 --------------------
4319 procedure Analyze_Pragma (N : Node_Id) is
4320 Loc : constant Source_Ptr := Sloc (N);
4322 Pname : Name_Id := Pragma_Name (N);
4323 -- Name of the source pragma, or name of the corresponding aspect for
4324 -- pragmas which originate in a source aspect. In the latter case, the
4325 -- name may be different from the pragma name.
4327 Prag_Id : constant Pragma_Id := Get_Pragma_Id (Pname);
4329 Pragma_Exit : exception;
4330 -- This exception is used to exit pragma processing completely. It
4331 -- is used when an error is detected, and no further processing is
4332 -- required. It is also used if an earlier error has left the tree in
4333 -- a state where the pragma should not be processed.
4335 Arg_Count : Nat;
4336 -- Number of pragma argument associations
4338 Arg1 : Node_Id;
4339 Arg2 : Node_Id;
4340 Arg3 : Node_Id;
4341 Arg4 : Node_Id;
4342 Arg5 : Node_Id;
4343 -- First five pragma arguments (pragma argument association nodes, or
4344 -- Empty if the corresponding argument does not exist).
4346 type Name_List is array (Natural range <>) of Name_Id;
4347 type Args_List is array (Natural range <>) of Node_Id;
4348 -- Types used for arguments to Check_Arg_Order and Gather_Associations
4350 -----------------------
4351 -- Local Subprograms --
4352 -----------------------
4354 procedure Ada_2005_Pragma;
4355 -- Called for pragmas defined in Ada 2005, that are not in Ada 95. In
4356 -- Ada 95 mode, these are implementation defined pragmas, so should be
4357 -- caught by the No_Implementation_Pragmas restriction.
4359 procedure Ada_2012_Pragma;
4360 -- Called for pragmas defined in Ada 2012, that are not in Ada 95 or 05.
4361 -- In Ada 95 or 05 mode, these are implementation defined pragmas, so
4362 -- should be caught by the No_Implementation_Pragmas restriction.
4364 procedure Analyze_Depends_Global
4365 (Spec_Id : out Entity_Id;
4366 Subp_Decl : out Node_Id;
4367 Legal : out Boolean);
4368 -- Subsidiary to the analysis of pragmas Depends and Global. Verify the
4369 -- legality of the placement and related context of the pragma. Spec_Id
4370 -- is the entity of the related subprogram. Subp_Decl is the declaration
4371 -- of the related subprogram. Sets flag Legal when the pragma is legal.
4373 procedure Analyze_If_Present (Id : Pragma_Id);
4374 -- Inspect the remainder of the list containing pragma N and look for
4375 -- a pragma that matches Id. If found, analyze the pragma.
4377 procedure Analyze_Pre_Post_Condition;
4378 -- Subsidiary to the analysis of pragmas Precondition and Postcondition
4380 procedure Analyze_Refined_Depends_Global_Post
4381 (Spec_Id : out Entity_Id;
4382 Body_Id : out Entity_Id;
4383 Legal : out Boolean);
4384 -- Subsidiary routine to the analysis of body pragmas Refined_Depends,
4385 -- Refined_Global and Refined_Post. Verify the legality of the placement
4386 -- and related context of the pragma. Spec_Id is the entity of the
4387 -- related subprogram. Body_Id is the entity of the subprogram body.
4388 -- Flag Legal is set when the pragma is legal.
4390 procedure Analyze_Unmodified_Or_Unused (Is_Unused : Boolean := False);
4391 -- Perform full analysis of pragma Unmodified and the write aspect of
4392 -- pragma Unused. Flag Is_Unused should be set when verifying the
4393 -- semantics of pragma Unused.
4395 procedure Analyze_Unreferenced_Or_Unused (Is_Unused : Boolean := False);
4396 -- Perform full analysis of pragma Unreferenced and the read aspect of
4397 -- pragma Unused. Flag Is_Unused should be set when verifying the
4398 -- semantics of pragma Unused.
4400 procedure Check_Ada_83_Warning;
4401 -- Issues a warning message for the current pragma if operating in Ada
4402 -- 83 mode (used for language pragmas that are not a standard part of
4403 -- Ada 83). This procedure does not raise Pragma_Exit. Also notes use
4404 -- of 95 pragma.
4406 procedure Check_Arg_Count (Required : Nat);
4407 -- Check argument count for pragma is equal to given parameter. If not,
4408 -- then issue an error message and raise Pragma_Exit.
4410 -- Note: all routines whose name is Check_Arg_Is_xxx take an argument
4411 -- Arg which can either be a pragma argument association, in which case
4412 -- the check is applied to the expression of the association or an
4413 -- expression directly.
4415 procedure Check_Arg_Is_External_Name (Arg : Node_Id);
4416 -- Check that an argument has the right form for an EXTERNAL_NAME
4417 -- parameter of an extended import/export pragma. The rule is that the
4418 -- name must be an identifier or string literal (in Ada 83 mode) or a
4419 -- static string expression (in Ada 95 mode).
4421 procedure Check_Arg_Is_Identifier (Arg : Node_Id);
4422 -- Check the specified argument Arg to make sure that it is an
4423 -- identifier. If not give error and raise Pragma_Exit.
4425 procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id);
4426 -- Check the specified argument Arg to make sure that it is an integer
4427 -- literal. If not give error and raise Pragma_Exit.
4429 procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id);
4430 -- Check the specified argument Arg to make sure that it has the proper
4431 -- syntactic form for a local name and meets the semantic requirements
4432 -- for a local name. The local name is analyzed as part of the
4433 -- processing for this call. In addition, the local name is required
4434 -- to represent an entity at the library level.
4436 procedure Check_Arg_Is_Local_Name (Arg : Node_Id);
4437 -- Check the specified argument Arg to make sure that it has the proper
4438 -- syntactic form for a local name and meets the semantic requirements
4439 -- for a local name. The local name is analyzed as part of the
4440 -- processing for this call.
4442 procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id);
4443 -- Check the specified argument Arg to make sure that it is a valid
4444 -- locking policy name. If not give error and raise Pragma_Exit.
4446 procedure Check_Arg_Is_Partition_Elaboration_Policy (Arg : Node_Id);
4447 -- Check the specified argument Arg to make sure that it is a valid
4448 -- elaboration policy name. If not give error and raise Pragma_Exit.
4450 procedure Check_Arg_Is_One_Of
4451 (Arg : Node_Id;
4452 N1, N2 : Name_Id);
4453 procedure Check_Arg_Is_One_Of
4454 (Arg : Node_Id;
4455 N1, N2, N3 : Name_Id);
4456 procedure Check_Arg_Is_One_Of
4457 (Arg : Node_Id;
4458 N1, N2, N3, N4 : Name_Id);
4459 procedure Check_Arg_Is_One_Of
4460 (Arg : Node_Id;
4461 N1, N2, N3, N4, N5 : Name_Id);
4462 -- Check the specified argument Arg to make sure that it is an
4463 -- identifier whose name matches either N1 or N2 (or N3, N4, N5 if
4464 -- present). If not then give error and raise Pragma_Exit.
4466 procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id);
4467 -- Check the specified argument Arg to make sure that it is a valid
4468 -- queuing policy name. If not give error and raise Pragma_Exit.
4470 procedure Check_Arg_Is_OK_Static_Expression
4471 (Arg : Node_Id;
4472 Typ : Entity_Id := Empty);
4473 -- Check the specified argument Arg to make sure that it is a static
4474 -- expression of the given type (i.e. it will be analyzed and resolved
4475 -- using this type, which can be any valid argument to Resolve, e.g.
4476 -- Any_Integer is OK). If not, given error and raise Pragma_Exit. If
4477 -- Typ is left Empty, then any static expression is allowed. Includes
4478 -- checking that the argument does not raise Constraint_Error.
4480 procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id);
4481 -- Check the specified argument Arg to make sure that it is a valid task
4482 -- dispatching policy name. If not give error and raise Pragma_Exit.
4484 procedure Check_Arg_Order (Names : Name_List);
4485 -- Checks for an instance of two arguments with identifiers for the
4486 -- current pragma which are not in the sequence indicated by Names,
4487 -- and if so, generates a fatal message about bad order of arguments.
4489 procedure Check_At_Least_N_Arguments (N : Nat);
4490 -- Check there are at least N arguments present
4492 procedure Check_At_Most_N_Arguments (N : Nat);
4493 -- Check there are no more than N arguments present
4495 procedure Check_Component
4496 (Comp : Node_Id;
4497 UU_Typ : Entity_Id;
4498 In_Variant_Part : Boolean := False);
4499 -- Examine an Unchecked_Union component for correct use of per-object
4500 -- constrained subtypes, and for restrictions on finalizable components.
4501 -- UU_Typ is the related Unchecked_Union type. Flag In_Variant_Part
4502 -- should be set when Comp comes from a record variant.
4504 procedure Check_Duplicate_Pragma (E : Entity_Id);
4505 -- Check if a rep item of the same name as the current pragma is already
4506 -- chained as a rep pragma to the given entity. If so give a message
4507 -- about the duplicate, and then raise Pragma_Exit so does not return.
4508 -- Note that if E is a type, then this routine avoids flagging a pragma
4509 -- which applies to a parent type from which E is derived.
4511 procedure Check_Duplicated_Export_Name (Nam : Node_Id);
4512 -- Nam is an N_String_Literal node containing the external name set by
4513 -- an Import or Export pragma (or extended Import or Export pragma).
4514 -- This procedure checks for possible duplications if this is the export
4515 -- case, and if found, issues an appropriate error message.
4517 procedure Check_Expr_Is_OK_Static_Expression
4518 (Expr : Node_Id;
4519 Typ : Entity_Id := Empty);
4520 -- Check the specified expression Expr to make sure that it is a static
4521 -- expression of the given type (i.e. it will be analyzed and resolved
4522 -- using this type, which can be any valid argument to Resolve, e.g.
4523 -- Any_Integer is OK). If not, given error and raise Pragma_Exit. If
4524 -- Typ is left Empty, then any static expression is allowed. Includes
4525 -- checking that the expression does not raise Constraint_Error.
4527 procedure Check_First_Subtype (Arg : Node_Id);
4528 -- Checks that Arg, whose expression is an entity name, references a
4529 -- first subtype.
4531 procedure Check_Identifier (Arg : Node_Id; Id : Name_Id);
4532 -- Checks that the given argument has an identifier, and if so, requires
4533 -- it to match the given identifier name. If there is no identifier, or
4534 -- a non-matching identifier, then an error message is given and
4535 -- Pragma_Exit is raised.
4537 procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
4538 -- Checks that the given argument has an identifier, and if so, requires
4539 -- it to match one of the given identifier names. If there is no
4540 -- identifier, or a non-matching identifier, then an error message is
4541 -- given and Pragma_Exit is raised.
4543 procedure Check_In_Main_Program;
4544 -- Common checks for pragmas that appear within a main program
4545 -- (Priority, Main_Storage, Time_Slice, Relative_Deadline, CPU).
4547 procedure Check_Interrupt_Or_Attach_Handler;
4548 -- Common processing for first argument of pragma Interrupt_Handler or
4549 -- pragma Attach_Handler.
4551 procedure Check_Loop_Pragma_Placement;
4552 -- Verify whether pragmas Loop_Invariant, Loop_Optimize and Loop_Variant
4553 -- appear immediately within a construct restricted to loops, and that
4554 -- pragmas Loop_Invariant and Loop_Variant are grouped together.
4556 procedure Check_Is_In_Decl_Part_Or_Package_Spec;
4557 -- Check that pragma appears in a declarative part, or in a package
4558 -- specification, i.e. that it does not occur in a statement sequence
4559 -- in a body.
4561 procedure Check_No_Identifier (Arg : Node_Id);
4562 -- Checks that the given argument does not have an identifier. If
4563 -- an identifier is present, then an error message is issued, and
4564 -- Pragma_Exit is raised.
4566 procedure Check_No_Identifiers;
4567 -- Checks that none of the arguments to the pragma has an identifier.
4568 -- If any argument has an identifier, then an error message is issued,
4569 -- and Pragma_Exit is raised.
4571 procedure Check_No_Link_Name;
4572 -- Checks that no link name is specified
4574 procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id);
4575 -- Checks if the given argument has an identifier, and if so, requires
4576 -- it to match the given identifier name. If there is a non-matching
4577 -- identifier, then an error message is given and Pragma_Exit is raised.
4579 procedure Check_Optional_Identifier (Arg : Node_Id; Id : String);
4580 -- Checks if the given argument has an identifier, and if so, requires
4581 -- it to match the given identifier name. If there is a non-matching
4582 -- identifier, then an error message is given and Pragma_Exit is raised.
4583 -- In this version of the procedure, the identifier name is given as
4584 -- a string with lower case letters.
4586 procedure Check_Static_Boolean_Expression (Expr : Node_Id);
4587 -- Subsidiary to the analysis of pragmas Async_Readers, Async_Writers,
4588 -- Constant_After_Elaboration, Effective_Reads, Effective_Writes,
4589 -- Extensions_Visible, Side_Effects and Volatile_Function. Ensure
4590 -- that expression Expr is an OK static boolean expression. Emit an
4591 -- error if this is not the case.
4593 procedure Check_Static_Constraint (Constr : Node_Id);
4594 -- Constr is a constraint from an N_Subtype_Indication node from a
4595 -- component constraint in an Unchecked_Union type, a range, or a
4596 -- discriminant association. This routine checks that the constraint
4597 -- is static as required by the restrictions for Unchecked_Union.
4599 procedure Check_Valid_Configuration_Pragma;
4600 -- Legality checks for placement of a configuration pragma
4602 procedure Check_Valid_Library_Unit_Pragma;
4603 -- Legality checks for library unit pragmas. A special case arises for
4604 -- pragmas in generic instances that come from copies of the original
4605 -- library unit pragmas in the generic templates. In the case of other
4606 -- than library level instantiations these can appear in contexts which
4607 -- would normally be invalid (they only apply to the original template
4608 -- and to library level instantiations), and they are simply ignored,
4609 -- which is implemented by rewriting them as null statements and
4610 -- optionally raising Pragma_Exit to terminate analysis. An exception
4611 -- is not always raised to avoid exception propagation during the
4612 -- bootstrap, so all callers should check whether N has been rewritten.
4614 procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id);
4615 -- Check an Unchecked_Union variant for lack of nested variants and
4616 -- presence of at least one component. UU_Typ is the related Unchecked_
4617 -- Union type.
4619 procedure Ensure_Aggregate_Form (Arg : Node_Id);
4620 -- Subsidiary routine to the processing of pragmas Abstract_State,
4621 -- Contract_Cases, Depends, Exceptional_Cases, Global, Initializes,
4622 -- Refined_Depends, Refined_Global, Refined_State and
4623 -- Subprogram_Variant. Transform argument Arg into an aggregate if not
4624 -- one already. N_Null is never transformed. Arg may denote an aspect
4625 -- specification or a pragma argument association.
4627 procedure Error_Pragma (Msg : String);
4628 pragma No_Return (Error_Pragma);
4629 -- Outputs error message for current pragma. The message contains a %
4630 -- that will be replaced with the pragma name, and the flag is placed
4631 -- on the pragma itself. Pragma_Exit is then raised. Note: this routine
4632 -- calls Fix_Error (see spec of that procedure for details).
4634 procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id);
4635 pragma No_Return (Error_Pragma_Arg);
4636 -- Outputs error message for current pragma. The message may contain
4637 -- a % that will be replaced with the pragma name. The parameter Arg
4638 -- may either be a pragma argument association, in which case the flag
4639 -- is placed on the expression of this association, or an expression,
4640 -- in which case the flag is placed directly on the expression. The
4641 -- message is placed using Error_Msg_N, so the message may also contain
4642 -- an & insertion character which will reference the given Arg value.
4643 -- After placing the message, Pragma_Exit is raised. Note: this routine
4644 -- calls Fix_Error (see spec of that procedure for details).
4646 procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id);
4647 pragma No_Return (Error_Pragma_Arg);
4648 -- Similar to above form of Error_Pragma_Arg except that two messages
4649 -- are provided, the second is a continuation comment starting with \.
4651 procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id);
4652 pragma No_Return (Error_Pragma_Arg_Ident);
4653 -- Outputs error message for current pragma. The message may contain a %
4654 -- that will be replaced with the pragma name. The parameter Arg must be
4655 -- a pragma argument association with a non-empty identifier (i.e. its
4656 -- Chars field must be set), and the error message is placed on the
4657 -- identifier. The message is placed using Error_Msg_N so the message
4658 -- may also contain an & insertion character which will reference
4659 -- the identifier. After placing the message, Pragma_Exit is raised.
4660 -- Note: this routine calls Fix_Error (see spec of that procedure for
4661 -- details).
4663 procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id);
4664 pragma No_Return (Error_Pragma_Ref);
4665 -- Outputs error message for current pragma. The message may contain
4666 -- a % that will be replaced with the pragma name. The parameter Ref
4667 -- must be an entity whose name can be referenced by & and sloc by #.
4668 -- After placing the message, Pragma_Exit is raised. Note: this routine
4669 -- calls Fix_Error (see spec of that procedure for details).
4671 function Find_Lib_Unit_Name return Entity_Id;
4672 -- Used for a library unit pragma to find the entity to which the
4673 -- library unit pragma applies, returns the entity found.
4675 procedure Find_Program_Unit_Name (Id : Node_Id);
4676 -- If the pragma is a compilation unit pragma, the id must denote the
4677 -- compilation unit in the same compilation, and the pragma must appear
4678 -- in the list of preceding or trailing pragmas. If it is a program
4679 -- unit pragma that is not a compilation unit pragma, then the
4680 -- identifier must be visible.
4682 function Find_Unique_Parameterless_Procedure
4683 (Name : Entity_Id;
4684 Arg : Node_Id) return Entity_Id;
4685 -- Used for a procedure pragma to find the unique parameterless
4686 -- procedure identified by Name, returns it if it exists, otherwise
4687 -- errors out and uses Arg as the pragma argument for the message.
4689 function Fix_Error (Msg : String) return String;
4690 -- This is called prior to issuing an error message. Msg is the normal
4691 -- error message issued in the pragma case. This routine checks for the
4692 -- case of a pragma coming from an aspect in the source, and returns a
4693 -- message suitable for the aspect case as follows:
4695 -- Each substring "pragma" is replaced by "aspect"
4697 -- If "argument of" is at the start of the error message text, it is
4698 -- replaced by "entity for".
4700 -- If "argument" is at the start of the error message text, it is
4701 -- replaced by "entity".
4703 -- So for example, "argument of pragma X must be discrete type"
4704 -- returns "entity for aspect X must be a discrete type".
4706 -- Finally Error_Msg_Name_1 is set to the name of the aspect (which may
4707 -- be different from the pragma name). If the current pragma results
4708 -- from rewriting another pragma, then Error_Msg_Name_1 is set to the
4709 -- original pragma name.
4711 procedure Gather_Associations
4712 (Names : Name_List;
4713 Args : out Args_List);
4714 -- This procedure is used to gather the arguments for a pragma that
4715 -- permits arbitrary ordering of parameters using the normal rules
4716 -- for named and positional parameters. The Names argument is a list
4717 -- of Name_Id values that corresponds to the allowed pragma argument
4718 -- association identifiers in order. The result returned in Args is
4719 -- a list of corresponding expressions that are the pragma arguments.
4720 -- Note that this is a list of expressions, not of pragma argument
4721 -- associations (Gather_Associations has completely checked all the
4722 -- optional identifiers when it returns). An entry in Args is Empty
4723 -- on return if the corresponding argument is not present.
4725 procedure GNAT_Pragma;
4726 -- Called for all GNAT defined pragmas to check the relevant restriction
4727 -- (No_Implementation_Pragmas).
4729 function Is_Before_First_Decl
4730 (Pragma_Node : Node_Id;
4731 Decls : List_Id) return Boolean;
4732 -- Return True if Pragma_Node is before the first declarative item in
4733 -- Decls where Decls is the list of declarative items.
4735 function Is_Configuration_Pragma return Boolean;
4736 -- Determines if the placement of the current pragma is appropriate
4737 -- for a configuration pragma.
4739 function Is_In_Context_Clause return Boolean;
4740 -- Returns True if pragma appears within the context clause of a unit,
4741 -- and False for any other placement (does not generate any messages).
4743 function Is_Static_String_Expression (Arg : Node_Id) return Boolean;
4744 -- Analyzes the argument, and determines if it is a static string
4745 -- expression, returns True if so, False if non-static or not String.
4746 -- A special case is that a string literal returns True in Ada 83 mode
4747 -- (which has no such thing as static string expressions). Note that
4748 -- the call analyzes its argument, so this cannot be used for the case
4749 -- where an identifier might not be declared.
4751 procedure Pragma_Misplaced;
4752 pragma No_Return (Pragma_Misplaced);
4753 -- Issue fatal error message for misplaced pragma
4755 procedure Process_Atomic_Independent_Shared_Volatile;
4756 -- Common processing for pragmas Atomic, Independent, Shared, Volatile,
4757 -- Volatile_Full_Access. Note that Shared is an obsolete Ada 83 pragma
4758 -- and treated as being identical in effect to pragma Atomic.
4760 procedure Process_Compile_Time_Warning_Or_Error;
4761 -- Common processing for Compile_Time_Error and Compile_Time_Warning
4763 procedure Process_Convention
4764 (C : out Convention_Id;
4765 Ent : out Entity_Id);
4766 -- Common processing for Convention, Interface, Import and Export.
4767 -- Checks first two arguments of pragma, and sets the appropriate
4768 -- convention value in the specified entity or entities. On return
4769 -- C is the convention, Ent is the referenced entity.
4771 procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id);
4772 -- Common processing for Disable/Enable_Atomic_Synchronization. Nam is
4773 -- Name_Suppress for Disable and Name_Unsuppress for Enable.
4775 procedure Process_Extended_Import_Export_Object_Pragma
4776 (Arg_Internal : Node_Id;
4777 Arg_External : Node_Id;
4778 Arg_Size : Node_Id);
4779 -- Common processing for the pragmas Import/Export_Object. The three
4780 -- arguments correspond to the three named parameters of the pragmas. An
4781 -- argument is empty if the corresponding parameter is not present in
4782 -- the pragma.
4784 procedure Process_Extended_Import_Export_Internal_Arg
4785 (Arg_Internal : Node_Id := Empty);
4786 -- Common processing for all extended Import and Export pragmas. The
4787 -- argument is the pragma parameter for the Internal argument. If
4788 -- Arg_Internal is empty or inappropriate, an error message is posted.
4789 -- Otherwise, on normal return, the Entity_Field of Arg_Internal is
4790 -- set to identify the referenced entity.
4792 procedure Process_Extended_Import_Export_Subprogram_Pragma
4793 (Arg_Internal : Node_Id;
4794 Arg_External : Node_Id;
4795 Arg_Parameter_Types : Node_Id;
4796 Arg_Result_Type : Node_Id := Empty;
4797 Arg_Mechanism : Node_Id;
4798 Arg_Result_Mechanism : Node_Id := Empty);
4799 -- Common processing for all extended Import and Export pragmas applying
4800 -- to subprograms. The caller omits any arguments that do not apply to
4801 -- the pragma in question (for example, Arg_Result_Type can be non-Empty
4802 -- only in the Import_Function and Export_Function cases). The argument
4803 -- names correspond to the allowed pragma association identifiers.
4805 procedure Process_Generic_List;
4806 -- Common processing for Share_Generic and Inline_Generic
4808 procedure Process_Import_Or_Interface;
4809 -- Common processing for Import or Interface
4811 procedure Process_Import_Predefined_Type;
4812 -- Processing for completing a type with pragma Import. This is used
4813 -- to declare types that match predefined C types, especially for cases
4814 -- without corresponding Ada predefined type.
4816 type Inline_Status is (Suppressed, Disabled, Enabled);
4817 -- Inline status of a subprogram, indicated as follows:
4818 -- Suppressed: inlining is suppressed for the subprogram
4819 -- Disabled: no inlining is requested for the subprogram
4820 -- Enabled: inlining is requested/required for the subprogram
4822 procedure Process_Inline (Status : Inline_Status);
4823 -- Common processing for No_Inline, Inline and Inline_Always. Parameter
4824 -- indicates the inline status specified by the pragma.
4826 procedure Process_Interface_Name
4827 (Subprogram_Def : Entity_Id;
4828 Ext_Arg : Node_Id;
4829 Link_Arg : Node_Id;
4830 Prag : Node_Id);
4831 -- Given the last two arguments of pragma Import, pragma Export, or
4832 -- pragma Interface_Name, performs validity checks and sets the
4833 -- Interface_Name field of the given subprogram entity to the
4834 -- appropriate external or link name, depending on the arguments given.
4835 -- Ext_Arg is always present, but Link_Arg may be missing. Note that
4836 -- Ext_Arg may represent the Link_Name if Link_Arg is missing, and
4837 -- appropriate named notation is used for Ext_Arg. If neither Ext_Arg
4838 -- nor Link_Arg is present, the interface name is set to the default
4839 -- from the subprogram name. In addition, the pragma itself is passed
4840 -- to analyze any expressions in the case the pragma came from an aspect
4841 -- specification.
4843 procedure Process_Interrupt_Or_Attach_Handler;
4844 -- Common processing for Interrupt and Attach_Handler pragmas
4846 procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
4847 -- Common processing for Restrictions and Restriction_Warnings pragmas.
4848 -- Warn is True for Restriction_Warnings, or for Restrictions if the
4849 -- flag Treat_Restrictions_As_Warnings is set, and False if this flag
4850 -- is not set in the Restrictions case.
4852 procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
4853 -- Common processing for Suppress and Unsuppress. The boolean parameter
4854 -- Suppress_Case is True for the Suppress case, and False for the
4855 -- Unsuppress case.
4857 procedure Record_Independence_Check (N : Node_Id; E : Entity_Id);
4858 -- Subsidiary to the analysis of pragmas Independent[_Components].
4859 -- Record such a pragma N applied to entity E for future checks.
4861 procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
4862 -- This procedure sets the Is_Exported flag for the given entity,
4863 -- checking that the entity was not previously imported. Arg is
4864 -- the argument that specified the entity. A check is also made
4865 -- for exporting inappropriate entities.
4867 procedure Set_Extended_Import_Export_External_Name
4868 (Internal_Ent : Entity_Id;
4869 Arg_External : Node_Id);
4870 -- Common processing for all extended import export pragmas. The first
4871 -- argument, Internal_Ent, is the internal entity, which has already
4872 -- been checked for validity by the caller. Arg_External is from the
4873 -- Import or Export pragma, and may be null if no External parameter
4874 -- was present. If Arg_External is present and is a non-null string
4875 -- (a null string is treated as the default), then the Interface_Name
4876 -- field of Internal_Ent is set appropriately.
4878 procedure Set_Imported (E : Entity_Id);
4879 -- This procedure sets the Is_Imported flag for the given entity,
4880 -- checking that it is not previously exported or imported.
4882 procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
4883 -- Mech is a parameter passing mechanism (see Import_Function syntax
4884 -- for MECHANISM_NAME). This routine checks that the mechanism argument
4885 -- has the right form, and if not issues an error message. If the
4886 -- argument has the right form then the Mechanism field of Ent is
4887 -- set appropriately.
4889 procedure Set_Rational_Profile;
4890 -- Activate the set of configuration pragmas and permissions that make
4891 -- up the Rational profile.
4893 procedure Set_Ravenscar_Profile (Profile : Profile_Name; N : Node_Id);
4894 -- Activate the set of configuration pragmas and restrictions that make
4895 -- up the Profile. Profile must be either GNAT_Extended_Ravenscar,
4896 -- GNAT_Ravenscar_EDF, Jorvik, or Ravenscar. N is the corresponding
4897 -- pragma node, which is used for error messages on any constructs
4898 -- violating the profile.
4900 ---------------------
4901 -- Ada_2005_Pragma --
4902 ---------------------
4904 procedure Ada_2005_Pragma is
4905 begin
4906 if Ada_Version <= Ada_95 then
4907 Check_Restriction (No_Implementation_Pragmas, N);
4908 end if;
4909 end Ada_2005_Pragma;
4911 ---------------------
4912 -- Ada_2012_Pragma --
4913 ---------------------
4915 procedure Ada_2012_Pragma is
4916 begin
4917 if Ada_Version <= Ada_2005 then
4918 Check_Restriction (No_Implementation_Pragmas, N);
4919 end if;
4920 end Ada_2012_Pragma;
4922 ----------------------------
4923 -- Analyze_Depends_Global --
4924 ----------------------------
4926 procedure Analyze_Depends_Global
4927 (Spec_Id : out Entity_Id;
4928 Subp_Decl : out Node_Id;
4929 Legal : out Boolean)
4931 begin
4932 -- Assume that the pragma is illegal
4934 Spec_Id := Empty;
4935 Subp_Decl := Empty;
4936 Legal := False;
4938 GNAT_Pragma;
4939 Check_Arg_Count (1);
4941 -- Ensure the proper placement of the pragma. Depends/Global must be
4942 -- associated with a subprogram declaration or a body that acts as a
4943 -- spec.
4945 Subp_Decl := Find_Related_Declaration_Or_Body (N, Do_Checks => True);
4947 -- Entry
4949 if Nkind (Subp_Decl) = N_Entry_Declaration then
4950 null;
4952 -- Generic subprogram
4954 elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
4955 null;
4957 -- Object declaration of a single concurrent type
4959 elsif Nkind (Subp_Decl) = N_Object_Declaration
4960 and then Is_Single_Concurrent_Object
4961 (Unique_Defining_Entity (Subp_Decl))
4962 then
4963 null;
4965 -- Single task type
4967 elsif Nkind (Subp_Decl) = N_Single_Task_Declaration then
4968 null;
4970 -- Abstract subprogram declaration
4972 elsif Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
4973 null;
4975 -- Subprogram body acts as spec
4977 elsif Nkind (Subp_Decl) = N_Subprogram_Body
4978 and then No (Corresponding_Spec (Subp_Decl))
4979 then
4980 null;
4982 -- Subprogram body stub acts as spec
4984 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
4985 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
4986 then
4987 null;
4989 -- Subprogram declaration
4991 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
4993 -- Pragmas Global and Depends are forbidden on null procedures
4994 -- (SPARK RM 6.1.2(2)).
4996 if Nkind (Specification (Subp_Decl)) = N_Procedure_Specification
4997 and then Null_Present (Specification (Subp_Decl))
4998 then
4999 Error_Msg_N (Fix_Error
5000 ("pragma % cannot apply to null procedure"), N);
5001 return;
5002 end if;
5004 -- Task type
5006 elsif Nkind (Subp_Decl) = N_Task_Type_Declaration then
5007 null;
5009 else
5010 Pragma_Misplaced;
5011 end if;
5013 -- If we get here, then the pragma is legal
5015 Legal := True;
5016 Spec_Id := Unique_Defining_Entity (Subp_Decl);
5018 -- When the related context is an entry, the entry must belong to a
5019 -- protected unit (SPARK RM 6.1.4(6)).
5021 if Is_Entry_Declaration (Spec_Id)
5022 and then Ekind (Scope (Spec_Id)) /= E_Protected_Type
5023 then
5024 Pragma_Misplaced;
5026 -- When the related context is an anonymous object created for a
5027 -- simple concurrent type, the type must be a task
5028 -- (SPARK RM 6.1.4(6)).
5030 elsif Is_Single_Concurrent_Object (Spec_Id)
5031 and then Ekind (Etype (Spec_Id)) /= E_Task_Type
5032 then
5033 Pragma_Misplaced;
5034 end if;
5036 -- A pragma that applies to a Ghost entity becomes Ghost for the
5037 -- purposes of legality checks and removal of ignored Ghost code.
5039 Mark_Ghost_Pragma (N, Spec_Id);
5040 Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
5041 end Analyze_Depends_Global;
5043 ------------------------
5044 -- Analyze_If_Present --
5045 ------------------------
5047 procedure Analyze_If_Present (Id : Pragma_Id) is
5048 begin
5049 Analyze_If_Present_Internal (N, Id, Included => False);
5050 end Analyze_If_Present;
5052 --------------------------------
5053 -- Analyze_Pre_Post_Condition --
5054 --------------------------------
5056 procedure Analyze_Pre_Post_Condition is
5057 Prag_Iden : constant Node_Id := Pragma_Identifier (N);
5058 Subp_Decl : Node_Id;
5059 Subp_Id : Entity_Id;
5061 Duplicates_OK : Boolean := False;
5062 -- Flag set when a pre/postcondition allows multiple pragmas of the
5063 -- same kind.
5065 In_Body_OK : Boolean := False;
5066 -- Flag set when a pre/postcondition is allowed to appear on a body
5067 -- even though the subprogram may have a spec.
5069 Is_Pre_Post : Boolean := False;
5070 -- Flag set when the pragma is one of Pre, Pre_Class, Post or
5071 -- Post_Class.
5073 function Inherits_Class_Wide_Pre (E : Entity_Id) return Boolean;
5074 -- Implement rules in AI12-0131: an overriding operation can have
5075 -- a class-wide precondition only if one of its ancestors has an
5076 -- explicit class-wide precondition.
5078 -----------------------------
5079 -- Inherits_Class_Wide_Pre --
5080 -----------------------------
5082 function Inherits_Class_Wide_Pre (E : Entity_Id) return Boolean is
5083 Typ : constant Entity_Id := Find_Dispatching_Type (E);
5084 Cont : Node_Id;
5085 Prag : Node_Id;
5086 Prev : Entity_Id := Overridden_Operation (E);
5088 begin
5089 -- Check ancestors on the overriding operation to examine the
5090 -- preconditions that may apply to them.
5092 while Present (Prev) loop
5093 Cont := Contract (Prev);
5094 if Present (Cont) then
5095 Prag := Pre_Post_Conditions (Cont);
5096 while Present (Prag) loop
5097 if Pragma_Name (Prag) = Name_Precondition
5098 and then Class_Present (Prag)
5099 then
5100 return True;
5101 end if;
5103 Prag := Next_Pragma (Prag);
5104 end loop;
5105 end if;
5107 -- For a type derived from a generic formal type, the operation
5108 -- inheriting the condition is a renaming, not an overriding of
5109 -- the operation of the formal. Ditto for an inherited
5110 -- operation which has no explicit contracts.
5112 if Is_Generic_Type (Find_Dispatching_Type (Prev))
5113 or else not Comes_From_Source (Prev)
5114 then
5115 Prev := Alias (Prev);
5116 else
5117 Prev := Overridden_Operation (Prev);
5118 end if;
5119 end loop;
5121 -- If the controlling type of the subprogram has progenitors, an
5122 -- interface operation implemented by the current operation may
5123 -- have a class-wide precondition.
5125 if Has_Interfaces (Typ) then
5126 declare
5127 Elmt : Elmt_Id;
5128 Ints : Elist_Id;
5129 Prim : Entity_Id;
5130 Prim_Elmt : Elmt_Id;
5131 Prim_List : Elist_Id;
5133 begin
5134 Collect_Interfaces (Typ, Ints);
5135 Elmt := First_Elmt (Ints);
5137 -- Iterate over the primitive operations of each interface
5139 while Present (Elmt) loop
5140 Prim_List := Direct_Primitive_Operations (Node (Elmt));
5141 Prim_Elmt := First_Elmt (Prim_List);
5142 while Present (Prim_Elmt) loop
5143 Prim := Node (Prim_Elmt);
5144 if Chars (Prim) = Chars (E)
5145 and then Present (Contract (Prim))
5146 and then Class_Present
5147 (Pre_Post_Conditions (Contract (Prim)))
5148 then
5149 return True;
5150 end if;
5152 Next_Elmt (Prim_Elmt);
5153 end loop;
5155 Next_Elmt (Elmt);
5156 end loop;
5157 end;
5158 end if;
5160 return False;
5161 end Inherits_Class_Wide_Pre;
5163 -- Start of processing for Analyze_Pre_Post_Condition
5165 begin
5166 -- Change the name of pragmas Pre, Pre_Class, Post and Post_Class to
5167 -- offer uniformity among the various kinds of pre/postconditions by
5168 -- rewriting the pragma identifier. This allows the retrieval of the
5169 -- original pragma name by routine Original_Aspect_Pragma_Name.
5171 if Comes_From_Source (N) then
5172 if Pname in Name_Pre | Name_Pre_Class then
5173 Is_Pre_Post := True;
5174 Set_Class_Present (N, Pname = Name_Pre_Class);
5175 Rewrite (Prag_Iden, Make_Identifier (Loc, Name_Precondition));
5177 elsif Pname in Name_Post | Name_Post_Class then
5178 Is_Pre_Post := True;
5179 Set_Class_Present (N, Pname = Name_Post_Class);
5180 Rewrite (Prag_Iden, Make_Identifier (Loc, Name_Postcondition));
5181 end if;
5182 end if;
5184 -- Determine the semantics with respect to duplicates and placement
5185 -- in a body. Pragmas Precondition and Postcondition were introduced
5186 -- before aspects and are not subject to the same aspect-like rules.
5188 if Pname in Name_Precondition | Name_Postcondition then
5189 Duplicates_OK := True;
5190 In_Body_OK := True;
5191 end if;
5193 GNAT_Pragma;
5195 -- Pragmas Pre, Pre_Class, Post and Post_Class allow for a single
5196 -- argument without an identifier.
5198 if Is_Pre_Post then
5199 Check_Arg_Count (1);
5200 Check_No_Identifiers;
5202 -- Pragmas Precondition and Postcondition have complex argument
5203 -- profile.
5205 else
5206 Check_At_Least_N_Arguments (1);
5207 Check_At_Most_N_Arguments (2);
5208 Check_Optional_Identifier (Arg1, Name_Check);
5210 if Present (Arg2) then
5211 Check_Optional_Identifier (Arg2, Name_Message);
5212 Preanalyze_Spec_Expression
5213 (Get_Pragma_Arg (Arg2), Standard_String);
5214 end if;
5215 end if;
5217 -- For a pragma PPC in the extended main source unit, record enabled
5218 -- status in SCO.
5219 -- ??? nothing checks that the pragma is in the main source unit
5221 if Is_Checked (N) then
5222 Set_SCO_Pragma_Enabled (Loc);
5223 end if;
5225 -- Ensure the proper placement of the pragma
5227 Subp_Decl :=
5228 Find_Related_Declaration_Or_Body
5229 (N, Do_Checks => not Duplicates_OK);
5231 -- When a pre/postcondition pragma applies to an abstract subprogram,
5232 -- its original form must be an aspect with 'Class.
5234 if Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
5235 if not From_Aspect_Specification (N) then
5236 Error_Pragma
5237 ("pragma % cannot be applied to abstract subprogram");
5239 elsif not Class_Present (N) then
5240 Error_Pragma
5241 ("aspect % requires ''Class for abstract subprogram");
5242 end if;
5244 -- Entry declaration
5246 elsif Nkind (Subp_Decl) = N_Entry_Declaration then
5247 null;
5249 -- Generic subprogram declaration
5251 elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
5252 null;
5254 -- Subprogram body
5256 elsif Nkind (Subp_Decl) = N_Subprogram_Body
5257 and then (No (Corresponding_Spec (Subp_Decl)) or In_Body_OK)
5258 then
5259 null;
5261 -- Subprogram body stub
5263 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
5264 and then (No (Corresponding_Spec_Of_Stub (Subp_Decl)) or In_Body_OK)
5265 then
5266 null;
5268 -- Subprogram declaration
5270 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
5272 -- AI05-0230: When a pre/postcondition pragma applies to a null
5273 -- procedure, its original form must be an aspect with 'Class.
5275 if Nkind (Specification (Subp_Decl)) = N_Procedure_Specification
5276 and then Null_Present (Specification (Subp_Decl))
5277 and then From_Aspect_Specification (N)
5278 and then not Class_Present (N)
5279 then
5280 Error_Pragma ("aspect % requires ''Class for null procedure");
5281 end if;
5283 -- Implement the legality checks mandated by AI12-0131:
5284 -- Pre'Class shall not be specified for an overriding primitive
5285 -- subprogram of a tagged type T unless the Pre'Class aspect is
5286 -- specified for the corresponding primitive subprogram of some
5287 -- ancestor of T.
5289 declare
5290 E : constant Entity_Id := Defining_Entity (Subp_Decl);
5292 begin
5293 if Class_Present (N)
5294 and then Pragma_Name (N) = Name_Precondition
5295 and then Present (Overridden_Operation (E))
5296 and then not Inherits_Class_Wide_Pre (E)
5297 then
5298 Error_Msg_N
5299 ("illegal class-wide precondition on overriding operation",
5300 Corresponding_Aspect (N));
5301 end if;
5302 end;
5304 -- A renaming declaration may inherit a generated pragma, its
5305 -- placement comes from expansion, not from source.
5307 elsif Nkind (Subp_Decl) = N_Subprogram_Renaming_Declaration
5308 and then not Comes_From_Source (N)
5309 then
5310 null;
5312 -- For Ada 2022, pre/postconditions can appear on formal subprograms
5314 elsif Nkind (Subp_Decl) = N_Formal_Concrete_Subprogram_Declaration
5315 and then Ada_Version >= Ada_2022
5316 then
5317 null;
5319 -- An access-to-subprogram type can have pre/postconditions, which
5320 -- are both analyzed when attached to the type and copied to the
5321 -- generated subprogram wrapper and analyzed there.
5323 elsif Nkind (Subp_Decl) = N_Full_Type_Declaration
5324 and then Nkind (Type_Definition (Subp_Decl)) in
5325 N_Access_To_Subprogram_Definition
5326 then
5327 if Ada_Version < Ada_2022 then
5328 Error_Msg_Ada_2022_Feature
5329 ("pre/postcondition on access-to-subprogram", Loc);
5330 raise Pragma_Exit;
5331 end if;
5333 -- Otherwise the placement of the pragma is illegal
5335 else
5336 Pragma_Misplaced;
5337 end if;
5339 Subp_Id := Defining_Entity (Subp_Decl);
5341 -- A pragma that applies to a Ghost entity becomes Ghost for the
5342 -- purposes of legality checks and removal of ignored Ghost code.
5344 Mark_Ghost_Pragma (N, Subp_Id);
5346 -- Chain the pragma on the contract for further processing by
5347 -- Analyze_Pre_Post_Condition_In_Decl_Part.
5349 if Ekind (Subp_Id) in Access_Subprogram_Kind then
5350 Add_Contract_Item (N, Directly_Designated_Type (Subp_Id));
5351 else
5352 Add_Contract_Item (N, Subp_Id);
5353 end if;
5355 -- Fully analyze the pragma when it appears inside an entry or
5356 -- subprogram body because it cannot benefit from forward references.
5358 if Nkind (Subp_Decl) in N_Entry_Body
5359 | N_Subprogram_Body
5360 | N_Subprogram_Body_Stub
5361 then
5362 -- The legality checks of pragmas Precondition and Postcondition
5363 -- are affected by the SPARK mode in effect and the volatility of
5364 -- the context. Analyze all pragmas in a specific order.
5366 Analyze_If_Present (Pragma_SPARK_Mode);
5367 Analyze_If_Present (Pragma_Volatile_Function);
5368 Analyze_Pre_Post_Condition_In_Decl_Part (N);
5369 end if;
5370 end Analyze_Pre_Post_Condition;
5372 -----------------------------------------
5373 -- Analyze_Refined_Depends_Global_Post --
5374 -----------------------------------------
5376 procedure Analyze_Refined_Depends_Global_Post
5377 (Spec_Id : out Entity_Id;
5378 Body_Id : out Entity_Id;
5379 Legal : out Boolean)
5381 Body_Decl : Node_Id;
5382 Spec_Decl : Node_Id;
5384 begin
5385 -- Assume that the pragma is illegal
5387 Spec_Id := Empty;
5388 Body_Id := Empty;
5389 Legal := False;
5391 GNAT_Pragma;
5392 Check_Arg_Count (1);
5393 Check_No_Identifiers;
5395 -- Verify the placement of the pragma and check for duplicates. The
5396 -- pragma must apply to a subprogram body [stub].
5398 Body_Decl := Find_Related_Declaration_Or_Body (N, Do_Checks => True);
5400 if Nkind (Body_Decl) not in
5401 N_Entry_Body | N_Subprogram_Body | N_Subprogram_Body_Stub |
5402 N_Task_Body | N_Task_Body_Stub
5403 then
5404 Pragma_Misplaced;
5405 end if;
5407 Body_Id := Defining_Entity (Body_Decl);
5408 Spec_Id := Unique_Defining_Entity (Body_Decl);
5410 -- The pragma must apply to the second declaration of a subprogram.
5411 -- In other words, the body [stub] cannot acts as a spec.
5413 if No (Spec_Id) then
5414 Error_Pragma ("pragma % cannot apply to a stand alone body");
5416 -- Catch the case where the subprogram body is a subunit and acts as
5417 -- the third declaration of the subprogram.
5419 elsif Nkind (Parent (Body_Decl)) = N_Subunit then
5420 Error_Pragma ("pragma % cannot apply to a subunit");
5421 end if;
5423 -- A refined pragma can only apply to the body [stub] of a subprogram
5424 -- declared in the visible part of a package. Retrieve the context of
5425 -- the subprogram declaration.
5427 Spec_Decl := Unit_Declaration_Node (Spec_Id);
5429 -- When dealing with protected entries or protected subprograms, use
5430 -- the enclosing protected type as the proper context.
5432 if Ekind (Spec_Id) in E_Entry
5433 | E_Entry_Family
5434 | E_Function
5435 | E_Procedure
5436 and then Ekind (Scope (Spec_Id)) = E_Protected_Type
5437 then
5438 Spec_Decl := Declaration_Node (Scope (Spec_Id));
5439 end if;
5441 if Nkind (Parent (Spec_Decl)) /= N_Package_Specification then
5442 Error_Pragma
5443 (Fix_Msg (Spec_Id, "pragma % must apply to the body of "
5444 & "subprogram declared in a package specification"));
5445 end if;
5447 -- If we get here, then the pragma is legal
5449 Legal := True;
5451 -- A pragma that applies to a Ghost entity becomes Ghost for the
5452 -- purposes of legality checks and removal of ignored Ghost code.
5454 Mark_Ghost_Pragma (N, Spec_Id);
5456 if Pname in Name_Refined_Depends | Name_Refined_Global then
5457 Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
5458 end if;
5459 end Analyze_Refined_Depends_Global_Post;
5461 ----------------------------------
5462 -- Analyze_Unmodified_Or_Unused --
5463 ----------------------------------
5465 procedure Analyze_Unmodified_Or_Unused (Is_Unused : Boolean := False) is
5466 Arg : Node_Id;
5467 Arg_Expr : Node_Id;
5468 Arg_Id : Entity_Id;
5470 Ghost_Error_Posted : Boolean := False;
5471 -- Flag set when an error concerning the illegal mix of Ghost and
5472 -- non-Ghost variables is emitted.
5474 Ghost_Id : Entity_Id := Empty;
5475 -- The entity of the first Ghost variable encountered while
5476 -- processing the arguments of the pragma.
5478 begin
5479 GNAT_Pragma;
5480 Check_At_Least_N_Arguments (1);
5482 -- Loop through arguments
5484 Arg := Arg1;
5485 while Present (Arg) loop
5486 Check_No_Identifier (Arg);
5488 -- Note: the analyze call done by Check_Arg_Is_Local_Name will
5489 -- in fact generate reference, so that the entity will have a
5490 -- reference, which will inhibit any warnings about it not
5491 -- being referenced, and also properly show up in the ali file
5492 -- as a reference. But this reference is recorded before the
5493 -- Has_Pragma_Unreferenced flag is set, so that no warning is
5494 -- generated for this reference.
5496 Check_Arg_Is_Local_Name (Arg);
5497 Arg_Expr := Get_Pragma_Arg (Arg);
5499 if Is_Entity_Name (Arg_Expr) then
5500 Arg_Id := Entity (Arg_Expr);
5502 -- Skip processing the argument if already flagged
5504 if Is_Assignable (Arg_Id)
5505 and then not Has_Pragma_Unmodified (Arg_Id)
5506 and then not Has_Pragma_Unused (Arg_Id)
5507 then
5508 Set_Has_Pragma_Unmodified (Arg_Id);
5510 if Is_Unused then
5511 Set_Has_Pragma_Unused (Arg_Id);
5512 end if;
5514 -- A pragma that applies to a Ghost entity becomes Ghost for
5515 -- the purposes of legality checks and removal of ignored
5516 -- Ghost code.
5518 Mark_Ghost_Pragma (N, Arg_Id);
5520 -- Capture the entity of the first Ghost variable being
5521 -- processed for error detection purposes.
5523 if Is_Ghost_Entity (Arg_Id) then
5524 if No (Ghost_Id) then
5525 Ghost_Id := Arg_Id;
5526 end if;
5528 -- Otherwise the variable is non-Ghost. It is illegal to mix
5529 -- references to Ghost and non-Ghost entities
5530 -- (SPARK RM 6.9).
5532 elsif Present (Ghost_Id)
5533 and then not Ghost_Error_Posted
5534 then
5535 Ghost_Error_Posted := True;
5537 Error_Msg_Name_1 := Pname;
5538 Error_Msg_N
5539 ("pragma % cannot mention ghost and non-ghost "
5540 & "variables", N);
5542 Error_Msg_Sloc := Sloc (Ghost_Id);
5543 Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
5545 Error_Msg_Sloc := Sloc (Arg_Id);
5546 Error_Msg_NE ("\& # declared as non-ghost", N, Arg_Id);
5547 end if;
5549 -- Warn if already flagged as Unused or Unmodified
5551 elsif Has_Pragma_Unmodified (Arg_Id) then
5552 if Has_Pragma_Unused (Arg_Id) then
5553 Error_Msg_NE
5554 (Fix_Error ("??pragma Unused already given for &!"),
5555 Arg_Expr, Arg_Id);
5556 else
5557 Error_Msg_NE
5558 (Fix_Error ("??pragma Unmodified already given for &!"),
5559 Arg_Expr, Arg_Id);
5560 end if;
5562 -- Otherwise the pragma referenced an illegal entity
5564 else
5565 Error_Pragma_Arg
5566 ("pragma% can only be applied to a variable", Arg_Expr);
5567 end if;
5568 end if;
5570 Next (Arg);
5571 end loop;
5572 end Analyze_Unmodified_Or_Unused;
5574 ------------------------------------
5575 -- Analyze_Unreferenced_Or_Unused --
5576 ------------------------------------
5578 procedure Analyze_Unreferenced_Or_Unused
5579 (Is_Unused : Boolean := False)
5581 Arg : Node_Id;
5582 Arg_Expr : Node_Id;
5583 Arg_Id : Entity_Id;
5584 Citem : Node_Id;
5586 Ghost_Error_Posted : Boolean := False;
5587 -- Flag set when an error concerning the illegal mix of Ghost and
5588 -- non-Ghost names is emitted.
5590 Ghost_Id : Entity_Id := Empty;
5591 -- The entity of the first Ghost name encountered while processing
5592 -- the arguments of the pragma.
5594 begin
5595 GNAT_Pragma;
5596 Check_At_Least_N_Arguments (1);
5598 -- Check case of appearing within context clause
5600 if not Is_Unused and then Is_In_Context_Clause then
5602 -- The arguments must all be units mentioned in a with clause in
5603 -- the same context clause. Note that Par.Prag already checked
5604 -- that the arguments are either identifiers or selected
5605 -- components.
5607 Arg := Arg1;
5608 while Present (Arg) loop
5609 Citem := First (List_Containing (N));
5610 while Citem /= N loop
5611 Arg_Expr := Get_Pragma_Arg (Arg);
5613 if Nkind (Citem) = N_With_Clause
5614 and then Same_Name (Name (Citem), Arg_Expr)
5615 then
5616 Set_Has_Pragma_Unreferenced
5617 (Cunit_Entity
5618 (Get_Source_Unit
5619 (Library_Unit (Citem))));
5620 Set_Elab_Unit_Name (Arg_Expr, Name (Citem));
5621 exit;
5622 end if;
5624 Next (Citem);
5625 end loop;
5627 if Citem = N then
5628 Error_Pragma_Arg
5629 ("argument of pragma% is not withed unit", Arg);
5630 end if;
5632 Next (Arg);
5633 end loop;
5635 -- Case of not in list of context items
5637 else
5638 Arg := Arg1;
5639 while Present (Arg) loop
5640 Check_No_Identifier (Arg);
5642 -- Note: the analyze call done by Check_Arg_Is_Local_Name will
5643 -- in fact generate reference, so that the entity will have a
5644 -- reference, which will inhibit any warnings about it not
5645 -- being referenced, and also properly show up in the ali file
5646 -- as a reference. But this reference is recorded before the
5647 -- Has_Pragma_Unreferenced flag is set, so that no warning is
5648 -- generated for this reference.
5650 Check_Arg_Is_Local_Name (Arg);
5651 Arg_Expr := Get_Pragma_Arg (Arg);
5653 if Is_Entity_Name (Arg_Expr) then
5654 Arg_Id := Entity (Arg_Expr);
5656 -- Warn if already flagged as Unused or Unreferenced and
5657 -- skip processing the argument.
5659 if Has_Pragma_Unreferenced (Arg_Id) then
5660 if Has_Pragma_Unused (Arg_Id) then
5661 Error_Msg_NE
5662 (Fix_Error ("??pragma Unused already given for &!"),
5663 Arg_Expr, Arg_Id);
5664 else
5665 Error_Msg_NE
5666 (Fix_Error
5667 ("??pragma Unreferenced already given for &!"),
5668 Arg_Expr, Arg_Id);
5669 end if;
5671 -- Apply Unreferenced to the entity
5673 else
5674 -- If the entity is overloaded, the pragma applies to the
5675 -- most recent overloading, as documented. In this case,
5676 -- name resolution does not generate a reference, so it
5677 -- must be done here explicitly.
5679 if Is_Overloaded (Arg_Expr) then
5680 Generate_Reference (Arg_Id, N);
5681 end if;
5683 Set_Has_Pragma_Unreferenced (Arg_Id);
5685 if Is_Unused then
5686 Set_Has_Pragma_Unused (Arg_Id);
5687 end if;
5689 -- A pragma that applies to a Ghost entity becomes Ghost
5690 -- for the purposes of legality checks and removal of
5691 -- ignored Ghost code.
5693 Mark_Ghost_Pragma (N, Arg_Id);
5695 -- Capture the entity of the first Ghost name being
5696 -- processed for error detection purposes.
5698 if Is_Ghost_Entity (Arg_Id) then
5699 if No (Ghost_Id) then
5700 Ghost_Id := Arg_Id;
5701 end if;
5703 -- Otherwise the name is non-Ghost. It is illegal to mix
5704 -- references to Ghost and non-Ghost entities
5705 -- (SPARK RM 6.9).
5707 elsif Present (Ghost_Id)
5708 and then not Ghost_Error_Posted
5709 then
5710 Ghost_Error_Posted := True;
5712 Error_Msg_Name_1 := Pname;
5713 Error_Msg_N
5714 ("pragma % cannot mention ghost and non-ghost "
5715 & "names", N);
5717 Error_Msg_Sloc := Sloc (Ghost_Id);
5718 Error_Msg_NE
5719 ("\& # declared as ghost", N, Ghost_Id);
5721 Error_Msg_Sloc := Sloc (Arg_Id);
5722 Error_Msg_NE
5723 ("\& # declared as non-ghost", N, Arg_Id);
5724 end if;
5725 end if;
5726 end if;
5728 Next (Arg);
5729 end loop;
5730 end if;
5731 end Analyze_Unreferenced_Or_Unused;
5733 --------------------------
5734 -- Check_Ada_83_Warning --
5735 --------------------------
5737 procedure Check_Ada_83_Warning is
5738 begin
5739 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
5740 Error_Msg_N ("(Ada 83) pragma& is non-standard??", N);
5741 end if;
5742 end Check_Ada_83_Warning;
5744 ---------------------
5745 -- Check_Arg_Count --
5746 ---------------------
5748 procedure Check_Arg_Count (Required : Nat) is
5749 begin
5750 if Arg_Count /= Required then
5751 Error_Pragma ("wrong number of arguments for pragma%");
5752 end if;
5753 end Check_Arg_Count;
5755 --------------------------------
5756 -- Check_Arg_Is_External_Name --
5757 --------------------------------
5759 procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
5760 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5762 begin
5763 if Nkind (Argx) = N_Identifier then
5764 return;
5766 else
5767 Analyze_And_Resolve (Argx, Standard_String);
5769 if Is_OK_Static_Expression (Argx) then
5770 return;
5772 elsif Etype (Argx) = Any_Type then
5773 raise Pragma_Exit;
5775 -- An interesting special case, if we have a string literal and
5776 -- we are in Ada 83 mode, then we allow it even though it will
5777 -- not be flagged as static. This allows expected Ada 83 mode
5778 -- use of external names which are string literals, even though
5779 -- technically these are not static in Ada 83.
5781 elsif Ada_Version = Ada_83
5782 and then Nkind (Argx) = N_String_Literal
5783 then
5784 return;
5786 -- Here we have a real error (non-static expression)
5788 else
5789 Error_Msg_Name_1 := Pname;
5790 Flag_Non_Static_Expr
5791 (Fix_Error ("argument for pragma% must be a identifier or "
5792 & "static string expression!"), Argx);
5794 raise Pragma_Exit;
5795 end if;
5796 end if;
5797 end Check_Arg_Is_External_Name;
5799 -----------------------------
5800 -- Check_Arg_Is_Identifier --
5801 -----------------------------
5803 procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
5804 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5805 begin
5806 if Nkind (Argx) /= N_Identifier then
5807 Error_Pragma_Arg ("argument for pragma% must be identifier", Argx);
5808 end if;
5809 end Check_Arg_Is_Identifier;
5811 ----------------------------------
5812 -- Check_Arg_Is_Integer_Literal --
5813 ----------------------------------
5815 procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
5816 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5817 begin
5818 if Nkind (Argx) /= N_Integer_Literal then
5819 Error_Pragma_Arg
5820 ("argument for pragma% must be integer literal", Argx);
5821 end if;
5822 end Check_Arg_Is_Integer_Literal;
5824 -------------------------------------------
5825 -- Check_Arg_Is_Library_Level_Local_Name --
5826 -------------------------------------------
5828 -- LOCAL_NAME ::=
5829 -- DIRECT_NAME
5830 -- | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
5831 -- | library_unit_NAME
5833 procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
5834 begin
5835 Check_Arg_Is_Local_Name (Arg);
5837 -- If it came from an aspect, we want to give the error just as if it
5838 -- came from source.
5840 if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
5841 and then (Comes_From_Source (N)
5842 or else Present (Corresponding_Aspect (Parent (Arg))))
5843 then
5844 Error_Pragma_Arg
5845 ("argument for pragma% must be library level entity", Arg);
5846 end if;
5847 end Check_Arg_Is_Library_Level_Local_Name;
5849 -----------------------------
5850 -- Check_Arg_Is_Local_Name --
5851 -----------------------------
5853 -- LOCAL_NAME ::=
5854 -- DIRECT_NAME
5855 -- | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
5856 -- | library_unit_NAME
5858 procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
5859 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5861 begin
5862 -- If this pragma came from an aspect specification, we don't want to
5863 -- check for this error, because that would cause spurious errors, in
5864 -- case a type is frozen in a scope more nested than the type. The
5865 -- aspect itself of course can't be anywhere but on the declaration
5866 -- itself.
5868 if Nkind (Arg) = N_Pragma_Argument_Association then
5869 if From_Aspect_Specification (Parent (Arg)) then
5870 return;
5871 end if;
5873 -- Arg is the Expression of an N_Pragma_Argument_Association
5875 else
5876 if From_Aspect_Specification (Parent (Parent (Arg))) then
5877 return;
5878 end if;
5879 end if;
5881 Analyze (Argx);
5883 if Nkind (Argx) not in N_Direct_Name
5884 and then (Nkind (Argx) /= N_Attribute_Reference
5885 or else Present (Expressions (Argx))
5886 or else Nkind (Prefix (Argx)) /= N_Identifier)
5887 and then (not Is_Entity_Name (Argx)
5888 or else not Is_Compilation_Unit (Entity (Argx)))
5889 then
5890 Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
5891 end if;
5893 -- No further check required if not an entity name
5895 if not Is_Entity_Name (Argx) then
5896 null;
5898 else
5899 declare
5900 OK : Boolean;
5901 Ent : constant Entity_Id := Entity (Argx);
5902 Scop : constant Entity_Id := Scope (Ent);
5904 begin
5905 -- Case of a pragma applied to a compilation unit: pragma must
5906 -- occur immediately after the program unit in the compilation.
5908 if Is_Compilation_Unit (Ent) then
5909 declare
5910 Decl : constant Node_Id := Unit_Declaration_Node (Ent);
5912 begin
5913 -- Case of pragma placed immediately after spec
5915 if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
5916 OK := True;
5918 -- Case of pragma placed immediately after body
5920 elsif Nkind (Decl) = N_Subprogram_Declaration
5921 and then Present (Corresponding_Body (Decl))
5922 then
5923 OK := Parent (N) =
5924 Aux_Decls_Node
5925 (Parent (Unit_Declaration_Node
5926 (Corresponding_Body (Decl))));
5928 -- All other cases are illegal
5930 else
5931 OK := False;
5932 end if;
5933 end;
5935 -- Special restricted placement rule from 10.2.1(11.8/2)
5937 elsif Is_Generic_Formal (Ent)
5938 and then Prag_Id = Pragma_Preelaborable_Initialization
5939 then
5940 OK := List_Containing (N) =
5941 Generic_Formal_Declarations
5942 (Unit_Declaration_Node (Scop));
5944 -- If this is an aspect applied to a subprogram body, the
5945 -- pragma is inserted in its declarative part.
5947 elsif From_Aspect_Specification (N)
5948 and then Ent = Current_Scope
5949 and then
5950 Nkind (Unit_Declaration_Node (Ent)) = N_Subprogram_Body
5951 then
5952 OK := True;
5954 -- If the aspect is a predicate (possibly others ???) and the
5955 -- context is a record type, this is a discriminant expression
5956 -- within a type declaration, that freezes the predicated
5957 -- subtype.
5959 elsif From_Aspect_Specification (N)
5960 and then Prag_Id = Pragma_Predicate
5961 and then Ekind (Current_Scope) = E_Record_Type
5962 and then Scop = Scope (Current_Scope)
5963 then
5964 OK := True;
5966 -- Special case for postconditions wrappers
5968 elsif Ekind (Scop) in Subprogram_Kind
5969 and then Present (Wrapped_Statements (Scop))
5970 and then Wrapped_Statements (Scop) = Current_Scope
5971 then
5972 OK := True;
5974 -- Default case, just check that the pragma occurs in the scope
5975 -- of the entity denoted by the name.
5977 else
5978 OK := Current_Scope = Scop;
5979 end if;
5981 if not OK then
5982 Error_Pragma_Arg
5983 ("pragma% argument must be in same declarative part", Arg);
5984 end if;
5985 end;
5986 end if;
5987 end Check_Arg_Is_Local_Name;
5989 ---------------------------------
5990 -- Check_Arg_Is_Locking_Policy --
5991 ---------------------------------
5993 procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
5994 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5996 begin
5997 Check_Arg_Is_Identifier (Argx);
5999 if not Is_Locking_Policy_Name (Chars (Argx)) then
6000 Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
6001 end if;
6002 end Check_Arg_Is_Locking_Policy;
6004 -----------------------------------------------
6005 -- Check_Arg_Is_Partition_Elaboration_Policy --
6006 -----------------------------------------------
6008 procedure Check_Arg_Is_Partition_Elaboration_Policy (Arg : Node_Id) is
6009 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6011 begin
6012 Check_Arg_Is_Identifier (Argx);
6014 if not Is_Partition_Elaboration_Policy_Name (Chars (Argx)) then
6015 Error_Pragma_Arg
6016 ("& is not a valid partition elaboration policy name", Argx);
6017 end if;
6018 end Check_Arg_Is_Partition_Elaboration_Policy;
6020 -------------------------
6021 -- Check_Arg_Is_One_Of --
6022 -------------------------
6024 procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
6025 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6027 begin
6028 Check_Arg_Is_Identifier (Argx);
6030 if Chars (Argx) not in N1 | N2 then
6031 Error_Msg_Name_2 := N1;
6032 Error_Msg_Name_3 := N2;
6033 Error_Pragma_Arg ("argument for pragma% must be% or%", Argx);
6034 end if;
6035 end Check_Arg_Is_One_Of;
6037 procedure Check_Arg_Is_One_Of
6038 (Arg : Node_Id;
6039 N1, N2, N3 : Name_Id)
6041 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6043 begin
6044 Check_Arg_Is_Identifier (Argx);
6046 if Chars (Argx) not in N1 | N2 | N3 then
6047 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
6048 end if;
6049 end Check_Arg_Is_One_Of;
6051 procedure Check_Arg_Is_One_Of
6052 (Arg : Node_Id;
6053 N1, N2, N3, N4 : Name_Id)
6055 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6057 begin
6058 Check_Arg_Is_Identifier (Argx);
6060 if Chars (Argx) not in N1 | N2 | N3 | N4 then
6061 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
6062 end if;
6063 end Check_Arg_Is_One_Of;
6065 procedure Check_Arg_Is_One_Of
6066 (Arg : Node_Id;
6067 N1, N2, N3, N4, N5 : Name_Id)
6069 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6071 begin
6072 Check_Arg_Is_Identifier (Argx);
6074 if Chars (Argx) not in N1 | N2 | N3 | N4 | N5 then
6075 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
6076 end if;
6077 end Check_Arg_Is_One_Of;
6079 ---------------------------------
6080 -- Check_Arg_Is_Queuing_Policy --
6081 ---------------------------------
6083 procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
6084 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6086 begin
6087 Check_Arg_Is_Identifier (Argx);
6089 if not Is_Queuing_Policy_Name (Chars (Argx)) then
6090 Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
6091 end if;
6092 end Check_Arg_Is_Queuing_Policy;
6094 ---------------------------------------
6095 -- Check_Arg_Is_OK_Static_Expression --
6096 ---------------------------------------
6098 procedure Check_Arg_Is_OK_Static_Expression
6099 (Arg : Node_Id;
6100 Typ : Entity_Id := Empty)
6102 begin
6103 Check_Expr_Is_OK_Static_Expression (Get_Pragma_Arg (Arg), Typ);
6104 end Check_Arg_Is_OK_Static_Expression;
6106 ------------------------------------------
6107 -- Check_Arg_Is_Task_Dispatching_Policy --
6108 ------------------------------------------
6110 procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
6111 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6113 begin
6114 Check_Arg_Is_Identifier (Argx);
6116 if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
6117 Error_Pragma_Arg
6118 ("& is not an allowed task dispatching policy name", Argx);
6119 end if;
6120 end Check_Arg_Is_Task_Dispatching_Policy;
6122 ---------------------
6123 -- Check_Arg_Order --
6124 ---------------------
6126 procedure Check_Arg_Order (Names : Name_List) is
6127 Arg : Node_Id;
6129 Highest_So_Far : Natural := 0;
6130 -- Highest index in Names seen do far
6132 begin
6133 Arg := Arg1;
6134 for J in 1 .. Arg_Count loop
6135 if Chars (Arg) /= No_Name then
6136 for K in Names'Range loop
6137 if Chars (Arg) = Names (K) then
6138 if K < Highest_So_Far then
6139 Error_Msg_Name_1 := Pname;
6140 Error_Msg_N
6141 ("parameters out of order for pragma%", Arg);
6142 Error_Msg_Name_1 := Names (K);
6143 Error_Msg_Name_2 := Names (Highest_So_Far);
6144 Error_Msg_N ("\% must appear before %", Arg);
6145 raise Pragma_Exit;
6147 else
6148 Highest_So_Far := K;
6149 end if;
6150 end if;
6151 end loop;
6152 end if;
6154 Arg := Next (Arg);
6155 end loop;
6156 end Check_Arg_Order;
6158 --------------------------------
6159 -- Check_At_Least_N_Arguments --
6160 --------------------------------
6162 procedure Check_At_Least_N_Arguments (N : Nat) is
6163 begin
6164 if Arg_Count < N then
6165 Error_Pragma ("too few arguments for pragma%");
6166 end if;
6167 end Check_At_Least_N_Arguments;
6169 -------------------------------
6170 -- Check_At_Most_N_Arguments --
6171 -------------------------------
6173 procedure Check_At_Most_N_Arguments (N : Nat) is
6174 Arg : Node_Id;
6175 begin
6176 if Arg_Count > N then
6177 Arg := Arg1;
6178 for J in 1 .. N loop
6179 Next (Arg);
6180 Error_Pragma_Arg ("too many arguments for pragma%", Arg);
6181 end loop;
6182 end if;
6183 end Check_At_Most_N_Arguments;
6185 ---------------------
6186 -- Check_Component --
6187 ---------------------
6189 procedure Check_Component
6190 (Comp : Node_Id;
6191 UU_Typ : Entity_Id;
6192 In_Variant_Part : Boolean := False)
6194 Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
6195 Sindic : constant Node_Id :=
6196 Subtype_Indication (Component_Definition (Comp));
6197 Typ : constant Entity_Id := Etype (Comp_Id);
6199 begin
6200 -- Ada 2005 (AI-216): If a component subtype is subject to a per-
6201 -- object constraint, then the component type shall be an Unchecked_
6202 -- Union.
6204 if Nkind (Sindic) = N_Subtype_Indication
6205 and then Has_Per_Object_Constraint (Comp_Id)
6206 and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
6207 then
6208 Error_Msg_N
6209 ("component subtype subject to per-object constraint "
6210 & "must be an Unchecked_Union", Comp);
6212 -- Ada 2012 (AI05-0026): For an unchecked union type declared within
6213 -- the body of a generic unit, or within the body of any of its
6214 -- descendant library units, no part of the type of a component
6215 -- declared in a variant_part of the unchecked union type shall be of
6216 -- a formal private type or formal private extension declared within
6217 -- the formal part of the generic unit.
6219 elsif Ada_Version >= Ada_2012
6220 and then In_Generic_Body (UU_Typ)
6221 and then In_Variant_Part
6222 and then Is_Private_Type (Typ)
6223 and then Is_Generic_Type (Typ)
6224 then
6225 Error_Msg_N
6226 ("component of unchecked union cannot be of generic type", Comp);
6228 elsif Needs_Finalization (Typ) then
6229 Error_Msg_N
6230 ("component of unchecked union cannot be controlled", Comp);
6232 elsif Has_Task (Typ) then
6233 Error_Msg_N
6234 ("component of unchecked union cannot have tasks", Comp);
6235 end if;
6236 end Check_Component;
6238 ----------------------------
6239 -- Check_Duplicate_Pragma --
6240 ----------------------------
6242 procedure Check_Duplicate_Pragma (E : Entity_Id) is
6243 Id : Entity_Id := E;
6244 P : Node_Id;
6246 begin
6247 -- Nothing to do if this pragma comes from an aspect specification,
6248 -- since we could not be duplicating a pragma, and we dealt with the
6249 -- case of duplicated aspects in Analyze_Aspect_Specifications.
6251 if From_Aspect_Specification (N) then
6252 return;
6253 end if;
6255 -- Otherwise current pragma may duplicate previous pragma or a
6256 -- previously given aspect specification or attribute definition
6257 -- clause for the same pragma.
6259 P := Get_Rep_Item (E, Pragma_Name (N), Check_Parents => False);
6261 if Present (P) then
6263 -- If the entity is a type, then we have to make sure that the
6264 -- ostensible duplicate is not for a parent type from which this
6265 -- type is derived.
6267 if Is_Type (E) then
6268 if Nkind (P) = N_Pragma then
6269 declare
6270 Args : constant List_Id :=
6271 Pragma_Argument_Associations (P);
6272 begin
6273 if Present (Args)
6274 and then Is_Entity_Name (Expression (First (Args)))
6275 and then Is_Type (Entity (Expression (First (Args))))
6276 and then Entity (Expression (First (Args))) /= E
6277 then
6278 return;
6279 end if;
6280 end;
6282 elsif Nkind (P) = N_Aspect_Specification
6283 and then Is_Type (Entity (P))
6284 and then Entity (P) /= E
6285 then
6286 return;
6287 end if;
6288 end if;
6290 -- Here we have a definite duplicate
6292 Error_Msg_Name_1 := Pragma_Name (N);
6293 Error_Msg_Sloc := Sloc (P);
6295 -- For a single protected or a single task object, the error is
6296 -- issued on the original entity.
6298 if Ekind (Id) in E_Task_Type | E_Protected_Type then
6299 Id := Defining_Identifier (Original_Node (Parent (Id)));
6300 end if;
6302 if Nkind (P) = N_Aspect_Specification
6303 or else From_Aspect_Specification (P)
6304 then
6305 Error_Msg_NE ("aspect% for & previously given#", N, Id);
6306 else
6307 -- If -gnatwr is set, warn in case of a duplicate pragma
6308 -- [No_]Inline which is suspicious but not an error, generate
6309 -- an error for other pragmas.
6311 if Pragma_Name (N) in Name_Inline | Name_No_Inline then
6312 if Warn_On_Redundant_Constructs then
6313 Error_Msg_NE
6314 ("?r?pragma% for & duplicates pragma#", N, Id);
6315 end if;
6316 else
6317 Error_Msg_NE ("pragma% for & duplicates pragma#", N, Id);
6318 end if;
6319 end if;
6321 raise Pragma_Exit;
6322 end if;
6323 end Check_Duplicate_Pragma;
6325 ----------------------------------
6326 -- Check_Duplicated_Export_Name --
6327 ----------------------------------
6329 procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
6330 String_Val : constant String_Id := Strval (Nam);
6332 begin
6333 -- We are only interested in the export case, and in the case of
6334 -- generics, it is the instance, not the template, that is the
6335 -- problem (the template will generate a warning in any case).
6337 if not Inside_A_Generic
6338 and then (Prag_Id = Pragma_Export
6339 or else
6340 Prag_Id = Pragma_Export_Procedure
6341 or else
6342 Prag_Id = Pragma_Export_Valued_Procedure
6343 or else
6344 Prag_Id = Pragma_Export_Function)
6345 then
6346 for J in Externals.First .. Externals.Last loop
6347 if String_Equal (String_Val, Strval (Externals.Table (J))) then
6348 Error_Msg_Sloc := Sloc (Externals.Table (J));
6349 Error_Msg_N ("external name duplicates name given#", Nam);
6350 exit;
6351 end if;
6352 end loop;
6354 Externals.Append (Nam);
6355 end if;
6356 end Check_Duplicated_Export_Name;
6358 ----------------------------------------
6359 -- Check_Expr_Is_OK_Static_Expression --
6360 ----------------------------------------
6362 procedure Check_Expr_Is_OK_Static_Expression
6363 (Expr : Node_Id;
6364 Typ : Entity_Id := Empty)
6366 begin
6367 if Present (Typ) then
6368 Analyze_And_Resolve (Expr, Typ);
6369 else
6370 Analyze_And_Resolve (Expr);
6371 end if;
6373 -- An expression cannot be considered static if its resolution failed
6374 -- or if it's erroneous. Stop the analysis of the related pragma.
6376 if Etype (Expr) = Any_Type or else Error_Posted (Expr) then
6377 raise Pragma_Exit;
6379 elsif Is_OK_Static_Expression (Expr) then
6380 return;
6382 -- An interesting special case, if we have a string literal and we
6383 -- are in Ada 83 mode, then we allow it even though it will not be
6384 -- flagged as static. This allows the use of Ada 95 pragmas like
6385 -- Import in Ada 83 mode. They will of course be flagged with
6386 -- warnings as usual, but will not cause errors.
6388 elsif Ada_Version = Ada_83
6389 and then Nkind (Expr) = N_String_Literal
6390 then
6391 return;
6393 -- Finally, we have a real error
6395 else
6396 Error_Msg_Name_1 := Pname;
6397 Flag_Non_Static_Expr
6398 (Fix_Error ("argument for pragma% must be a static expression!"),
6399 Expr);
6400 raise Pragma_Exit;
6401 end if;
6402 end Check_Expr_Is_OK_Static_Expression;
6404 -------------------------
6405 -- Check_First_Subtype --
6406 -------------------------
6408 procedure Check_First_Subtype (Arg : Node_Id) is
6409 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6410 Ent : constant Entity_Id := Entity (Argx);
6412 begin
6413 if Is_First_Subtype (Ent) then
6414 null;
6416 elsif Is_Type (Ent) then
6417 Error_Pragma_Arg
6418 ("pragma% cannot apply to subtype", Argx);
6420 elsif Is_Object (Ent) then
6421 Error_Pragma_Arg
6422 ("pragma% cannot apply to object, requires a type", Argx);
6424 else
6425 Error_Pragma_Arg
6426 ("pragma% cannot apply to&, requires a type", Argx);
6427 end if;
6428 end Check_First_Subtype;
6430 ----------------------
6431 -- Check_Identifier --
6432 ----------------------
6434 procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
6435 begin
6436 if Present (Arg)
6437 and then Nkind (Arg) = N_Pragma_Argument_Association
6438 then
6439 if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
6440 Error_Msg_Name_1 := Pname;
6441 Error_Msg_Name_2 := Id;
6442 Error_Msg_N ("pragma% argument expects identifier%", Arg);
6443 raise Pragma_Exit;
6444 end if;
6445 end if;
6446 end Check_Identifier;
6448 --------------------------------
6449 -- Check_Identifier_Is_One_Of --
6450 --------------------------------
6452 procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
6453 begin
6454 if Present (Arg)
6455 and then Nkind (Arg) = N_Pragma_Argument_Association
6456 then
6457 if Chars (Arg) = No_Name then
6458 Error_Msg_Name_1 := Pname;
6459 Error_Msg_N ("pragma% argument expects an identifier", Arg);
6460 raise Pragma_Exit;
6462 elsif Chars (Arg) /= N1
6463 and then Chars (Arg) /= N2
6464 then
6465 Error_Msg_Name_1 := Pname;
6466 Error_Msg_N ("invalid identifier for pragma% argument", Arg);
6467 raise Pragma_Exit;
6468 end if;
6469 end if;
6470 end Check_Identifier_Is_One_Of;
6472 ---------------------------
6473 -- Check_In_Main_Program --
6474 ---------------------------
6476 procedure Check_In_Main_Program is
6477 P : constant Node_Id := Parent (N);
6479 begin
6480 -- Must be in subprogram body
6482 if Nkind (P) /= N_Subprogram_Body then
6483 Error_Pragma ("% pragma allowed only in subprogram");
6485 -- Otherwise warn if obviously not main program
6487 elsif Present (Parameter_Specifications (Specification (P)))
6488 or else not Is_Compilation_Unit (Defining_Entity (P))
6489 then
6490 Error_Msg_Name_1 := Pname;
6491 Error_Msg_N
6492 ("??pragma% is only effective in main program", N);
6493 end if;
6494 end Check_In_Main_Program;
6496 ---------------------------------------
6497 -- Check_Interrupt_Or_Attach_Handler --
6498 ---------------------------------------
6500 procedure Check_Interrupt_Or_Attach_Handler is
6501 Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
6502 Handler_Proc, Proc_Scope : Entity_Id;
6504 begin
6505 Analyze (Arg1_X);
6507 if Prag_Id = Pragma_Interrupt_Handler then
6508 Check_Restriction (No_Dynamic_Attachment, N);
6509 end if;
6511 Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
6512 Proc_Scope := Scope (Handler_Proc);
6514 if Ekind (Proc_Scope) /= E_Protected_Type then
6515 Error_Pragma_Arg
6516 ("argument of pragma% must be protected procedure", Arg1);
6517 end if;
6519 -- For pragma case (as opposed to access case), check placement.
6520 -- We don't need to do that for aspects, because we have the
6521 -- check that they aspect applies an appropriate procedure.
6523 if not From_Aspect_Specification (N)
6524 and then Parent (N) /= Protected_Definition (Parent (Proc_Scope))
6525 then
6526 Error_Pragma ("pragma% must be in protected definition");
6527 end if;
6529 if not Is_Library_Level_Entity (Proc_Scope) then
6530 Error_Pragma_Arg
6531 ("argument for pragma% must be library level entity", Arg1);
6532 end if;
6534 -- AI05-0033: A pragma cannot appear within a generic body, because
6535 -- instance can be in a nested scope. The check that protected type
6536 -- is itself a library-level declaration is done elsewhere.
6538 -- Note: we omit this check in Relaxed_RM_Semantics mode to properly
6539 -- handle code prior to AI-0033. Analysis tools typically are not
6540 -- interested in this pragma in any case, so no need to worry too
6541 -- much about its placement.
6543 if Inside_A_Generic then
6544 if Ekind (Scope (Current_Scope)) = E_Generic_Package
6545 and then In_Package_Body (Scope (Current_Scope))
6546 and then not Relaxed_RM_Semantics
6547 then
6548 Error_Pragma ("pragma% cannot be used inside a generic");
6549 end if;
6550 end if;
6551 end Check_Interrupt_Or_Attach_Handler;
6553 ---------------------------------
6554 -- Check_Loop_Pragma_Placement --
6555 ---------------------------------
6557 procedure Check_Loop_Pragma_Placement is
6558 procedure Check_Loop_Pragma_Grouping (Loop_Stmt : Node_Id);
6559 -- Verify whether the current pragma is properly grouped with other
6560 -- pragma Loop_Invariant and/or Loop_Variant. Node Loop_Stmt is the
6561 -- related loop where the pragma appears.
6563 function Is_Loop_Pragma (Stmt : Node_Id) return Boolean;
6564 -- Determine whether an arbitrary statement Stmt denotes pragma
6565 -- Loop_Invariant or Loop_Variant.
6567 procedure Placement_Error (Constr : Node_Id);
6568 pragma No_Return (Placement_Error);
6569 -- Node Constr denotes the last loop restricted construct before we
6570 -- encountered an illegal relation between enclosing constructs. Emit
6571 -- an error depending on what Constr was.
6573 --------------------------------
6574 -- Check_Loop_Pragma_Grouping --
6575 --------------------------------
6577 procedure Check_Loop_Pragma_Grouping (Loop_Stmt : Node_Id) is
6578 function Check_Grouping (L : List_Id) return Boolean;
6579 -- Find the first group of pragmas in list L and if successful,
6580 -- ensure that the current pragma is part of that group. The
6581 -- routine returns True once such a check is performed to
6582 -- stop the analysis.
6584 procedure Grouping_Error (Prag : Node_Id);
6585 pragma No_Return (Grouping_Error);
6586 -- Emit an error concerning the current pragma indicating that it
6587 -- should be placed after pragma Prag.
6589 --------------------
6590 -- Check_Grouping --
6591 --------------------
6593 function Check_Grouping (L : List_Id) return Boolean is
6594 HSS : Node_Id;
6595 Stmt : Node_Id;
6596 Prag : Node_Id := Empty; -- init to avoid warning
6598 begin
6599 -- Inspect the list of declarations or statements looking for
6600 -- the first grouping of pragmas:
6602 -- loop
6603 -- pragma Loop_Invariant ...;
6604 -- pragma Loop_Variant ...;
6605 -- . . . -- (1)
6606 -- pragma Loop_Variant ...; -- current pragma
6608 -- If the current pragma is not in the grouping, then it must
6609 -- either appear in a different declarative or statement list
6610 -- or the construct at (1) is separating the pragma from the
6611 -- grouping.
6613 Stmt := First (L);
6614 while Present (Stmt) loop
6616 -- First pragma of the first topmost grouping has been found
6618 if Is_Loop_Pragma (Stmt) then
6620 -- The group and the current pragma are not in the same
6621 -- declarative or statement list.
6623 if not In_Same_List (Stmt, N) then
6624 Grouping_Error (Stmt);
6626 -- Try to reach the current pragma from the first pragma
6627 -- of the grouping while skipping other members:
6629 -- pragma Loop_Invariant ...; -- first pragma
6630 -- pragma Loop_Variant ...; -- member
6631 -- . . .
6632 -- pragma Loop_Variant ...; -- current pragma
6634 else
6635 while Present (Stmt) loop
6636 -- The current pragma is either the first pragma
6637 -- of the group or is a member of the group.
6638 -- Stop the search as the placement is legal.
6640 if Stmt = N then
6641 return True;
6643 -- Skip group members, but keep track of the
6644 -- last pragma in the group.
6646 elsif Is_Loop_Pragma (Stmt) then
6647 Prag := Stmt;
6649 -- Skip Annotate pragmas, typically used to justify
6650 -- unproved loop pragmas in GNATprove.
6652 elsif Nkind (Stmt) = N_Pragma
6653 and then Pragma_Name (Stmt) = Name_Annotate
6654 then
6655 null;
6657 -- Skip declarations and statements generated by
6658 -- the compiler during expansion. Note that some
6659 -- source statements (e.g. pragma Assert) may have
6660 -- been transformed so that they do not appear as
6661 -- coming from source anymore, so we instead look
6662 -- at their Original_Node.
6664 elsif not Comes_From_Source (Original_Node (Stmt))
6665 then
6666 null;
6668 -- A non-pragma is separating the group from the
6669 -- current pragma, the placement is illegal.
6671 else
6672 Grouping_Error (Prag);
6673 end if;
6675 Next (Stmt);
6676 end loop;
6678 -- If the traversal did not reach the current pragma,
6679 -- then the list must be malformed.
6681 raise Program_Error;
6682 end if;
6684 -- Pragmas Loop_Invariant and Loop_Variant may only appear
6685 -- inside a loop or a block housed inside a loop. Inspect
6686 -- the declarations and statements of the block as they may
6687 -- contain the first grouping. This case follows the one for
6688 -- loop pragmas, as block statements which originate in a
6689 -- loop pragma (and so Is_Loop_Pragma will return True on
6690 -- that block statement) should be treated in the previous
6691 -- case.
6693 elsif Nkind (Stmt) = N_Block_Statement then
6694 HSS := Handled_Statement_Sequence (Stmt);
6696 if Check_Grouping (Declarations (Stmt)) then
6697 return True;
6698 end if;
6700 if Present (HSS) then
6701 if Check_Grouping (Statements (HSS)) then
6702 return True;
6703 end if;
6704 end if;
6705 end if;
6707 Next (Stmt);
6708 end loop;
6710 return False;
6711 end Check_Grouping;
6713 --------------------
6714 -- Grouping_Error --
6715 --------------------
6717 procedure Grouping_Error (Prag : Node_Id) is
6718 begin
6719 Error_Msg_Sloc := Sloc (Prag);
6720 Error_Pragma ("pragma% must appear next to pragma#");
6721 end Grouping_Error;
6723 Ignore : Boolean;
6725 -- Start of processing for Check_Loop_Pragma_Grouping
6727 begin
6728 -- Inspect the statements of the loop or nested blocks housed
6729 -- within to determine whether the current pragma is part of the
6730 -- first topmost grouping of Loop_Invariant and Loop_Variant.
6732 Ignore := Check_Grouping (Statements (Loop_Stmt));
6733 end Check_Loop_Pragma_Grouping;
6735 --------------------
6736 -- Is_Loop_Pragma --
6737 --------------------
6739 function Is_Loop_Pragma (Stmt : Node_Id) return Boolean is
6740 Original_Stmt : constant Node_Id := Original_Node (Stmt);
6742 begin
6743 -- Inspect the original node as Loop_Invariant and Loop_Variant
6744 -- pragmas are rewritten to null when assertions are disabled.
6746 return Nkind (Original_Stmt) = N_Pragma
6747 and then Pragma_Name_Unmapped (Original_Stmt)
6748 in Name_Loop_Invariant | Name_Loop_Variant;
6749 end Is_Loop_Pragma;
6751 ---------------------
6752 -- Placement_Error --
6753 ---------------------
6755 procedure Placement_Error (Constr : Node_Id) is
6756 LA : constant String := " with Loop_Entry";
6758 begin
6759 if Prag_Id = Pragma_Assert then
6760 Error_Msg_String (1 .. LA'Length) := LA;
6761 Error_Msg_Strlen := LA'Length;
6762 else
6763 Error_Msg_Strlen := 0;
6764 end if;
6766 if Nkind (Constr) = N_Pragma then
6767 Error_Pragma
6768 ("pragma %~ must appear immediately within the statements "
6769 & "of a loop");
6770 else
6771 Error_Pragma_Arg
6772 ("block containing pragma %~ must appear immediately within "
6773 & "the statements of a loop", Constr);
6774 end if;
6775 end Placement_Error;
6777 -- Local declarations
6779 Prev : Node_Id;
6780 Stmt : Node_Id;
6782 -- Start of processing for Check_Loop_Pragma_Placement
6784 begin
6785 -- Check that pragma appears immediately within a loop statement,
6786 -- ignoring intervening block statements.
6788 Prev := N;
6789 Stmt := Parent (N);
6790 while Present (Stmt) loop
6792 -- The pragma or previous block must appear immediately within the
6793 -- current block's declarative or statement part.
6795 if Nkind (Stmt) = N_Block_Statement then
6796 if (No (Declarations (Stmt))
6797 or else List_Containing (Prev) /= Declarations (Stmt))
6798 and then
6799 List_Containing (Prev) /=
6800 Statements (Handled_Statement_Sequence (Stmt))
6801 then
6802 Placement_Error (Prev);
6804 -- Keep inspecting the parents because we are now within a
6805 -- chain of nested blocks.
6807 else
6808 Prev := Stmt;
6809 Stmt := Parent (Stmt);
6810 end if;
6812 -- The pragma or previous block must appear immediately within the
6813 -- statements of the loop.
6815 elsif Nkind (Stmt) = N_Loop_Statement then
6816 if List_Containing (Prev) /= Statements (Stmt) then
6817 Placement_Error (Prev);
6818 end if;
6820 -- Stop the traversal because we reached the innermost loop
6821 -- regardless of whether we encountered an error or not.
6823 exit;
6825 -- Ignore a handled statement sequence. Note that this node may
6826 -- be related to a subprogram body in which case we will emit an
6827 -- error on the next iteration of the search.
6829 elsif Nkind (Stmt) = N_Handled_Sequence_Of_Statements then
6830 Stmt := Parent (Stmt);
6832 -- Any other statement breaks the chain from the pragma to the
6833 -- loop.
6835 else
6836 Placement_Error (Prev);
6837 end if;
6838 end loop;
6840 -- Check that the current pragma Loop_Invariant or Loop_Variant is
6841 -- grouped together with other such pragmas.
6843 if Is_Loop_Pragma (N) then
6845 -- The previous check should have located the related loop
6847 pragma Assert (Nkind (Stmt) = N_Loop_Statement);
6848 Check_Loop_Pragma_Grouping (Stmt);
6849 end if;
6850 end Check_Loop_Pragma_Placement;
6852 -------------------------------------------
6853 -- Check_Is_In_Decl_Part_Or_Package_Spec --
6854 -------------------------------------------
6856 procedure Check_Is_In_Decl_Part_Or_Package_Spec is
6857 P : Node_Id;
6859 begin
6860 P := Parent (N);
6861 loop
6862 if No (P) then
6863 exit;
6865 elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
6866 exit;
6868 elsif Nkind (P) in N_Package_Specification | N_Block_Statement then
6869 return;
6871 -- Note: the following tests seem a little peculiar, because
6872 -- they test for bodies, but if we were in the statement part
6873 -- of the body, we would already have hit the handled statement
6874 -- sequence, so the only way we get here is by being in the
6875 -- declarative part of the body.
6877 elsif Nkind (P) in
6878 N_Subprogram_Body | N_Package_Body | N_Task_Body | N_Entry_Body
6879 then
6880 return;
6881 end if;
6883 P := Parent (P);
6884 end loop;
6886 Error_Pragma ("pragma% is not in declarative part or package spec");
6887 end Check_Is_In_Decl_Part_Or_Package_Spec;
6889 -------------------------
6890 -- Check_No_Identifier --
6891 -------------------------
6893 procedure Check_No_Identifier (Arg : Node_Id) is
6894 begin
6895 if Nkind (Arg) = N_Pragma_Argument_Association
6896 and then Chars (Arg) /= No_Name
6897 then
6898 Error_Pragma_Arg_Ident
6899 ("pragma% does not permit identifier& here", Arg);
6900 end if;
6901 end Check_No_Identifier;
6903 --------------------------
6904 -- Check_No_Identifiers --
6905 --------------------------
6907 procedure Check_No_Identifiers is
6908 Arg_Node : Node_Id;
6909 begin
6910 Arg_Node := Arg1;
6911 for J in 1 .. Arg_Count loop
6912 Check_No_Identifier (Arg_Node);
6913 Next (Arg_Node);
6914 end loop;
6915 end Check_No_Identifiers;
6917 ------------------------
6918 -- Check_No_Link_Name --
6919 ------------------------
6921 procedure Check_No_Link_Name is
6922 begin
6923 if Present (Arg3) and then Chars (Arg3) = Name_Link_Name then
6924 Arg4 := Arg3;
6925 end if;
6927 if Present (Arg4) then
6928 Error_Pragma_Arg
6929 ("Link_Name argument not allowed for Import Intrinsic", Arg4);
6930 end if;
6931 end Check_No_Link_Name;
6933 -------------------------------
6934 -- Check_Optional_Identifier --
6935 -------------------------------
6937 procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
6938 begin
6939 if Present (Arg)
6940 and then Nkind (Arg) = N_Pragma_Argument_Association
6941 and then Chars (Arg) /= No_Name
6942 then
6943 if Chars (Arg) /= Id then
6944 Error_Msg_Name_1 := Pname;
6945 Error_Msg_Name_2 := Id;
6946 Error_Msg_N ("pragma% argument expects identifier%", Arg);
6947 raise Pragma_Exit;
6948 end if;
6949 end if;
6950 end Check_Optional_Identifier;
6952 procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
6953 begin
6954 Check_Optional_Identifier (Arg, Name_Find (Id));
6955 end Check_Optional_Identifier;
6957 -------------------------------------
6958 -- Check_Static_Boolean_Expression --
6959 -------------------------------------
6961 procedure Check_Static_Boolean_Expression (Expr : Node_Id) is
6962 begin
6963 if Present (Expr) then
6964 Analyze_And_Resolve (Expr, Standard_Boolean);
6966 if not Is_OK_Static_Expression (Expr) then
6967 Error_Pragma_Arg
6968 ("expression of pragma % must be static", Expr);
6969 end if;
6970 end if;
6971 end Check_Static_Boolean_Expression;
6973 -----------------------------
6974 -- Check_Static_Constraint --
6975 -----------------------------
6977 procedure Check_Static_Constraint (Constr : Node_Id) is
6979 procedure Require_Static (E : Node_Id);
6980 -- Require given expression to be static expression
6982 --------------------
6983 -- Require_Static --
6984 --------------------
6986 procedure Require_Static (E : Node_Id) is
6987 begin
6988 if not Is_OK_Static_Expression (E) then
6989 Flag_Non_Static_Expr
6990 ("non-static constraint not allowed in Unchecked_Union!", E);
6991 raise Pragma_Exit;
6992 end if;
6993 end Require_Static;
6995 -- Start of processing for Check_Static_Constraint
6997 begin
6998 case Nkind (Constr) is
6999 when N_Discriminant_Association =>
7000 Require_Static (Expression (Constr));
7002 when N_Range =>
7003 Require_Static (Low_Bound (Constr));
7004 Require_Static (High_Bound (Constr));
7006 when N_Attribute_Reference =>
7007 Require_Static (Type_Low_Bound (Etype (Prefix (Constr))));
7008 Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
7010 when N_Range_Constraint =>
7011 Check_Static_Constraint (Range_Expression (Constr));
7013 when N_Index_Or_Discriminant_Constraint =>
7014 declare
7015 IDC : Entity_Id;
7016 begin
7017 IDC := First (Constraints (Constr));
7018 while Present (IDC) loop
7019 Check_Static_Constraint (IDC);
7020 Next (IDC);
7021 end loop;
7022 end;
7024 when others =>
7025 null;
7026 end case;
7027 end Check_Static_Constraint;
7029 --------------------------------------
7030 -- Check_Valid_Configuration_Pragma --
7031 --------------------------------------
7033 -- A configuration pragma must appear in the context clause of a
7034 -- compilation unit, and only other pragmas may precede it. Note that
7035 -- the test also allows use in a configuration pragma file.
7037 procedure Check_Valid_Configuration_Pragma is
7038 begin
7039 if not Is_Configuration_Pragma then
7040 Error_Pragma ("incorrect placement for configuration pragma%");
7041 end if;
7042 end Check_Valid_Configuration_Pragma;
7044 -------------------------------------
7045 -- Check_Valid_Library_Unit_Pragma --
7046 -------------------------------------
7048 procedure Check_Valid_Library_Unit_Pragma is
7049 Plist : List_Id;
7050 Parent_Node : Node_Id;
7051 Unit_Name : Entity_Id;
7052 Unit_Kind : Node_Kind;
7053 Unit_Node : Node_Id;
7054 Sindex : Source_File_Index;
7056 begin
7057 if not Is_List_Member (N) then
7058 Pragma_Misplaced;
7060 else
7061 Plist := List_Containing (N);
7062 Parent_Node := Parent (Plist);
7064 if Parent_Node = Empty then
7065 Pragma_Misplaced;
7067 -- Case of pragma appearing after a compilation unit. In this case
7068 -- it must have an argument with the corresponding name and must
7069 -- be part of the following pragmas of its parent.
7071 elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
7072 if Plist /= Pragmas_After (Parent_Node) then
7073 Error_Pragma
7074 ("pragma% misplaced, must be inside or after the "
7075 & "compilation unit");
7077 elsif Arg_Count = 0 then
7078 Error_Pragma
7079 ("argument required if outside compilation unit");
7081 else
7082 Check_No_Identifiers;
7083 Check_Arg_Count (1);
7084 Unit_Node := Unit (Parent (Parent_Node));
7085 Unit_Kind := Nkind (Unit_Node);
7087 Analyze (Get_Pragma_Arg (Arg1));
7089 if Unit_Kind = N_Generic_Subprogram_Declaration
7090 or else Unit_Kind = N_Subprogram_Declaration
7091 then
7092 Unit_Name := Defining_Entity (Unit_Node);
7094 elsif Unit_Kind in N_Generic_Instantiation then
7095 Unit_Name := Defining_Entity (Unit_Node);
7097 else
7098 Unit_Name := Cunit_Entity (Current_Sem_Unit);
7099 end if;
7101 if Chars (Unit_Name) /=
7102 Chars (Entity (Get_Pragma_Arg (Arg1)))
7103 then
7104 Error_Pragma_Arg
7105 ("pragma% argument is not current unit name", Arg1);
7106 end if;
7108 if Ekind (Unit_Name) = E_Package
7109 and then Present (Renamed_Entity (Unit_Name))
7110 then
7111 Error_Pragma ("pragma% not allowed for renamed package");
7112 end if;
7113 end if;
7115 -- Pragma appears other than after a compilation unit
7117 else
7118 -- Here we check for the generic instantiation case and also
7119 -- for the case of processing a generic formal package. We
7120 -- detect these cases by noting that the Sloc on the node
7121 -- does not belong to the current compilation unit.
7123 Sindex := Source_Index (Current_Sem_Unit);
7125 if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
7126 -- We do not want to raise an exception here since this code
7127 -- is part of the bootstrap path where we cannot rely on
7128 -- exception propagation working.
7129 -- Instead the caller should check for N being rewritten as
7130 -- a null statement.
7131 -- This code triggers when compiling a-except.adb.
7133 Rewrite (N, Make_Null_Statement (Loc));
7135 -- If before first declaration, the pragma applies to the
7136 -- enclosing unit, and the name if present must be this name.
7138 elsif Is_Before_First_Decl (N, Plist) then
7139 Unit_Node := Unit_Declaration_Node (Current_Scope);
7140 Unit_Kind := Nkind (Unit_Node);
7142 if Unit_Node = Standard_Package_Node then
7143 Error_Pragma
7144 ("pragma% misplaced, must be inside or after the "
7145 & "compilation unit");
7147 elsif Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
7148 Error_Pragma
7149 ("pragma% misplaced, must be on library unit");
7151 elsif Unit_Kind = N_Subprogram_Body
7152 and then not Acts_As_Spec (Unit_Node)
7153 then
7154 Error_Pragma
7155 ("pragma% misplaced, must be on the subprogram spec");
7157 elsif Nkind (Parent_Node) = N_Package_Body then
7158 Error_Pragma
7159 ("pragma% misplaced, must be on the package spec");
7161 elsif Nkind (Parent_Node) = N_Package_Specification
7162 and then Plist = Private_Declarations (Parent_Node)
7163 then
7164 Error_Pragma
7165 ("pragma% misplaced, must be in the public part");
7167 elsif Nkind (Parent_Node) in N_Generic_Declaration
7168 and then Plist = Generic_Formal_Declarations (Parent_Node)
7169 then
7170 Error_Pragma
7171 ("pragma% misplaced, must not be in formal part");
7173 elsif Arg_Count > 0 then
7174 Analyze (Get_Pragma_Arg (Arg1));
7176 if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
7177 Error_Pragma_Arg
7178 ("name in pragma% must be enclosing unit", Arg1);
7179 end if;
7181 -- It is legal to have no argument in this context
7183 else
7184 return;
7185 end if;
7187 -- Error if not before first declaration. This is because a
7188 -- library unit pragma argument must be the name of a library
7189 -- unit (RM 10.1.5(7)), but the only names permitted in this
7190 -- context are (RM 10.1.5(6)) names of subprogram declarations,
7191 -- generic subprogram declarations or generic instantiations.
7193 else
7194 Error_Pragma
7195 ("pragma% misplaced, must be before first declaration");
7196 end if;
7197 end if;
7198 end if;
7199 end Check_Valid_Library_Unit_Pragma;
7201 -------------------
7202 -- Check_Variant --
7203 -------------------
7205 procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
7206 Clist : constant Node_Id := Component_List (Variant);
7207 Comp : Node_Id;
7209 begin
7210 Comp := First_Non_Pragma (Component_Items (Clist));
7211 while Present (Comp) loop
7212 Check_Component (Comp, UU_Typ, In_Variant_Part => True);
7213 Next_Non_Pragma (Comp);
7214 end loop;
7215 end Check_Variant;
7217 ---------------------------
7218 -- Ensure_Aggregate_Form --
7219 ---------------------------
7221 procedure Ensure_Aggregate_Form (Arg : Node_Id) is
7222 CFSD : constant Boolean := Get_Comes_From_Source_Default;
7223 Expr : constant Node_Id := Expression (Arg);
7224 Loc : constant Source_Ptr := Sloc (Expr);
7225 Comps : List_Id := No_List;
7226 Exprs : List_Id := No_List;
7227 Nam : Name_Id := No_Name;
7228 Nam_Loc : Source_Ptr;
7230 begin
7231 -- The pragma argument is in positional form:
7233 -- pragma Depends (Nam => ...)
7234 -- ^
7235 -- Chars field
7237 -- Note that the Sloc of the Chars field is the Sloc of the pragma
7238 -- argument association.
7240 if Nkind (Arg) = N_Pragma_Argument_Association then
7241 Nam := Chars (Arg);
7242 Nam_Loc := Sloc (Arg);
7244 -- Remove the pragma argument name as this will be captured in the
7245 -- aggregate.
7247 Set_Chars (Arg, No_Name);
7248 end if;
7250 -- The argument is already in aggregate form, but the presence of a
7251 -- name causes this to be interpreted as named association which in
7252 -- turn must be converted into an aggregate.
7254 -- pragma Global (In_Out => (A, B, C))
7255 -- ^ ^
7256 -- name aggregate
7258 -- pragma Global ((In_Out => (A, B, C)))
7259 -- ^ ^
7260 -- aggregate aggregate
7262 if Nkind (Expr) = N_Aggregate then
7263 if Nam = No_Name then
7264 return;
7265 end if;
7267 -- Do not transform a null argument into an aggregate as N_Null has
7268 -- special meaning in formal verification pragmas.
7270 elsif Nkind (Expr) = N_Null then
7271 return;
7272 end if;
7274 -- Everything comes from source if the original comes from source
7276 Set_Comes_From_Source_Default (Comes_From_Source (Arg));
7278 -- Positional argument is transformed into an aggregate with an
7279 -- Expressions list.
7281 if Nam = No_Name then
7282 Exprs := New_List (Relocate_Node (Expr));
7284 -- An associative argument is transformed into an aggregate with
7285 -- Component_Associations.
7287 else
7288 Comps := New_List (
7289 Make_Component_Association (Loc,
7290 Choices => New_List (Make_Identifier (Nam_Loc, Nam)),
7291 Expression => Relocate_Node (Expr)));
7292 end if;
7294 Set_Expression (Arg,
7295 Make_Aggregate (Loc,
7296 Component_Associations => Comps,
7297 Expressions => Exprs));
7299 -- Restore Comes_From_Source default
7301 Set_Comes_From_Source_Default (CFSD);
7302 end Ensure_Aggregate_Form;
7304 ------------------
7305 -- Error_Pragma --
7306 ------------------
7308 procedure Error_Pragma (Msg : String) is
7309 begin
7310 Error_Msg_Name_1 := Pname;
7311 Error_Msg_N (Fix_Error (Msg), N);
7312 raise Pragma_Exit;
7313 end Error_Pragma;
7315 ----------------------
7316 -- Error_Pragma_Arg --
7317 ----------------------
7319 procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
7320 begin
7321 Error_Msg_Name_1 := Pname;
7322 Error_Msg_N (Fix_Error (Msg), Get_Pragma_Arg (Arg));
7323 raise Pragma_Exit;
7324 end Error_Pragma_Arg;
7326 procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
7327 begin
7328 Error_Msg_Name_1 := Pname;
7329 Error_Msg_N (Fix_Error (Msg1), Get_Pragma_Arg (Arg));
7330 Error_Pragma_Arg (Msg2, Arg);
7331 end Error_Pragma_Arg;
7333 ----------------------------
7334 -- Error_Pragma_Arg_Ident --
7335 ----------------------------
7337 procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
7338 begin
7339 Error_Msg_Name_1 := Pname;
7340 Error_Msg_N (Fix_Error (Msg), Arg);
7341 raise Pragma_Exit;
7342 end Error_Pragma_Arg_Ident;
7344 ----------------------
7345 -- Error_Pragma_Ref --
7346 ----------------------
7348 procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
7349 begin
7350 Error_Msg_Name_1 := Pname;
7351 Error_Msg_Sloc := Sloc (Ref);
7352 Error_Msg_NE (Fix_Error (Msg), N, Ref);
7353 raise Pragma_Exit;
7354 end Error_Pragma_Ref;
7356 ------------------------
7357 -- Find_Lib_Unit_Name --
7358 ------------------------
7360 function Find_Lib_Unit_Name return Entity_Id is
7361 begin
7362 -- Return inner compilation unit entity, for case of nested
7363 -- categorization pragmas. This happens in generic unit.
7365 if Nkind (Parent (N)) = N_Package_Specification
7366 and then Defining_Entity (Parent (N)) /= Current_Scope
7367 then
7368 return Defining_Entity (Parent (N));
7369 else
7370 return Current_Scope;
7371 end if;
7372 end Find_Lib_Unit_Name;
7374 ----------------------------
7375 -- Find_Program_Unit_Name --
7376 ----------------------------
7378 procedure Find_Program_Unit_Name (Id : Node_Id) is
7379 Unit_Name : Entity_Id;
7380 Unit_Kind : Node_Kind;
7381 P : constant Node_Id := Parent (N);
7383 begin
7384 if Nkind (P) = N_Compilation_Unit then
7385 Unit_Kind := Nkind (Unit (P));
7387 if Unit_Kind in N_Subprogram_Declaration
7388 | N_Package_Declaration
7389 | N_Generic_Declaration
7390 then
7391 Unit_Name := Defining_Entity (Unit (P));
7393 if Chars (Id) = Chars (Unit_Name) then
7394 Set_Entity (Id, Unit_Name);
7395 Set_Etype (Id, Etype (Unit_Name));
7396 else
7397 Set_Etype (Id, Any_Type);
7398 Error_Pragma
7399 ("cannot find program unit referenced by pragma%");
7400 end if;
7402 else
7403 Set_Etype (Id, Any_Type);
7404 Error_Pragma ("pragma% inapplicable to this unit");
7405 end if;
7407 else
7408 Analyze (Id);
7409 end if;
7410 end Find_Program_Unit_Name;
7412 -----------------------------------------
7413 -- Find_Unique_Parameterless_Procedure --
7414 -----------------------------------------
7416 function Find_Unique_Parameterless_Procedure
7417 (Name : Entity_Id;
7418 Arg : Node_Id) return Entity_Id
7420 Proc : Entity_Id := Empty;
7422 begin
7423 -- Perform sanity checks on Name
7425 if not Is_Entity_Name (Name) then
7426 Error_Pragma_Arg
7427 ("argument of pragma% must be entity name", Arg);
7429 elsif not Is_Overloaded (Name) then
7430 Proc := Entity (Name);
7432 if Ekind (Proc) /= E_Procedure
7433 or else Present (First_Formal (Proc))
7434 then
7435 Error_Pragma_Arg
7436 ("argument of pragma% must be parameterless procedure", Arg);
7437 end if;
7439 -- Otherwise, search through interpretations looking for one which
7440 -- has no parameters.
7442 else
7443 declare
7444 Found : Boolean := False;
7445 It : Interp;
7446 Index : Interp_Index;
7448 begin
7449 Get_First_Interp (Name, Index, It);
7450 while Present (It.Nam) loop
7451 Proc := It.Nam;
7453 if Ekind (Proc) = E_Procedure
7454 and then No (First_Formal (Proc))
7455 then
7456 -- We found an interpretation, note it and continue
7457 -- looking looking to verify it is unique.
7459 if not Found then
7460 Found := True;
7461 Set_Entity (Name, Proc);
7462 Set_Is_Overloaded (Name, False);
7464 -- Two procedures with the same name, log an error
7465 -- since the name is ambiguous.
7467 else
7468 Error_Pragma_Arg
7469 ("ambiguous handler name for pragma%", Arg);
7470 end if;
7471 end if;
7473 Get_Next_Interp (Index, It);
7474 end loop;
7476 if not Found then
7477 -- Issue an error if we haven't found a suitable match for
7478 -- Name.
7480 Error_Pragma_Arg
7481 ("argument of pragma% must be parameterless procedure",
7482 Arg);
7484 else
7485 Proc := Entity (Name);
7486 end if;
7487 end;
7488 end if;
7490 return Proc;
7491 end Find_Unique_Parameterless_Procedure;
7493 ---------------
7494 -- Fix_Error --
7495 ---------------
7497 function Fix_Error (Msg : String) return String is
7498 Res : String (Msg'Range) := Msg;
7499 Res_Last : Natural := Msg'Last;
7500 J : Natural;
7502 begin
7503 -- If we have a rewriting of another pragma, go to that pragma
7505 if Is_Rewrite_Substitution (N)
7506 and then Nkind (Original_Node (N)) = N_Pragma
7507 then
7508 Error_Msg_Name_1 := Pragma_Name (Original_Node (N));
7509 end if;
7511 -- Case where pragma comes from an aspect specification
7513 if From_Aspect_Specification (N) then
7515 -- Change appearance of "pragma" in message to "aspect"
7517 J := Res'First;
7518 while J <= Res_Last - 5 loop
7519 if Res (J .. J + 5) = "pragma" then
7520 Res (J .. J + 5) := "aspect";
7521 J := J + 6;
7523 else
7524 J := J + 1;
7525 end if;
7526 end loop;
7528 -- Change "argument of" at start of message to "entity for"
7530 if Res'Length > 11
7531 and then Res (Res'First .. Res'First + 10) = "argument of"
7532 then
7533 Res (Res'First .. Res'First + 9) := "entity for";
7534 Res (Res'First + 10 .. Res_Last - 1) :=
7535 Res (Res'First + 11 .. Res_Last);
7536 Res_Last := Res_Last - 1;
7537 end if;
7539 -- Change "argument" at start of message to "entity"
7541 if Res'Length > 8
7542 and then Res (Res'First .. Res'First + 7) = "argument"
7543 then
7544 Res (Res'First .. Res'First + 5) := "entity";
7545 Res (Res'First + 6 .. Res_Last - 2) :=
7546 Res (Res'First + 8 .. Res_Last);
7547 Res_Last := Res_Last - 2;
7548 end if;
7550 -- Get name from corresponding aspect
7552 Error_Msg_Name_1 := Original_Aspect_Pragma_Name (N);
7553 end if;
7555 -- Return possibly modified message
7557 return Res (Res'First .. Res_Last);
7558 end Fix_Error;
7560 -------------------------
7561 -- Gather_Associations --
7562 -------------------------
7564 procedure Gather_Associations
7565 (Names : Name_List;
7566 Args : out Args_List)
7568 Arg : Node_Id;
7570 begin
7571 -- Initialize all parameters to Empty
7573 for J in Args'Range loop
7574 Args (J) := Empty;
7575 end loop;
7577 -- That's all we have to do if there are no argument associations
7579 if No (Pragma_Argument_Associations (N)) then
7580 return;
7581 end if;
7583 -- Otherwise first deal with any positional parameters present
7585 Arg := First (Pragma_Argument_Associations (N));
7586 for Index in Args'Range loop
7587 exit when No (Arg) or else Chars (Arg) /= No_Name;
7588 Args (Index) := Get_Pragma_Arg (Arg);
7589 Next (Arg);
7590 end loop;
7592 -- Positional parameters all processed, if any left, then we
7593 -- have too many positional parameters.
7595 if Present (Arg) and then Chars (Arg) = No_Name then
7596 Error_Pragma_Arg
7597 ("too many positional associations for pragma%", Arg);
7598 end if;
7600 -- Process named parameters if any are present
7602 while Present (Arg) loop
7603 if Chars (Arg) = No_Name then
7604 Error_Pragma_Arg
7605 ("positional association cannot follow named association",
7606 Arg);
7608 else
7609 for Index in Names'Range loop
7610 if Names (Index) = Chars (Arg) then
7611 if Present (Args (Index)) then
7612 Error_Pragma_Arg
7613 ("duplicate argument association for pragma%", Arg);
7614 else
7615 Args (Index) := Get_Pragma_Arg (Arg);
7616 exit;
7617 end if;
7618 end if;
7620 if Index = Names'Last then
7621 Error_Msg_Name_1 := Pname;
7622 Error_Msg_N ("pragma% does not allow & argument", Arg);
7624 -- Check for possible misspelling
7626 for Index1 in Names'Range loop
7627 if Is_Bad_Spelling_Of
7628 (Chars (Arg), Names (Index1))
7629 then
7630 Error_Msg_Name_1 := Names (Index1);
7631 Error_Msg_N -- CODEFIX
7632 ("\possible misspelling of%", Arg);
7633 exit;
7634 end if;
7635 end loop;
7637 raise Pragma_Exit;
7638 end if;
7639 end loop;
7640 end if;
7642 Next (Arg);
7643 end loop;
7644 end Gather_Associations;
7646 -----------------
7647 -- GNAT_Pragma --
7648 -----------------
7650 procedure GNAT_Pragma is
7651 begin
7652 -- We need to check the No_Implementation_Pragmas restriction for
7653 -- the case of a pragma from source. Note that the case of aspects
7654 -- generating corresponding pragmas marks these pragmas as not being
7655 -- from source, so this test also catches that case.
7657 if Comes_From_Source (N) then
7658 Check_Restriction (No_Implementation_Pragmas, N);
7659 end if;
7660 end GNAT_Pragma;
7662 --------------------------
7663 -- Is_Before_First_Decl --
7664 --------------------------
7666 function Is_Before_First_Decl
7667 (Pragma_Node : Node_Id;
7668 Decls : List_Id) return Boolean
7670 Item : Node_Id := First (Decls);
7672 begin
7673 -- Only other pragmas can come before this pragma, but they might
7674 -- have been rewritten so check the original node.
7676 loop
7677 if No (Item) or else Nkind (Original_Node (Item)) /= N_Pragma then
7678 return False;
7680 elsif Item = Pragma_Node then
7681 return True;
7682 end if;
7684 Next (Item);
7685 end loop;
7686 end Is_Before_First_Decl;
7688 -----------------------------
7689 -- Is_Configuration_Pragma --
7690 -----------------------------
7692 -- A configuration pragma must appear in the context clause of a
7693 -- compilation unit, and only other pragmas may precede it. Note that
7694 -- the test below also permits use in a configuration pragma file.
7696 function Is_Configuration_Pragma return Boolean is
7697 Lis : List_Id;
7698 Par : constant Node_Id := Parent (N);
7699 Prg : Node_Id;
7701 begin
7702 -- Don't evaluate List_Containing (N) if Parent (N) could be
7703 -- an N_Aspect_Specification node.
7705 if not Is_List_Member (N) then
7706 return False;
7707 end if;
7709 Lis := List_Containing (N);
7711 -- If no parent, then we are in the configuration pragma file,
7712 -- so the placement is definitely appropriate.
7714 if No (Par) then
7715 return True;
7717 -- Otherwise we must be in the context clause of a compilation unit
7718 -- and the only thing allowed before us in the context list is more
7719 -- configuration pragmas.
7721 elsif Nkind (Par) = N_Compilation_Unit
7722 and then Context_Items (Par) = Lis
7723 then
7724 Prg := First (Lis);
7726 loop
7727 if Prg = N then
7728 return True;
7729 elsif Nkind (Prg) /= N_Pragma then
7730 return False;
7731 end if;
7733 Next (Prg);
7734 end loop;
7736 else
7737 return False;
7738 end if;
7739 end Is_Configuration_Pragma;
7741 --------------------------
7742 -- Is_In_Context_Clause --
7743 --------------------------
7745 function Is_In_Context_Clause return Boolean is
7746 Plist : List_Id;
7747 Parent_Node : Node_Id;
7749 begin
7750 if Is_List_Member (N) then
7751 Plist := List_Containing (N);
7752 Parent_Node := Parent (Plist);
7754 return Present (Parent_Node)
7755 and then Nkind (Parent_Node) = N_Compilation_Unit
7756 and then Context_Items (Parent_Node) = Plist;
7757 end if;
7759 return False;
7760 end Is_In_Context_Clause;
7762 ---------------------------------
7763 -- Is_Static_String_Expression --
7764 ---------------------------------
7766 function Is_Static_String_Expression (Arg : Node_Id) return Boolean is
7767 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
7768 Lit : constant Boolean := Nkind (Argx) = N_String_Literal;
7770 begin
7771 Analyze_And_Resolve (Argx);
7773 -- Special case Ada 83, where the expression will never be static,
7774 -- but we will return true if we had a string literal to start with.
7776 if Ada_Version = Ada_83 then
7777 return Lit;
7779 -- Normal case, true only if we end up with a string literal that
7780 -- is marked as being the result of evaluating a static expression.
7782 else
7783 return Is_OK_Static_Expression (Argx)
7784 and then Nkind (Argx) = N_String_Literal;
7785 end if;
7787 end Is_Static_String_Expression;
7789 ----------------------
7790 -- Pragma_Misplaced --
7791 ----------------------
7793 procedure Pragma_Misplaced is
7794 begin
7795 Error_Pragma ("incorrect placement of pragma%");
7796 end Pragma_Misplaced;
7798 ------------------------------------------------
7799 -- Process_Atomic_Independent_Shared_Volatile --
7800 ------------------------------------------------
7802 procedure Process_Atomic_Independent_Shared_Volatile is
7803 procedure Check_Full_Access_Only (Ent : Entity_Id);
7804 -- Apply legality checks to type or object Ent subject to the
7805 -- Full_Access_Only aspect in Ada 2022 (RM C.6(8.2)).
7807 procedure Mark_Component_Or_Object (Ent : Entity_Id);
7808 -- Appropriately set flags on the given entity, either an array or
7809 -- record component, or an object declaration) according to the
7810 -- current pragma.
7812 procedure Mark_Type (Ent : Entity_Id);
7813 -- Appropriately set flags on the given entity, a type
7815 procedure Set_Atomic_VFA (Ent : Entity_Id);
7816 -- Set given type as Is_Atomic or Is_Volatile_Full_Access. Also, if
7817 -- no explicit alignment was given, set alignment to unknown, since
7818 -- back end knows what the alignment requirements are for atomic and
7819 -- full access arrays. Note: this is necessary for derived types.
7821 -------------------------
7822 -- Check_Full_Access_Only --
7823 -------------------------
7825 procedure Check_Full_Access_Only (Ent : Entity_Id) is
7826 Typ : Entity_Id;
7828 Full_Access_Subcomponent : exception;
7829 -- Exception raised if a full access subcomponent is found
7831 Generic_Type_Subcomponent : exception;
7832 -- Exception raised if a subcomponent with generic type is found
7834 procedure Check_Subcomponents (Typ : Entity_Id);
7835 -- Apply checks to subcomponents recursively
7837 -------------------------
7838 -- Check_Subcomponents --
7839 -------------------------
7841 procedure Check_Subcomponents (Typ : Entity_Id) is
7842 Comp : Entity_Id;
7844 begin
7845 if Is_Array_Type (Typ) then
7846 Comp := Component_Type (Typ);
7848 if Has_Atomic_Components (Typ)
7849 or else Is_Full_Access (Comp)
7850 then
7851 raise Full_Access_Subcomponent;
7853 elsif Is_Generic_Type (Comp) then
7854 raise Generic_Type_Subcomponent;
7855 end if;
7857 -- Recurse on the component type
7859 Check_Subcomponents (Comp);
7861 elsif Is_Record_Type (Typ) then
7862 Comp := First_Component_Or_Discriminant (Typ);
7863 while Present (Comp) loop
7865 if Is_Full_Access (Comp)
7866 or else Is_Full_Access (Etype (Comp))
7867 then
7868 raise Full_Access_Subcomponent;
7870 elsif Is_Generic_Type (Etype (Comp)) then
7871 raise Generic_Type_Subcomponent;
7872 end if;
7874 -- Recurse on the component type
7876 Check_Subcomponents (Etype (Comp));
7878 Next_Component_Or_Discriminant (Comp);
7879 end loop;
7880 end if;
7881 end Check_Subcomponents;
7883 -- Start of processing for Check_Full_Access_Only
7885 begin
7886 -- Fetch the type in case we are dealing with an object or
7887 -- component.
7889 if Is_Type (Ent) then
7890 Typ := Ent;
7891 else
7892 pragma Assert (Is_Object (Ent)
7893 or else
7894 Nkind (Declaration_Node (Ent)) = N_Component_Declaration);
7896 Typ := Etype (Ent);
7897 end if;
7899 if not Is_Volatile (Ent) and then not Is_Volatile (Typ) then
7900 Error_Pragma
7901 ("cannot have Full_Access_Only without Volatile/Atomic "
7902 & "(RM C.6(8.2))");
7903 end if;
7905 -- Check all the subcomponents of the type recursively, if any
7907 Check_Subcomponents (Typ);
7909 exception
7910 when Full_Access_Subcomponent =>
7911 Error_Pragma
7912 ("cannot have Full_Access_Only with full access subcomponent "
7913 & "(RM C.6(8.2))");
7915 when Generic_Type_Subcomponent =>
7916 Error_Pragma
7917 ("cannot have Full_Access_Only with subcomponent of generic "
7918 & "type (RM C.6(8.2))");
7920 end Check_Full_Access_Only;
7922 ------------------------------
7923 -- Mark_Component_Or_Object --
7924 ------------------------------
7926 procedure Mark_Component_Or_Object (Ent : Entity_Id) is
7927 begin
7928 if Prag_Id = Pragma_Atomic
7929 or else Prag_Id = Pragma_Shared
7930 or else Prag_Id = Pragma_Volatile_Full_Access
7931 then
7932 if Prag_Id = Pragma_Volatile_Full_Access then
7933 Set_Is_Volatile_Full_Access (Ent);
7934 else
7935 Set_Is_Atomic (Ent);
7936 end if;
7938 -- If the object declaration has an explicit initialization, a
7939 -- temporary may have to be created to hold the expression, to
7940 -- ensure that access to the object remains atomic.
7942 if Nkind (Parent (Ent)) = N_Object_Declaration
7943 and then Present (Expression (Parent (Ent)))
7944 then
7945 Set_Has_Delayed_Freeze (Ent);
7946 end if;
7947 end if;
7949 -- Atomic/Shared/Volatile_Full_Access imply Independent
7951 if Prag_Id /= Pragma_Volatile then
7952 Set_Is_Independent (Ent);
7954 if Prag_Id = Pragma_Independent then
7955 Record_Independence_Check (N, Ent);
7956 end if;
7957 end if;
7959 -- Atomic/Shared/Volatile_Full_Access imply Volatile
7961 if Prag_Id /= Pragma_Independent then
7962 Set_Is_Volatile (Ent);
7963 Set_Treat_As_Volatile (Ent);
7964 end if;
7965 end Mark_Component_Or_Object;
7967 ---------------
7968 -- Mark_Type --
7969 ---------------
7971 procedure Mark_Type (Ent : Entity_Id) is
7972 begin
7973 -- Attribute belongs on the base type. If the view of the type is
7974 -- currently private, it also belongs on the underlying type.
7976 -- In Ada 2022, the pragma can apply to a formal type, for which
7977 -- there may be no underlying type.
7979 if Prag_Id = Pragma_Atomic
7980 or else Prag_Id = Pragma_Shared
7981 or else Prag_Id = Pragma_Volatile_Full_Access
7982 then
7983 Set_Atomic_VFA (Ent);
7984 Set_Atomic_VFA (Base_Type (Ent));
7986 if not Is_Generic_Type (Ent) then
7987 Set_Atomic_VFA (Underlying_Type (Ent));
7988 end if;
7989 end if;
7991 -- Atomic/Shared/Volatile_Full_Access imply Independent
7993 if Prag_Id /= Pragma_Volatile then
7994 Set_Is_Independent (Ent);
7995 Set_Is_Independent (Base_Type (Ent));
7997 if not Is_Generic_Type (Ent) then
7998 Set_Is_Independent (Underlying_Type (Ent));
8000 if Prag_Id = Pragma_Independent then
8001 Record_Independence_Check (N, Base_Type (Ent));
8002 end if;
8003 end if;
8004 end if;
8006 -- Atomic/Shared/Volatile_Full_Access imply Volatile
8008 if Prag_Id /= Pragma_Independent then
8009 Set_Is_Volatile (Ent);
8010 Set_Is_Volatile (Base_Type (Ent));
8012 if not Is_Generic_Type (Ent) then
8013 Set_Is_Volatile (Underlying_Type (Ent));
8014 Set_Treat_As_Volatile (Underlying_Type (Ent));
8015 end if;
8017 Set_Treat_As_Volatile (Ent);
8018 end if;
8020 -- Apply Volatile to the composite type's individual components,
8021 -- (RM C.6(8/3)).
8023 if Prag_Id = Pragma_Volatile
8024 and then Is_Record_Type (Etype (Ent))
8025 then
8026 declare
8027 Comp : Entity_Id;
8028 begin
8029 Comp := First_Component (Ent);
8030 while Present (Comp) loop
8031 Mark_Component_Or_Object (Comp);
8033 Next_Component (Comp);
8034 end loop;
8035 end;
8036 end if;
8037 end Mark_Type;
8039 --------------------
8040 -- Set_Atomic_VFA --
8041 --------------------
8043 procedure Set_Atomic_VFA (Ent : Entity_Id) is
8044 begin
8045 if Prag_Id = Pragma_Volatile_Full_Access then
8046 Set_Is_Volatile_Full_Access (Ent);
8047 else
8048 Set_Is_Atomic (Ent);
8049 end if;
8051 if not Has_Alignment_Clause (Ent) then
8052 Reinit_Alignment (Ent);
8053 end if;
8054 end Set_Atomic_VFA;
8056 -- Local variables
8058 Decl : Node_Id;
8059 E : Entity_Id;
8060 E_Arg : Node_Id;
8062 -- Start of processing for Process_Atomic_Independent_Shared_Volatile
8064 begin
8065 Check_Ada_83_Warning;
8066 Check_No_Identifiers;
8067 Check_Arg_Count (1);
8068 Check_Arg_Is_Local_Name (Arg1);
8069 E_Arg := Get_Pragma_Arg (Arg1);
8071 if Etype (E_Arg) = Any_Type then
8072 return;
8073 end if;
8075 E := Entity (E_Arg);
8076 Decl := Declaration_Node (E);
8078 -- A pragma that applies to a Ghost entity becomes Ghost for the
8079 -- purposes of legality checks and removal of ignored Ghost code.
8081 Mark_Ghost_Pragma (N, E);
8083 -- Check duplicate before we chain ourselves
8085 Check_Duplicate_Pragma (E);
8087 -- Check the constraints of Full_Access_Only in Ada 2022. Note that
8088 -- they do not apply to GNAT's Volatile_Full_Access because 1) this
8089 -- aspect subsumes the Volatile aspect and 2) nesting is supported
8090 -- for this aspect and the outermost enclosing VFA object prevails.
8092 -- Note also that we used to forbid specifying both Atomic and VFA on
8093 -- the same type or object, but the restriction has been lifted in
8094 -- light of the semantics of Full_Access_Only and Atomic in Ada 2022.
8096 if Prag_Id = Pragma_Volatile_Full_Access
8097 and then From_Aspect_Specification (N)
8098 and then
8099 Get_Aspect_Id (Corresponding_Aspect (N)) = Aspect_Full_Access_Only
8100 then
8101 Check_Full_Access_Only (E);
8102 end if;
8104 -- Deal with the case where the pragma/attribute is applied to a type
8106 if Is_Type (E) then
8107 if Rep_Item_Too_Early (E, N)
8108 or else Rep_Item_Too_Late (E, N)
8109 then
8110 return;
8111 else
8112 Check_First_Subtype (Arg1);
8113 end if;
8115 Mark_Type (E);
8117 -- Deal with the case where the pragma/attribute applies to a
8118 -- component or object declaration.
8120 elsif Nkind (Decl) = N_Object_Declaration
8121 or else (Nkind (Decl) = N_Component_Declaration
8122 and then Original_Record_Component (E) = E)
8123 then
8124 if Rep_Item_Too_Late (E, N) then
8125 return;
8126 end if;
8128 Mark_Component_Or_Object (E);
8130 -- In other cases give an error
8132 else
8133 Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
8134 end if;
8135 end Process_Atomic_Independent_Shared_Volatile;
8137 -------------------------------------------
8138 -- Process_Compile_Time_Warning_Or_Error --
8139 -------------------------------------------
8141 procedure Process_Compile_Time_Warning_Or_Error is
8142 P : Node_Id := Parent (N);
8143 Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
8145 begin
8146 Check_Arg_Count (2);
8147 Check_No_Identifiers;
8148 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
8149 Analyze_And_Resolve (Arg1x, Standard_Boolean);
8151 -- In GNATprove mode, pragma Compile_Time_Error is translated as
8152 -- a Check pragma in GNATprove mode, handled as an assumption in
8153 -- GNATprove. This is correct as the compiler will issue an error
8154 -- if the condition cannot be statically evaluated to False.
8155 -- Compile_Time_Warning are ignored, as the analyzer may not have the
8156 -- same information as the compiler (in particular regarding size of
8157 -- objects decided in gigi) so it makes no sense to issue a warning
8158 -- in GNATprove.
8160 if GNATprove_Mode then
8161 if Prag_Id = Pragma_Compile_Time_Error then
8162 declare
8163 New_Args : List_Id;
8164 begin
8165 -- Implement Compile_Time_Error by generating
8166 -- a corresponding Check pragma:
8168 -- pragma Check (name, condition);
8170 -- where name is the identifier matching the pragma name. So
8171 -- rewrite pragma in this manner and analyze the result.
8173 New_Args := New_List
8174 (Make_Pragma_Argument_Association
8175 (Loc,
8176 Expression => Make_Identifier (Loc, Pname)),
8177 Make_Pragma_Argument_Association
8178 (Sloc (Arg1x),
8179 Expression => Arg1x));
8181 -- Rewrite as Check pragma
8183 Rewrite (N,
8184 Make_Pragma (Loc,
8185 Chars => Name_Check,
8186 Pragma_Argument_Associations => New_Args));
8188 Analyze (N);
8189 end;
8191 else
8192 Rewrite (N, Make_Null_Statement (Loc));
8193 end if;
8195 return;
8196 end if;
8198 -- If the condition is known at compile time (now), validate it now.
8199 -- Otherwise, register the expression for validation after the back
8200 -- end has been called, because it might be known at compile time
8201 -- then. For example, if the expression is "Record_Type'Size /= 32"
8202 -- it might be known after the back end has determined the size of
8203 -- Record_Type. We do not defer validation if we're inside a generic
8204 -- unit, because we will have more information in the instances, and
8205 -- this ultimately applies to the main unit itself, because it is not
8206 -- compiled by the back end when it is generic.
8208 if Compile_Time_Known_Value (Arg1x) then
8209 Validate_Compile_Time_Warning_Or_Error (N, Sloc (Arg1));
8211 else
8212 while Present (P) and then Nkind (P) not in N_Generic_Declaration
8213 loop
8214 if (Nkind (P) = N_Subprogram_Body and then not Acts_As_Spec (P))
8215 or else Nkind (P) = N_Package_Body
8216 then
8217 P := Parent (Corresponding_Spec (P));
8219 else
8220 P := Parent (P);
8221 end if;
8222 end loop;
8224 if No (P)
8225 and then
8226 Nkind (Unit (Cunit (Main_Unit))) not in N_Generic_Declaration
8227 then
8228 Defer_Compile_Time_Warning_Error_To_BE (N);
8229 end if;
8230 end if;
8231 end Process_Compile_Time_Warning_Or_Error;
8233 ------------------------
8234 -- Process_Convention --
8235 ------------------------
8237 procedure Process_Convention
8238 (C : out Convention_Id;
8239 Ent : out Entity_Id)
8241 Cname : Name_Id;
8243 procedure Diagnose_Multiple_Pragmas (S : Entity_Id);
8244 -- Called if we have more than one Export/Import/Convention pragma.
8245 -- This is generally illegal, but we have a special case of allowing
8246 -- Import and Interface to coexist if they specify the convention in
8247 -- a consistent manner. We are allowed to do this, since Interface is
8248 -- an implementation defined pragma, and we choose to do it since we
8249 -- know Rational allows this combination. S is the entity id of the
8250 -- subprogram in question. This procedure also sets the special flag
8251 -- Import_Interface_Present in both pragmas in the case where we do
8252 -- have matching Import and Interface pragmas.
8254 procedure Set_Convention_From_Pragma (E : Entity_Id);
8255 -- Set convention in entity E, and also flag that the entity has a
8256 -- convention pragma. If entity is for a private or incomplete type,
8257 -- also set convention and flag on underlying type. This procedure
8258 -- also deals with the special case of C_Pass_By_Copy convention,
8259 -- and error checks for inappropriate convention specification.
8261 -------------------------------
8262 -- Diagnose_Multiple_Pragmas --
8263 -------------------------------
8265 procedure Diagnose_Multiple_Pragmas (S : Entity_Id) is
8266 Pdec : constant Node_Id := Declaration_Node (S);
8267 Decl : Node_Id;
8268 Err : Boolean;
8270 function Same_Convention (Decl : Node_Id) return Boolean;
8271 -- Decl is a pragma node. This function returns True if this
8272 -- pragma has a first argument that is an identifier with a
8273 -- Chars field corresponding to the Convention_Id C.
8275 function Same_Name (Decl : Node_Id) return Boolean;
8276 -- Decl is a pragma node. This function returns True if this
8277 -- pragma has a second argument that is an identifier with a
8278 -- Chars field that matches the Chars of the current subprogram.
8280 ---------------------
8281 -- Same_Convention --
8282 ---------------------
8284 function Same_Convention (Decl : Node_Id) return Boolean is
8285 Arg1 : constant Node_Id :=
8286 First (Pragma_Argument_Associations (Decl));
8288 begin
8289 if Present (Arg1) then
8290 declare
8291 Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
8292 begin
8293 if Nkind (Arg) = N_Identifier
8294 and then Is_Convention_Name (Chars (Arg))
8295 and then Get_Convention_Id (Chars (Arg)) = C
8296 then
8297 return True;
8298 end if;
8299 end;
8300 end if;
8302 return False;
8303 end Same_Convention;
8305 ---------------
8306 -- Same_Name --
8307 ---------------
8309 function Same_Name (Decl : Node_Id) return Boolean is
8310 Arg1 : constant Node_Id :=
8311 First (Pragma_Argument_Associations (Decl));
8312 Arg2 : Node_Id;
8314 begin
8315 if No (Arg1) then
8316 return False;
8317 end if;
8319 Arg2 := Next (Arg1);
8321 if No (Arg2) then
8322 return False;
8323 end if;
8325 declare
8326 Arg : constant Node_Id := Get_Pragma_Arg (Arg2);
8327 begin
8328 if Nkind (Arg) = N_Identifier
8329 and then Chars (Arg) = Chars (S)
8330 then
8331 return True;
8332 end if;
8333 end;
8335 return False;
8336 end Same_Name;
8338 -- Start of processing for Diagnose_Multiple_Pragmas
8340 begin
8341 Err := True;
8343 -- Definitely give message if we have Convention/Export here
8345 if Prag_Id = Pragma_Convention or else Prag_Id = Pragma_Export then
8346 null;
8348 -- If we have an Import or Export, scan back from pragma to
8349 -- find any previous pragma applying to the same procedure.
8350 -- The scan will be terminated by the start of the list, or
8351 -- hitting the subprogram declaration. This won't allow one
8352 -- pragma to appear in the public part and one in the private
8353 -- part, but that seems very unlikely in practice.
8355 else
8356 Decl := Prev (N);
8357 while Present (Decl) and then Decl /= Pdec loop
8359 -- Look for pragma with same name as us
8361 if Nkind (Decl) = N_Pragma
8362 and then Same_Name (Decl)
8363 then
8364 -- Give error if same as our pragma or Export/Convention
8366 if Pragma_Name_Unmapped (Decl)
8367 in Name_Export
8368 | Name_Convention
8369 | Pragma_Name_Unmapped (N)
8370 then
8371 exit;
8373 -- Case of Import/Interface or the other way round
8375 elsif Pragma_Name_Unmapped (Decl)
8376 in Name_Interface | Name_Import
8377 then
8378 -- Here we know that we have Import and Interface. It
8379 -- doesn't matter which way round they are. See if
8380 -- they specify the same convention. If so, all OK,
8381 -- and set special flags to stop other messages
8383 if Same_Convention (Decl) then
8384 Set_Import_Interface_Present (N);
8385 Set_Import_Interface_Present (Decl);
8386 Err := False;
8388 -- If different conventions, special message
8390 else
8391 Error_Msg_Sloc := Sloc (Decl);
8392 Error_Pragma_Arg
8393 ("convention differs from that given#", Arg1);
8394 end if;
8395 end if;
8396 end if;
8398 Next (Decl);
8399 end loop;
8400 end if;
8402 -- Give message if needed if we fall through those tests
8403 -- except on Relaxed_RM_Semantics where we let go: either this
8404 -- is a case accepted/ignored by other Ada compilers (e.g.
8405 -- a mix of Convention and Import), or another error will be
8406 -- generated later (e.g. using both Import and Export).
8408 if Err and not Relaxed_RM_Semantics then
8409 Error_Pragma_Arg
8410 ("at most one Convention/Export/Import pragma is allowed",
8411 Arg2);
8412 end if;
8413 end Diagnose_Multiple_Pragmas;
8415 --------------------------------
8416 -- Set_Convention_From_Pragma --
8417 --------------------------------
8419 procedure Set_Convention_From_Pragma (E : Entity_Id) is
8420 begin
8421 -- Ada 2005 (AI-430): Check invalid attempt to change convention
8422 -- for an overridden dispatching operation. Technically this is
8423 -- an amendment and should only be done in Ada 2005 mode. However,
8424 -- this is clearly a mistake, since the problem that is addressed
8425 -- by this AI is that there is a clear gap in the RM.
8427 if Is_Dispatching_Operation (E)
8428 and then Present (Overridden_Operation (E))
8429 and then C /= Convention (Overridden_Operation (E))
8430 then
8431 Error_Pragma_Arg
8432 ("cannot change convention for overridden dispatching "
8433 & "operation", Arg1);
8435 -- Special check for convention Stdcall: a dispatching call is not
8436 -- allowed. A dispatching subprogram cannot be used to interface
8437 -- to the Win32 API, so this check actually does not impose any
8438 -- effective restriction.
8440 elsif Is_Dispatching_Operation (E)
8441 and then C = Convention_Stdcall
8442 then
8443 -- Note: make this unconditional so that if there is more
8444 -- than one call to which the pragma applies, we get a
8445 -- message for each call. Also don't use Error_Pragma,
8446 -- so that we get multiple messages.
8448 Error_Msg_Sloc := Sloc (E);
8449 Error_Msg_N
8450 ("dispatching subprogram# cannot use Stdcall convention!",
8451 Get_Pragma_Arg (Arg1));
8452 end if;
8454 -- Set the convention
8456 Set_Convention (E, C);
8457 Set_Has_Convention_Pragma (E);
8459 -- For the case of a record base type, also set the convention of
8460 -- any anonymous access types declared in the record which do not
8461 -- currently have a specified convention.
8462 -- Similarly for an array base type and anonymous access types
8463 -- components.
8465 if Is_Base_Type (E) then
8466 if Is_Record_Type (E) then
8467 declare
8468 Comp : Node_Id;
8470 begin
8471 Comp := First_Component (E);
8472 while Present (Comp) loop
8473 if Present (Etype (Comp))
8474 and then
8475 Ekind (Etype (Comp)) in
8476 E_Anonymous_Access_Type |
8477 E_Anonymous_Access_Subprogram_Type
8478 and then not Has_Convention_Pragma (Comp)
8479 then
8480 Set_Convention (Comp, C);
8481 end if;
8483 Next_Component (Comp);
8484 end loop;
8485 end;
8487 elsif Is_Array_Type (E)
8488 and then Ekind (Component_Type (E)) in
8489 E_Anonymous_Access_Type |
8490 E_Anonymous_Access_Subprogram_Type
8491 then
8492 Set_Convention (Designated_Type (Component_Type (E)), C);
8493 end if;
8494 end if;
8496 -- Deal with incomplete/private type case, where underlying type
8497 -- is available, so set convention of that underlying type.
8499 if Is_Incomplete_Or_Private_Type (E)
8500 and then Present (Underlying_Type (E))
8501 then
8502 Set_Convention (Underlying_Type (E), C);
8503 Set_Has_Convention_Pragma (Underlying_Type (E), True);
8504 end if;
8506 -- A class-wide type should inherit the convention of the specific
8507 -- root type (although this isn't specified clearly by the RM).
8509 if Is_Type (E) and then Present (Class_Wide_Type (E)) then
8510 Set_Convention (Class_Wide_Type (E), C);
8511 end if;
8513 -- If the entity is a record type, then check for special case of
8514 -- C_Pass_By_Copy, which is treated the same as C except that the
8515 -- special record flag is set. This convention is only permitted
8516 -- on record types (see AI95-00131).
8518 if Cname = Name_C_Pass_By_Copy then
8519 if Is_Record_Type (E) then
8520 Set_C_Pass_By_Copy (Base_Type (E));
8521 elsif Is_Incomplete_Or_Private_Type (E)
8522 and then Is_Record_Type (Underlying_Type (E))
8523 then
8524 Set_C_Pass_By_Copy (Base_Type (Underlying_Type (E)));
8525 else
8526 Error_Pragma_Arg
8527 ("C_Pass_By_Copy convention allowed only for record type",
8528 Arg2);
8529 end if;
8530 end if;
8532 -- If the convention of a record type is changed (such as to C),
8533 -- this must override C_Pass_By_Copy if that flag was inherited
8534 -- from a parent type where the latter convention was specified,
8535 -- so we force the flag to False.
8537 if Cname /= Name_C_Pass_By_Copy and then Is_Record_Type (E) then
8538 Set_C_Pass_By_Copy (Base_Type (E), False);
8539 end if;
8541 -- If the entity is a derived boolean type, check for the special
8542 -- case of convention C, C++, or Fortran, where we consider any
8543 -- nonzero value to represent true.
8545 if Is_Discrete_Type (E)
8546 and then Root_Type (Etype (E)) = Standard_Boolean
8547 and then
8548 (C = Convention_C
8549 or else
8550 C = Convention_CPP
8551 or else
8552 C = Convention_Fortran)
8553 then
8554 Set_Nonzero_Is_True (Base_Type (E));
8555 end if;
8556 end Set_Convention_From_Pragma;
8558 -- Local variables
8560 Comp_Unit : Unit_Number_Type;
8561 E : Entity_Id;
8562 E1 : Entity_Id;
8563 Id : Node_Id;
8564 Subp : Entity_Id;
8566 -- Start of processing for Process_Convention
8568 begin
8569 Check_At_Least_N_Arguments (2);
8570 Check_Optional_Identifier (Arg1, Name_Convention);
8571 Check_Arg_Is_Identifier (Arg1);
8572 Cname := Chars (Get_Pragma_Arg (Arg1));
8574 -- C_Pass_By_Copy is treated as a synonym for convention C (this is
8575 -- tested again below to set the critical flag).
8577 if Cname = Name_C_Pass_By_Copy then
8578 C := Convention_C;
8580 -- Otherwise we must have something in the standard convention list
8582 elsif Is_Convention_Name (Cname) then
8583 C := Get_Convention_Id (Chars (Get_Pragma_Arg (Arg1)));
8585 -- Otherwise warn on unrecognized convention
8587 else
8588 if Warn_On_Export_Import then
8589 Error_Msg_N
8590 ("??unrecognized convention name, C assumed",
8591 Get_Pragma_Arg (Arg1));
8592 end if;
8594 C := Convention_C;
8595 end if;
8597 Check_Optional_Identifier (Arg2, Name_Entity);
8598 Check_Arg_Is_Local_Name (Arg2);
8600 Id := Get_Pragma_Arg (Arg2);
8601 Analyze (Id);
8603 if not Is_Entity_Name (Id) then
8604 Error_Pragma_Arg ("entity name required", Arg2);
8605 end if;
8607 E := Entity (Id);
8609 -- Set entity to return
8611 Ent := E;
8613 -- Ada_Pass_By_Copy special checking
8615 if C = Convention_Ada_Pass_By_Copy then
8616 if not Is_First_Subtype (E) then
8617 Error_Pragma_Arg
8618 ("convention `Ada_Pass_By_Copy` only allowed for types",
8619 Arg2);
8620 end if;
8622 if Is_By_Reference_Type (E) then
8623 Error_Pragma_Arg
8624 ("convention `Ada_Pass_By_Copy` not allowed for by-reference "
8625 & "type", Arg1);
8626 end if;
8628 -- Ada_Pass_By_Reference special checking
8630 elsif C = Convention_Ada_Pass_By_Reference then
8631 if not Is_First_Subtype (E) then
8632 Error_Pragma_Arg
8633 ("convention `Ada_Pass_By_Reference` only allowed for types",
8634 Arg2);
8635 end if;
8637 if Is_By_Copy_Type (E) then
8638 Error_Pragma_Arg
8639 ("convention `Ada_Pass_By_Reference` not allowed for by-copy "
8640 & "type", Arg1);
8641 end if;
8642 end if;
8644 -- Go to renamed subprogram if present, since convention applies to
8645 -- the actual renamed entity, not to the renaming entity. If the
8646 -- subprogram is inherited, go to parent subprogram.
8648 if Is_Subprogram (E)
8649 and then Present (Alias (E))
8650 then
8651 if Nkind (Parent (Declaration_Node (E))) =
8652 N_Subprogram_Renaming_Declaration
8653 then
8654 if Scope (E) /= Scope (Alias (E)) then
8655 Error_Pragma_Ref
8656 ("cannot apply pragma% to non-local entity&#", E);
8657 end if;
8659 E := Alias (E);
8661 elsif Nkind (Parent (E)) in
8662 N_Full_Type_Declaration | N_Private_Extension_Declaration
8663 and then Scope (E) = Scope (Alias (E))
8664 then
8665 E := Alias (E);
8667 -- Return the parent subprogram the entity was inherited from
8669 Ent := E;
8670 end if;
8671 end if;
8673 -- Check that we are not applying this to a specless body. Relax this
8674 -- check if Relaxed_RM_Semantics to accommodate other Ada compilers.
8676 if Is_Subprogram (E)
8677 and then Nkind (Parent (Declaration_Node (E))) = N_Subprogram_Body
8678 and then not Relaxed_RM_Semantics
8679 then
8680 Error_Pragma
8681 ("pragma% requires separate spec and must come before body");
8682 end if;
8684 -- Check that we are not applying this to a named constant
8686 if Is_Named_Number (E) then
8687 Error_Msg_Name_1 := Pname;
8688 Error_Msg_N
8689 ("cannot apply pragma% to named constant!",
8690 Get_Pragma_Arg (Arg2));
8691 Error_Pragma_Arg
8692 ("\supply appropriate type for&!", Arg2);
8693 end if;
8695 if Ekind (E) = E_Enumeration_Literal then
8696 Error_Pragma ("enumeration literal not allowed for pragma%");
8697 end if;
8699 -- Check for rep item appearing too early or too late
8701 if Etype (E) = Any_Type
8702 or else Rep_Item_Too_Early (E, N)
8703 then
8704 raise Pragma_Exit;
8706 elsif Present (Underlying_Type (E)) then
8707 E := Underlying_Type (E);
8708 end if;
8710 if Rep_Item_Too_Late (E, N) then
8711 raise Pragma_Exit;
8712 end if;
8714 if Has_Convention_Pragma (E) then
8715 Diagnose_Multiple_Pragmas (E);
8717 elsif Convention (E) = Convention_Protected
8718 or else Ekind (Scope (E)) = E_Protected_Type
8719 then
8720 Error_Pragma_Arg
8721 ("a protected operation cannot be given a different convention",
8722 Arg2);
8723 end if;
8725 -- For Intrinsic, a subprogram is required
8727 if C = Convention_Intrinsic
8728 and then not Is_Subprogram_Or_Generic_Subprogram (E)
8729 then
8730 -- Accept Intrinsic Export on types if Relaxed_RM_Semantics
8732 if not (Is_Type (E) and then Relaxed_RM_Semantics) then
8733 if From_Aspect_Specification (N) then
8734 Error_Pragma_Arg
8735 ("entity for aspect% must be a subprogram", Arg2);
8736 else
8737 Error_Pragma_Arg
8738 ("second argument of pragma% must be a subprogram", Arg2);
8739 end if;
8740 end if;
8742 -- Special checks for C_Variadic_n
8744 elsif C in Convention_C_Variadic then
8746 -- Several allowed cases
8748 if Is_Subprogram_Or_Generic_Subprogram (E) then
8749 Subp := E;
8751 -- An access to subprogram is also allowed
8753 elsif Is_Access_Type (E)
8754 and then Ekind (Designated_Type (E)) = E_Subprogram_Type
8755 then
8756 Subp := Designated_Type (E);
8758 -- Allow internal call to set convention of subprogram type
8760 elsif Ekind (E) = E_Subprogram_Type then
8761 Subp := E;
8763 else
8764 Error_Pragma_Arg
8765 ("argument of pragma% must be subprogram or access type",
8766 Arg2);
8767 end if;
8769 -- ISO C requires a named parameter before the ellipsis, so a
8770 -- variadic C function taking 0 fixed parameter cannot exist.
8772 if C = Convention_C_Variadic_0 then
8774 Error_Msg_N
8775 ("??C_Variadic_0 cannot be used for an 'I'S'O C function",
8776 Get_Pragma_Arg (Arg2));
8778 -- Now check the number of parameters of the subprogram and give
8779 -- an error if it is lower than n.
8781 elsif Present (Subp) then
8782 declare
8783 Minimum : constant Nat :=
8784 Convention_Id'Pos (C) -
8785 Convention_Id'Pos (Convention_C_Variadic_0);
8787 Count : Nat;
8788 Formal : Entity_Id;
8790 begin
8791 Count := 0;
8792 Formal := First_Formal (Subp);
8793 while Present (Formal) loop
8794 Count := Count + 1;
8795 Next_Formal (Formal);
8796 end loop;
8798 if Count < Minimum then
8799 Error_Msg_Uint_1 := UI_From_Int (Minimum);
8800 Error_Pragma_Arg
8801 ("argument of pragma% must have at least"
8802 & "^ parameters", Arg2);
8803 end if;
8804 end;
8805 end if;
8807 -- Special checks for Stdcall
8809 elsif C = Convention_Stdcall then
8811 -- Several allowed cases
8813 if Is_Subprogram_Or_Generic_Subprogram (E)
8815 -- A variable is OK
8817 or else Ekind (E) = E_Variable
8819 -- A component as well. The entity does not have its Ekind
8820 -- set until the enclosing record declaration is fully
8821 -- analyzed.
8823 or else Nkind (Parent (E)) = N_Component_Declaration
8825 -- An access to subprogram is also allowed
8827 or else
8828 (Is_Access_Type (E)
8829 and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
8831 -- Allow internal call to set convention of subprogram type
8833 or else Ekind (E) = E_Subprogram_Type
8834 then
8835 null;
8837 else
8838 Error_Pragma_Arg
8839 ("argument of pragma% must be subprogram or access type",
8840 Arg2);
8841 end if;
8842 end if;
8844 Set_Convention_From_Pragma (E);
8846 -- Deal with non-subprogram cases
8848 if not Is_Subprogram_Or_Generic_Subprogram (E) then
8849 if Is_Type (E) then
8851 -- The pragma must apply to a first subtype, but it can also
8852 -- apply to a generic type in a generic formal part, in which
8853 -- case it will also appear in the corresponding instance.
8855 if Is_Generic_Type (E) or else In_Instance then
8856 null;
8857 else
8858 Check_First_Subtype (Arg2);
8859 end if;
8861 Set_Convention_From_Pragma (Base_Type (E));
8863 -- For access subprograms, we must set the convention on the
8864 -- internally generated directly designated type as well.
8866 if Ekind (E) = E_Access_Subprogram_Type then
8867 Set_Convention_From_Pragma (Directly_Designated_Type (E));
8868 end if;
8869 end if;
8871 -- For the subprogram case, set proper convention for all homonyms
8872 -- in same scope and the same declarative part, i.e. the same
8873 -- compilation unit.
8875 else
8876 -- Treat a pragma Import as an implicit body, and pragma import
8877 -- as implicit reference (for navigation in GNAT Studio).
8879 if Prag_Id = Pragma_Import then
8880 Generate_Reference (E, Id, 'b');
8882 -- For exported entities we restrict the generation of references
8883 -- to entities exported to foreign languages since entities
8884 -- exported to Ada do not provide further information to
8885 -- GNAT Studio and add undesired references to the output of the
8886 -- gnatxref tool.
8888 elsif Prag_Id = Pragma_Export
8889 and then Convention (E) /= Convention_Ada
8890 then
8891 Generate_Reference (E, Id, 'i');
8892 end if;
8894 -- If the pragma comes from an aspect, it only applies to the
8895 -- given entity, not its homonyms.
8897 if From_Aspect_Specification (N) then
8898 if C = Convention_Intrinsic
8899 and then Nkind (Ent) = N_Defining_Operator_Symbol
8900 then
8901 if Is_Fixed_Point_Type (Etype (Ent))
8902 or else Is_Fixed_Point_Type (Etype (First_Entity (Ent)))
8903 or else Is_Fixed_Point_Type (Etype (Last_Entity (Ent)))
8904 then
8905 Error_Msg_N
8906 ("no intrinsic operator available for this fixed-point "
8907 & "operation", N);
8908 Error_Msg_N
8909 ("\use expression functions with the desired "
8910 & "conversions made explicit", N);
8911 end if;
8912 end if;
8914 return;
8915 end if;
8917 -- Otherwise Loop through the homonyms of the pragma argument's
8918 -- entity, an apply convention to those in the current scope.
8920 Comp_Unit := Get_Source_Unit (E);
8921 E1 := Ent;
8923 loop
8924 E1 := Homonym (E1);
8925 exit when No (E1) or else Scope (E1) /= Current_Scope;
8927 -- Ignore entry for which convention is already set
8929 if Has_Convention_Pragma (E1) then
8930 goto Continue;
8931 end if;
8933 if Is_Subprogram (E1)
8934 and then Nkind (Parent (Declaration_Node (E1))) =
8935 N_Subprogram_Body
8936 and then not Relaxed_RM_Semantics
8937 then
8938 Set_Has_Completion (E); -- to prevent cascaded error
8939 Error_Pragma_Ref
8940 ("pragma% requires separate spec and must come before "
8941 & "body#", E1);
8942 end if;
8944 -- Do not set the pragma on inherited operations or on formal
8945 -- subprograms.
8947 if Comes_From_Source (E1)
8948 and then Comp_Unit = Get_Source_Unit (E1)
8949 and then not Is_Formal_Subprogram (E1)
8950 and then Nkind (Original_Node (Parent (E1))) /=
8951 N_Full_Type_Declaration
8952 then
8953 if Present (Alias (E1))
8954 and then Scope (E1) /= Scope (Alias (E1))
8955 then
8956 Error_Pragma_Ref
8957 ("cannot apply pragma% to non-local entity& declared#",
8958 E1);
8959 end if;
8961 Set_Convention_From_Pragma (E1);
8963 if Prag_Id = Pragma_Import then
8964 Generate_Reference (E1, Id, 'b');
8965 end if;
8966 end if;
8968 <<Continue>>
8969 null;
8970 end loop;
8971 end if;
8972 end Process_Convention;
8974 ----------------------------------------
8975 -- Process_Disable_Enable_Atomic_Sync --
8976 ----------------------------------------
8978 procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id) is
8979 begin
8980 Check_No_Identifiers;
8981 Check_At_Most_N_Arguments (1);
8983 -- Modeled internally as
8984 -- pragma Suppress/Unsuppress (Atomic_Synchronization [,Entity])
8986 Rewrite (N,
8987 Make_Pragma (Loc,
8988 Chars => Nam,
8989 Pragma_Argument_Associations => New_List (
8990 Make_Pragma_Argument_Association (Loc,
8991 Expression =>
8992 Make_Identifier (Loc, Name_Atomic_Synchronization)))));
8994 if Present (Arg1) then
8995 Append_To (Pragma_Argument_Associations (N), New_Copy (Arg1));
8996 end if;
8998 Analyze (N);
8999 end Process_Disable_Enable_Atomic_Sync;
9001 -------------------------------------------------
9002 -- Process_Extended_Import_Export_Internal_Arg --
9003 -------------------------------------------------
9005 procedure Process_Extended_Import_Export_Internal_Arg
9006 (Arg_Internal : Node_Id := Empty)
9008 begin
9009 if No (Arg_Internal) then
9010 Error_Pragma ("Internal parameter required for pragma%");
9011 end if;
9013 if Nkind (Arg_Internal) = N_Identifier then
9014 null;
9016 elsif Nkind (Arg_Internal) = N_Operator_Symbol
9017 and then (Prag_Id = Pragma_Import_Function
9018 or else
9019 Prag_Id = Pragma_Export_Function)
9020 then
9021 null;
9023 else
9024 Error_Pragma_Arg
9025 ("wrong form for Internal parameter for pragma%", Arg_Internal);
9026 end if;
9028 Check_Arg_Is_Local_Name (Arg_Internal);
9029 end Process_Extended_Import_Export_Internal_Arg;
9031 --------------------------------------------------
9032 -- Process_Extended_Import_Export_Object_Pragma --
9033 --------------------------------------------------
9035 procedure Process_Extended_Import_Export_Object_Pragma
9036 (Arg_Internal : Node_Id;
9037 Arg_External : Node_Id;
9038 Arg_Size : Node_Id)
9040 Def_Id : Entity_Id;
9042 begin
9043 Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
9044 Def_Id := Entity (Arg_Internal);
9046 if Ekind (Def_Id) not in E_Constant | E_Variable then
9047 Error_Pragma_Arg
9048 ("pragma% must designate an object", Arg_Internal);
9049 end if;
9051 if Has_Rep_Pragma (Def_Id, Name_Common_Object)
9052 or else
9053 Has_Rep_Pragma (Def_Id, Name_Psect_Object)
9054 then
9055 Error_Pragma_Arg
9056 ("previous Common/Psect_Object applies, pragma % not permitted",
9057 Arg_Internal);
9058 end if;
9060 if Rep_Item_Too_Late (Def_Id, N) then
9061 raise Pragma_Exit;
9062 end if;
9064 Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
9066 if Present (Arg_Size) then
9067 Check_Arg_Is_External_Name (Arg_Size);
9068 end if;
9070 -- Export_Object case
9072 if Prag_Id = Pragma_Export_Object then
9073 if not Is_Library_Level_Entity (Def_Id) then
9074 Error_Pragma_Arg
9075 ("argument for pragma% must be library level entity",
9076 Arg_Internal);
9077 end if;
9079 if Ekind (Current_Scope) = E_Generic_Package then
9080 Error_Pragma ("pragma& cannot appear in a generic unit");
9081 end if;
9083 if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
9084 Error_Pragma_Arg
9085 ("exported object must have compile time known size",
9086 Arg_Internal);
9087 end if;
9089 if Warn_On_Export_Import and then Is_Exported (Def_Id) then
9090 Error_Msg_N ("??duplicate Export_Object pragma", N);
9091 else
9092 Set_Exported (Def_Id, Arg_Internal);
9093 end if;
9095 -- Import_Object case
9097 else
9098 if Is_Concurrent_Type (Etype (Def_Id)) then
9099 Error_Pragma_Arg
9100 ("cannot use pragma% for task/protected object",
9101 Arg_Internal);
9102 end if;
9104 if Ekind (Def_Id) = E_Constant then
9105 Error_Pragma_Arg
9106 ("cannot import a constant", Arg_Internal);
9107 end if;
9109 if Warn_On_Export_Import
9110 and then Has_Discriminants (Etype (Def_Id))
9111 then
9112 Error_Msg_N
9113 ("imported value must be initialized??", Arg_Internal);
9114 end if;
9116 if Warn_On_Export_Import
9117 and then Is_Access_Type (Etype (Def_Id))
9118 then
9119 Error_Pragma_Arg
9120 ("cannot import object of an access type??", Arg_Internal);
9121 end if;
9123 if Warn_On_Export_Import
9124 and then Is_Imported (Def_Id)
9125 then
9126 Error_Msg_N ("??duplicate Import_Object pragma", N);
9128 -- Check for explicit initialization present. Note that an
9129 -- initialization generated by the code generator, e.g. for an
9130 -- access type, does not count here.
9132 elsif Present (Expression (Parent (Def_Id)))
9133 and then
9134 Comes_From_Source
9135 (Original_Node (Expression (Parent (Def_Id))))
9136 then
9137 Error_Msg_Sloc := Sloc (Def_Id);
9138 Error_Pragma_Arg
9139 ("imported entities cannot be initialized (RM B.1(24))",
9140 "\no initialization allowed for & declared#", Arg1);
9141 else
9142 Set_Imported (Def_Id);
9143 Note_Possible_Modification (Arg_Internal, Sure => False);
9144 end if;
9145 end if;
9146 end Process_Extended_Import_Export_Object_Pragma;
9148 ------------------------------------------------------
9149 -- Process_Extended_Import_Export_Subprogram_Pragma --
9150 ------------------------------------------------------
9152 procedure Process_Extended_Import_Export_Subprogram_Pragma
9153 (Arg_Internal : Node_Id;
9154 Arg_External : Node_Id;
9155 Arg_Parameter_Types : Node_Id;
9156 Arg_Result_Type : Node_Id := Empty;
9157 Arg_Mechanism : Node_Id;
9158 Arg_Result_Mechanism : Node_Id := Empty)
9160 Ent : Entity_Id;
9161 Def_Id : Entity_Id;
9162 Hom_Id : Entity_Id;
9163 Formal : Entity_Id;
9164 Ambiguous : Boolean;
9165 Match : Boolean;
9167 function Same_Base_Type
9168 (Ptype : Node_Id;
9169 Formal : Entity_Id) return Boolean;
9170 -- Determines if Ptype references the type of Formal. Note that only
9171 -- the base types need to match according to the spec. Ptype here is
9172 -- the argument from the pragma, which is either a type name, or an
9173 -- access attribute.
9175 --------------------
9176 -- Same_Base_Type --
9177 --------------------
9179 function Same_Base_Type
9180 (Ptype : Node_Id;
9181 Formal : Entity_Id) return Boolean
9183 Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
9184 Pref : Node_Id;
9186 begin
9187 -- Case where pragma argument is typ'Access
9189 if Nkind (Ptype) = N_Attribute_Reference
9190 and then Attribute_Name (Ptype) = Name_Access
9191 then
9192 Pref := Prefix (Ptype);
9193 Find_Type (Pref);
9195 if not Is_Entity_Name (Pref)
9196 or else Entity (Pref) = Any_Type
9197 then
9198 raise Pragma_Exit;
9199 end if;
9201 -- We have a match if the corresponding argument is of an
9202 -- anonymous access type, and its designated type matches the
9203 -- type of the prefix of the access attribute
9205 return Ekind (Ftyp) = E_Anonymous_Access_Type
9206 and then Base_Type (Entity (Pref)) =
9207 Base_Type (Etype (Designated_Type (Ftyp)));
9209 -- Case where pragma argument is a type name
9211 else
9212 Find_Type (Ptype);
9214 if not Is_Entity_Name (Ptype)
9215 or else Entity (Ptype) = Any_Type
9216 then
9217 raise Pragma_Exit;
9218 end if;
9220 -- We have a match if the corresponding argument is of the type
9221 -- given in the pragma (comparing base types)
9223 return Base_Type (Entity (Ptype)) = Ftyp;
9224 end if;
9225 end Same_Base_Type;
9227 -- Start of processing for
9228 -- Process_Extended_Import_Export_Subprogram_Pragma
9230 begin
9231 Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
9232 Ent := Empty;
9233 Ambiguous := False;
9235 -- Loop through homonyms (overloadings) of the entity
9237 Hom_Id := Entity (Arg_Internal);
9238 while Present (Hom_Id) loop
9239 Def_Id := Get_Base_Subprogram (Hom_Id);
9241 -- We need a subprogram in the current scope
9243 if not Is_Subprogram (Def_Id)
9244 or else Scope (Def_Id) /= Current_Scope
9245 then
9246 null;
9248 else
9249 Match := True;
9251 -- Pragma cannot apply to subprogram body
9253 if Is_Subprogram (Def_Id)
9254 and then Nkind (Parent (Declaration_Node (Def_Id))) =
9255 N_Subprogram_Body
9256 then
9257 Error_Pragma
9258 ("pragma% requires separate spec and must come before "
9259 & "body");
9260 end if;
9262 -- Test result type if given, note that the result type
9263 -- parameter can only be present for the function cases.
9265 if Present (Arg_Result_Type)
9266 and then not Same_Base_Type (Arg_Result_Type, Def_Id)
9267 then
9268 Match := False;
9270 elsif Etype (Def_Id) /= Standard_Void_Type
9271 and then
9272 Pname in Name_Export_Procedure | Name_Import_Procedure
9273 then
9274 Match := False;
9276 -- Test parameter types if given. Note that this parameter has
9277 -- not been analyzed (and must not be, since it is semantic
9278 -- nonsense), so we get it as the parser left it.
9280 elsif Present (Arg_Parameter_Types) then
9281 Check_Matching_Types : declare
9282 Formal : Entity_Id;
9283 Ptype : Node_Id;
9285 begin
9286 Formal := First_Formal (Def_Id);
9288 if Nkind (Arg_Parameter_Types) = N_Null then
9289 if Present (Formal) then
9290 Match := False;
9291 end if;
9293 -- A list of one type, e.g. (List) is parsed as a
9294 -- parenthesized expression.
9296 elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
9297 and then Paren_Count (Arg_Parameter_Types) = 1
9298 then
9299 if No (Formal)
9300 or else Present (Next_Formal (Formal))
9301 then
9302 Match := False;
9303 else
9304 Match :=
9305 Same_Base_Type (Arg_Parameter_Types, Formal);
9306 end if;
9308 -- A list of more than one type is parsed as a aggregate
9310 elsif Nkind (Arg_Parameter_Types) = N_Aggregate
9311 and then Paren_Count (Arg_Parameter_Types) = 0
9312 then
9313 Ptype := First (Expressions (Arg_Parameter_Types));
9314 while Present (Ptype) or else Present (Formal) loop
9315 if No (Ptype)
9316 or else No (Formal)
9317 or else not Same_Base_Type (Ptype, Formal)
9318 then
9319 Match := False;
9320 exit;
9321 else
9322 Next_Formal (Formal);
9323 Next (Ptype);
9324 end if;
9325 end loop;
9327 -- Anything else is of the wrong form
9329 else
9330 Error_Pragma_Arg
9331 ("wrong form for Parameter_Types parameter",
9332 Arg_Parameter_Types);
9333 end if;
9334 end Check_Matching_Types;
9335 end if;
9337 -- Match is now False if the entry we found did not match
9338 -- either a supplied Parameter_Types or Result_Types argument
9340 if Match then
9341 if No (Ent) then
9342 Ent := Def_Id;
9344 -- Ambiguous case, the flag Ambiguous shows if we already
9345 -- detected this and output the initial messages.
9347 else
9348 if not Ambiguous then
9349 Ambiguous := True;
9350 Error_Msg_Name_1 := Pname;
9351 Error_Msg_N
9352 ("pragma% does not uniquely identify subprogram!",
9354 Error_Msg_Sloc := Sloc (Ent);
9355 Error_Msg_N ("matching subprogram #!", N);
9356 Ent := Empty;
9357 end if;
9359 Error_Msg_Sloc := Sloc (Def_Id);
9360 Error_Msg_N ("matching subprogram #!", N);
9361 end if;
9362 end if;
9363 end if;
9365 Hom_Id := Homonym (Hom_Id);
9366 end loop;
9368 -- See if we found an entry
9370 if No (Ent) then
9371 if not Ambiguous then
9372 if Is_Generic_Subprogram (Entity (Arg_Internal)) then
9373 Error_Pragma
9374 ("pragma% cannot be given for generic subprogram");
9375 else
9376 Error_Pragma
9377 ("pragma% does not identify local subprogram");
9378 end if;
9379 end if;
9381 return;
9382 end if;
9384 -- Import pragmas must be for imported entities
9386 if Prag_Id = Pragma_Import_Function
9387 or else
9388 Prag_Id = Pragma_Import_Procedure
9389 or else
9390 Prag_Id = Pragma_Import_Valued_Procedure
9391 then
9392 if not Is_Imported (Ent) then
9393 Error_Pragma
9394 ("pragma Import or Interface must precede pragma%");
9395 end if;
9397 -- Here we have the Export case which can set the entity as exported
9399 -- But does not do so if the specified external name is null, since
9400 -- that is taken as a signal in DEC Ada 83 (with which we want to be
9401 -- compatible) to request no external name.
9403 elsif Nkind (Arg_External) = N_String_Literal
9404 and then String_Length (Strval (Arg_External)) = 0
9405 then
9406 null;
9408 -- In all other cases, set entity as exported
9410 else
9411 Set_Exported (Ent, Arg_Internal);
9412 end if;
9414 -- Special processing for Valued_Procedure cases
9416 if Prag_Id = Pragma_Import_Valued_Procedure
9417 or else
9418 Prag_Id = Pragma_Export_Valued_Procedure
9419 then
9420 Formal := First_Formal (Ent);
9422 if No (Formal) then
9423 Error_Pragma ("at least one parameter required for pragma%");
9425 elsif Ekind (Formal) /= E_Out_Parameter then
9426 Error_Pragma ("first parameter must have mode OUT for pragma%");
9428 else
9429 Set_Is_Valued_Procedure (Ent);
9430 end if;
9431 end if;
9433 Set_Extended_Import_Export_External_Name (Ent, Arg_External);
9435 -- Process Result_Mechanism argument if present. We have already
9436 -- checked that this is only allowed for the function case.
9438 if Present (Arg_Result_Mechanism) then
9439 Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
9440 end if;
9442 -- Process Mechanism parameter if present. Note that this parameter
9443 -- is not analyzed, and must not be analyzed since it is semantic
9444 -- nonsense, so we get it in exactly as the parser left it.
9446 if Present (Arg_Mechanism) then
9447 declare
9448 Formal : Entity_Id;
9449 Massoc : Node_Id;
9450 Mname : Node_Id;
9451 Choice : Node_Id;
9453 begin
9454 -- A single mechanism association without a formal parameter
9455 -- name is parsed as a parenthesized expression. All other
9456 -- cases are parsed as aggregates, so we rewrite the single
9457 -- parameter case as an aggregate for consistency.
9459 if Nkind (Arg_Mechanism) /= N_Aggregate
9460 and then Paren_Count (Arg_Mechanism) = 1
9461 then
9462 Rewrite (Arg_Mechanism,
9463 Make_Aggregate (Sloc (Arg_Mechanism),
9464 Expressions => New_List (
9465 Relocate_Node (Arg_Mechanism))));
9466 end if;
9468 -- Case of only mechanism name given, applies to all formals
9470 if Nkind (Arg_Mechanism) /= N_Aggregate then
9471 Formal := First_Formal (Ent);
9472 while Present (Formal) loop
9473 Set_Mechanism_Value (Formal, Arg_Mechanism);
9474 Next_Formal (Formal);
9475 end loop;
9477 -- Case of list of mechanism associations given
9479 else
9480 if Null_Record_Present (Arg_Mechanism) then
9481 Error_Pragma_Arg
9482 ("inappropriate form for Mechanism parameter",
9483 Arg_Mechanism);
9484 end if;
9486 -- Deal with positional ones first
9488 Formal := First_Formal (Ent);
9490 if Present (Expressions (Arg_Mechanism)) then
9491 Mname := First (Expressions (Arg_Mechanism));
9492 while Present (Mname) loop
9493 if No (Formal) then
9494 Error_Pragma_Arg
9495 ("too many mechanism associations", Mname);
9496 end if;
9498 Set_Mechanism_Value (Formal, Mname);
9499 Next_Formal (Formal);
9500 Next (Mname);
9501 end loop;
9502 end if;
9504 -- Deal with named entries
9506 if Present (Component_Associations (Arg_Mechanism)) then
9507 Massoc := First (Component_Associations (Arg_Mechanism));
9508 while Present (Massoc) loop
9509 Choice := First (Choices (Massoc));
9511 if Nkind (Choice) /= N_Identifier
9512 or else Present (Next (Choice))
9513 then
9514 Error_Pragma_Arg
9515 ("incorrect form for mechanism association",
9516 Massoc);
9517 end if;
9519 Formal := First_Formal (Ent);
9520 loop
9521 if No (Formal) then
9522 Error_Pragma_Arg
9523 ("parameter name & not present", Choice);
9524 end if;
9526 if Chars (Choice) = Chars (Formal) then
9527 Set_Mechanism_Value
9528 (Formal, Expression (Massoc));
9530 -- Set entity on identifier for proper tree
9531 -- structure.
9533 Set_Entity (Choice, Formal);
9535 exit;
9536 end if;
9538 Next_Formal (Formal);
9539 end loop;
9541 Next (Massoc);
9542 end loop;
9543 end if;
9544 end if;
9545 end;
9546 end if;
9547 end Process_Extended_Import_Export_Subprogram_Pragma;
9549 --------------------------
9550 -- Process_Generic_List --
9551 --------------------------
9553 procedure Process_Generic_List is
9554 Arg : Node_Id;
9555 Exp : Node_Id;
9557 begin
9558 Check_No_Identifiers;
9559 Check_At_Least_N_Arguments (1);
9561 -- Check all arguments are names of generic units or instances
9563 Arg := Arg1;
9564 while Present (Arg) loop
9565 Exp := Get_Pragma_Arg (Arg);
9566 Analyze (Exp);
9568 if not Is_Entity_Name (Exp)
9569 or else
9570 (not Is_Generic_Instance (Entity (Exp))
9571 and then
9572 not Is_Generic_Unit (Entity (Exp)))
9573 then
9574 Error_Pragma_Arg
9575 ("pragma% argument must be name of generic unit/instance",
9576 Arg);
9577 end if;
9579 Next (Arg);
9580 end loop;
9581 end Process_Generic_List;
9583 ------------------------------------
9584 -- Process_Import_Predefined_Type --
9585 ------------------------------------
9587 procedure Process_Import_Predefined_Type is
9588 Loc : constant Source_Ptr := Sloc (N);
9589 Elmt : Elmt_Id;
9590 Ftyp : Node_Id := Empty;
9591 Decl : Node_Id;
9592 Def : Node_Id;
9593 Nam : Name_Id;
9595 begin
9596 Nam := String_To_Name (Strval (Expression (Arg3)));
9598 Elmt := First_Elmt (Predefined_Float_Types);
9599 while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
9600 Next_Elmt (Elmt);
9601 end loop;
9603 Ftyp := Node (Elmt);
9605 if Present (Ftyp) then
9607 -- Don't build a derived type declaration, because predefined C
9608 -- types have no declaration anywhere, so cannot really be named.
9609 -- Instead build a full type declaration, starting with an
9610 -- appropriate type definition is built
9612 if Is_Floating_Point_Type (Ftyp) then
9613 Def := Make_Floating_Point_Definition (Loc,
9614 Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
9615 Make_Real_Range_Specification (Loc,
9616 Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
9617 Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
9619 -- Should never have a predefined type we cannot handle
9621 else
9622 raise Program_Error;
9623 end if;
9625 -- Build and insert a Full_Type_Declaration, which will be
9626 -- analyzed as soon as this list entry has been analyzed.
9628 Decl := Make_Full_Type_Declaration (Loc,
9629 Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
9630 Type_Definition => Def);
9632 Insert_After (N, Decl);
9633 Mark_Rewrite_Insertion (Decl);
9635 else
9636 Error_Pragma_Arg ("no matching type found for pragma%", Arg2);
9637 end if;
9638 end Process_Import_Predefined_Type;
9640 ---------------------------------
9641 -- Process_Import_Or_Interface --
9642 ---------------------------------
9644 procedure Process_Import_Or_Interface is
9645 C : Convention_Id;
9646 Def_Id : Entity_Id;
9647 Hom_Id : Entity_Id;
9649 begin
9650 -- In Relaxed_RM_Semantics, support old Ada 83 style:
9651 -- pragma Import (Entity, "external name");
9653 if Relaxed_RM_Semantics
9654 and then Arg_Count = 2
9655 and then Prag_Id = Pragma_Import
9656 and then Nkind (Expression (Arg2)) = N_String_Literal
9657 then
9658 C := Convention_C;
9659 Def_Id := Get_Pragma_Arg (Arg1);
9660 Analyze (Def_Id);
9662 if not Is_Entity_Name (Def_Id) then
9663 Error_Pragma_Arg ("entity name required", Arg1);
9664 end if;
9666 Def_Id := Entity (Def_Id);
9667 Kill_Size_Check_Code (Def_Id);
9668 if Ekind (Def_Id) /= E_Constant then
9669 Note_Possible_Modification
9670 (Get_Pragma_Arg (Arg1), Sure => False);
9671 end if;
9673 else
9674 Process_Convention (C, Def_Id);
9676 -- A pragma that applies to a Ghost entity becomes Ghost for the
9677 -- purposes of legality checks and removal of ignored Ghost code.
9679 Mark_Ghost_Pragma (N, Def_Id);
9680 Kill_Size_Check_Code (Def_Id);
9681 if Ekind (Def_Id) /= E_Constant then
9682 Note_Possible_Modification
9683 (Get_Pragma_Arg (Arg2), Sure => False);
9684 end if;
9685 end if;
9687 -- Various error checks
9689 if Ekind (Def_Id) in E_Variable | E_Constant then
9691 -- We do not permit Import to apply to a renaming declaration
9693 if Present (Renamed_Object (Def_Id)) then
9694 Error_Pragma_Arg
9695 ("pragma% not allowed for object renaming", Arg2);
9697 -- User initialization is not allowed for imported object, but
9698 -- the object declaration may contain a default initialization,
9699 -- that will be discarded. Note that an explicit initialization
9700 -- only counts if it comes from source, otherwise it is simply
9701 -- the code generator making an implicit initialization explicit.
9703 elsif Present (Expression (Parent (Def_Id)))
9704 and then Comes_From_Source
9705 (Original_Node (Expression (Parent (Def_Id))))
9706 then
9707 -- Set imported flag to prevent cascaded errors
9709 Set_Is_Imported (Def_Id);
9711 Error_Msg_Sloc := Sloc (Def_Id);
9712 Error_Pragma_Arg
9713 ("no initialization allowed for declaration of& #",
9714 "\imported entities cannot be initialized (RM B.1(24))",
9715 Arg2);
9717 else
9718 -- If the pragma comes from an aspect specification the
9719 -- Is_Imported flag has already been set.
9721 if not From_Aspect_Specification (N) then
9722 Set_Imported (Def_Id);
9723 end if;
9725 Process_Interface_Name (Def_Id, Arg3, Arg4, N);
9727 -- Note that we do not set Is_Public here. That's because we
9728 -- only want to set it if there is no address clause, and we
9729 -- don't know that yet, so we delay that processing till
9730 -- freeze time.
9732 -- pragma Import completes deferred constants
9734 if Ekind (Def_Id) = E_Constant then
9735 Set_Has_Completion (Def_Id);
9736 end if;
9738 -- It is not possible to import a constant of an unconstrained
9739 -- array type (e.g. string) because there is no simple way to
9740 -- write a meaningful subtype for it.
9742 if Is_Array_Type (Etype (Def_Id))
9743 and then not Is_Constrained (Etype (Def_Id))
9744 then
9745 Error_Msg_NE
9746 ("imported constant& must have a constrained subtype",
9747 N, Def_Id);
9748 end if;
9749 end if;
9751 elsif Is_Subprogram_Or_Generic_Subprogram (Def_Id) then
9753 -- If the name is overloaded, pragma applies to all of the denoted
9754 -- entities in the same declarative part, unless the pragma comes
9755 -- from an aspect specification or was generated by the compiler
9756 -- (such as for pragma Provide_Shift_Operators).
9758 Hom_Id := Def_Id;
9759 while Present (Hom_Id) loop
9761 Def_Id := Get_Base_Subprogram (Hom_Id);
9763 -- Ignore inherited subprograms because the pragma will apply
9764 -- to the parent operation, which is the one called.
9766 if Is_Overloadable (Def_Id)
9767 and then Present (Alias (Def_Id))
9768 then
9769 null;
9771 -- If it is not a subprogram, it must be in an outer scope and
9772 -- pragma does not apply.
9774 elsif not Is_Subprogram_Or_Generic_Subprogram (Def_Id) then
9775 null;
9777 -- The pragma does not apply to primitives of interfaces
9779 elsif Is_Dispatching_Operation (Def_Id)
9780 and then Present (Find_Dispatching_Type (Def_Id))
9781 and then Is_Interface (Find_Dispatching_Type (Def_Id))
9782 then
9783 null;
9785 -- Verify that the homonym is in the same declarative part (not
9786 -- just the same scope). If the pragma comes from an aspect
9787 -- specification we know that it is part of the declaration.
9789 elsif (No (Unit_Declaration_Node (Def_Id))
9790 or else Parent (Unit_Declaration_Node (Def_Id)) /=
9791 Parent (N))
9792 and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
9793 and then not From_Aspect_Specification (N)
9794 then
9795 exit;
9797 else
9798 -- If the pragma comes from an aspect specification the
9799 -- Is_Imported flag has already been set.
9801 if not From_Aspect_Specification (N) then
9802 Set_Imported (Def_Id);
9803 end if;
9805 -- Reject an Import applied to an abstract subprogram
9807 if Is_Subprogram (Def_Id)
9808 and then Is_Abstract_Subprogram (Def_Id)
9809 then
9810 Error_Msg_Sloc := Sloc (Def_Id);
9811 Error_Msg_NE
9812 ("cannot import abstract subprogram& declared#",
9813 Arg2, Def_Id);
9814 end if;
9816 -- Special processing for Convention_Intrinsic
9818 if C = Convention_Intrinsic then
9820 -- Link_Name argument not allowed for intrinsic
9822 Check_No_Link_Name;
9824 Set_Is_Intrinsic_Subprogram (Def_Id);
9826 -- If no external name is present, then check that this
9827 -- is a valid intrinsic subprogram. If an external name
9828 -- is present, then this is handled by the back end.
9830 if No (Arg3) then
9831 Check_Intrinsic_Subprogram
9832 (Def_Id, Get_Pragma_Arg (Arg2));
9833 end if;
9834 end if;
9836 -- Verify that the subprogram does not have a completion
9837 -- through a renaming declaration. For other completions the
9838 -- pragma appears as a too late representation.
9840 declare
9841 Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
9843 begin
9844 if Present (Decl)
9845 and then Nkind (Decl) = N_Subprogram_Declaration
9846 and then Present (Corresponding_Body (Decl))
9847 and then Nkind (Unit_Declaration_Node
9848 (Corresponding_Body (Decl))) =
9849 N_Subprogram_Renaming_Declaration
9850 then
9851 Error_Msg_Sloc := Sloc (Def_Id);
9852 Error_Msg_NE
9853 ("cannot import&, renaming already provided for "
9854 & "declaration #", N, Def_Id);
9855 end if;
9856 end;
9858 -- If the pragma comes from an aspect specification, there
9859 -- must be an Import aspect specified as well. In the rare
9860 -- case where Import is set to False, the subprogram needs
9861 -- to have a local completion.
9863 declare
9864 Imp_Aspect : constant Node_Id :=
9865 Find_Aspect (Def_Id, Aspect_Import);
9866 Expr : Node_Id;
9868 begin
9869 if Present (Imp_Aspect)
9870 and then Present (Expression (Imp_Aspect))
9871 then
9872 Expr := Expression (Imp_Aspect);
9873 Analyze_And_Resolve (Expr, Standard_Boolean);
9875 if Is_Entity_Name (Expr)
9876 and then Entity (Expr) = Standard_True
9877 then
9878 Set_Has_Completion (Def_Id);
9879 end if;
9881 -- If there is no expression, the default is True, as for
9882 -- all boolean aspects. Same for the older pragma.
9884 else
9885 Set_Has_Completion (Def_Id);
9886 end if;
9887 end;
9889 Process_Interface_Name (Def_Id, Arg3, Arg4, N);
9890 end if;
9892 if Is_Compilation_Unit (Hom_Id) then
9894 -- Its possible homonyms are not affected by the pragma.
9895 -- Such homonyms might be present in the context of other
9896 -- units being compiled.
9898 exit;
9900 elsif From_Aspect_Specification (N) then
9901 exit;
9903 -- If the pragma was created by the compiler, then we don't
9904 -- want it to apply to other homonyms. This kind of case can
9905 -- occur when using pragma Provide_Shift_Operators, which
9906 -- generates implicit shift and rotate operators with Import
9907 -- pragmas that might apply to earlier explicit or implicit
9908 -- declarations marked with Import (for example, coming from
9909 -- an earlier pragma Provide_Shift_Operators for another type),
9910 -- and we don't generally want other homonyms being treated
9911 -- as imported or the pragma flagged as an illegal duplicate.
9913 elsif not Comes_From_Source (N) then
9914 exit;
9916 else
9917 Hom_Id := Homonym (Hom_Id);
9918 end if;
9919 end loop;
9921 -- Import a CPP class
9923 elsif C = Convention_CPP
9924 and then (Is_Record_Type (Def_Id)
9925 or else Ekind (Def_Id) = E_Incomplete_Type)
9926 then
9927 if Ekind (Def_Id) = E_Incomplete_Type then
9928 if Present (Full_View (Def_Id)) then
9929 Def_Id := Full_View (Def_Id);
9931 else
9932 Error_Msg_N
9933 ("cannot import 'C'P'P type before full declaration seen",
9934 Get_Pragma_Arg (Arg2));
9936 -- Although we have reported the error we decorate it as
9937 -- CPP_Class to avoid reporting spurious errors
9939 Set_Is_CPP_Class (Def_Id);
9940 return;
9941 end if;
9942 end if;
9944 -- Types treated as CPP classes must be declared limited (note:
9945 -- this used to be a warning but there is no real benefit to it
9946 -- since we did effectively intend to treat the type as limited
9947 -- anyway).
9949 if not Is_Limited_Type (Def_Id) then
9950 Error_Msg_N
9951 ("imported 'C'P'P type must be limited",
9952 Get_Pragma_Arg (Arg2));
9953 end if;
9955 if Etype (Def_Id) /= Def_Id
9956 and then not Is_CPP_Class (Root_Type (Def_Id))
9957 then
9958 Error_Msg_N ("root type must be a 'C'P'P type", Arg1);
9959 end if;
9961 Set_Is_CPP_Class (Def_Id);
9963 -- Imported CPP types must not have discriminants (because C++
9964 -- classes do not have discriminants).
9966 if Has_Discriminants (Def_Id) then
9967 Error_Msg_N
9968 ("imported 'C'P'P type cannot have discriminants",
9969 First (Discriminant_Specifications
9970 (Declaration_Node (Def_Id))));
9971 end if;
9973 -- Check that components of imported CPP types do not have default
9974 -- expressions. For private types this check is performed when the
9975 -- full view is analyzed (see Process_Full_View).
9977 if not Is_Private_Type (Def_Id) then
9978 Check_CPP_Type_Has_No_Defaults (Def_Id);
9979 end if;
9981 -- Import a CPP exception
9983 elsif C = Convention_CPP
9984 and then Ekind (Def_Id) = E_Exception
9985 then
9986 if No (Arg3) then
9987 Error_Pragma_Arg
9988 ("'External_'Name arguments is required for 'Cpp exception",
9989 Arg3);
9990 else
9991 -- As only a string is allowed, Check_Arg_Is_External_Name
9992 -- isn't called.
9994 Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
9995 end if;
9997 if Present (Arg4) then
9998 Error_Pragma_Arg
9999 ("Link_Name argument not allowed for imported Cpp exception",
10000 Arg4);
10001 end if;
10003 -- Do not call Set_Interface_Name as the name of the exception
10004 -- shouldn't be modified (and in particular it shouldn't be
10005 -- the External_Name). For exceptions, the External_Name is the
10006 -- name of the RTTI structure.
10008 -- ??? Emit an error if pragma Import/Export_Exception is present
10010 elsif Nkind (Parent (Def_Id)) = N_Incomplete_Type_Declaration then
10011 Check_No_Link_Name;
10012 Check_Arg_Count (3);
10013 Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
10015 Process_Import_Predefined_Type;
10017 -- Emit an error unless Relaxed_RM_Semantics since some legacy Ada
10018 -- compilers may accept more cases, e.g. JGNAT allowed importing
10019 -- a Java package.
10021 elsif not Relaxed_RM_Semantics then
10022 if From_Aspect_Specification (N) then
10023 Error_Pragma_Arg
10024 ("entity for aspect% must be object, subprogram "
10025 & "or incomplete type",
10026 Arg2);
10027 else
10028 Error_Pragma_Arg
10029 ("second argument of pragma% must be object, subprogram "
10030 & "or incomplete type",
10031 Arg2);
10032 end if;
10033 end if;
10035 -- If this pragma applies to a compilation unit, then the unit, which
10036 -- is a subprogram, does not require (or allow) a body. We also do
10037 -- not need to elaborate imported procedures.
10039 if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
10040 declare
10041 Cunit : constant Node_Id := Parent (Parent (N));
10042 begin
10043 Set_Body_Required (Cunit, False);
10044 end;
10045 end if;
10046 end Process_Import_Or_Interface;
10048 --------------------
10049 -- Process_Inline --
10050 --------------------
10052 procedure Process_Inline (Status : Inline_Status) is
10053 Applies : Boolean;
10054 Assoc : Node_Id;
10055 Decl : Node_Id;
10056 Subp : Entity_Id;
10057 Subp_Id : Node_Id;
10059 Ghost_Error_Posted : Boolean := False;
10060 -- Flag set when an error concerning the illegal mix of Ghost and
10061 -- non-Ghost subprograms is emitted.
10063 Ghost_Id : Entity_Id := Empty;
10064 -- The entity of the first Ghost subprogram encountered while
10065 -- processing the arguments of the pragma.
10067 procedure Check_Inline_Always_Placement (Spec_Id : Entity_Id);
10068 -- Verify the placement of pragma Inline_Always with respect to the
10069 -- initial declaration of subprogram Spec_Id.
10071 function Inlining_Not_Possible (Subp : Entity_Id) return Boolean;
10072 -- Returns True if it can be determined at this stage that inlining
10073 -- is not possible, for example if the body is available and contains
10074 -- exception handlers, we prevent inlining, since otherwise we can
10075 -- get undefined symbols at link time. This function also emits a
10076 -- warning if the pragma appears too late.
10078 -- ??? is business with link symbols still valid, or does it relate
10079 -- to front end ZCX which is being phased out ???
10081 procedure Make_Inline (Subp : Entity_Id);
10082 -- Subp is the defining unit name of the subprogram declaration. If
10083 -- the pragma is valid, call Set_Inline_Flags on Subp, as well as on
10084 -- the corresponding body, if there is one present.
10086 procedure Set_Inline_Flags (Subp : Entity_Id);
10087 -- Set Has_Pragma_{No_Inline,Inline,Inline_Always} flag on Subp.
10088 -- Also set or clear Is_Inlined flag on Subp depending on Status.
10090 -----------------------------------
10091 -- Check_Inline_Always_Placement --
10092 -----------------------------------
10094 procedure Check_Inline_Always_Placement (Spec_Id : Entity_Id) is
10095 Spec_Decl : constant Node_Id := Unit_Declaration_Node (Spec_Id);
10097 function Compilation_Unit_OK return Boolean;
10098 pragma Inline (Compilation_Unit_OK);
10099 -- Determine whether pragma Inline_Always applies to a compatible
10100 -- compilation unit denoted by Spec_Id.
10102 function Declarative_List_OK return Boolean;
10103 pragma Inline (Declarative_List_OK);
10104 -- Determine whether the initial declaration of subprogram Spec_Id
10105 -- and the pragma appear in compatible declarative lists.
10107 function Subprogram_Body_OK return Boolean;
10108 pragma Inline (Subprogram_Body_OK);
10109 -- Determine whether pragma Inline_Always applies to a compatible
10110 -- subprogram body denoted by Spec_Id.
10112 -------------------------
10113 -- Compilation_Unit_OK --
10114 -------------------------
10116 function Compilation_Unit_OK return Boolean is
10117 Comp_Unit : constant Node_Id := Parent (Spec_Decl);
10119 begin
10120 -- The pragma appears after the initial declaration of a
10121 -- compilation unit.
10123 -- procedure Comp_Unit;
10124 -- pragma Inline_Always (Comp_Unit);
10126 -- Note that for compatibility reasons, the following case is
10127 -- also accepted.
10129 -- procedure Stand_Alone_Body_Comp_Unit is
10130 -- ...
10131 -- end Stand_Alone_Body_Comp_Unit;
10132 -- pragma Inline_Always (Stand_Alone_Body_Comp_Unit);
10134 return
10135 Nkind (Comp_Unit) = N_Compilation_Unit
10136 and then Present (Aux_Decls_Node (Comp_Unit))
10137 and then Is_List_Member (N)
10138 and then List_Containing (N) =
10139 Pragmas_After (Aux_Decls_Node (Comp_Unit));
10140 end Compilation_Unit_OK;
10142 -------------------------
10143 -- Declarative_List_OK --
10144 -------------------------
10146 function Declarative_List_OK return Boolean is
10147 Context : constant Node_Id := Parent (Spec_Decl);
10149 Init_Decl : Node_Id;
10150 Init_List : List_Id;
10151 Prag_List : List_Id;
10153 begin
10154 -- Determine the proper initial declaration. In general this is
10155 -- the declaration node of the subprogram except when the input
10156 -- denotes a generic instantiation.
10158 -- procedure Inst is new Gen;
10159 -- pragma Inline_Always (Inst);
10161 -- In this case the original subprogram is moved inside an
10162 -- anonymous package while pragma Inline_Always remains at the
10163 -- level of the anonymous package. Use the declaration of the
10164 -- package because it reflects the placement of the original
10165 -- instantiation.
10167 -- package Anon_Pack is
10168 -- procedure Inst is ... end Inst; -- original
10169 -- end Anon_Pack;
10171 -- procedure Inst renames Anon_Pack.Inst;
10172 -- pragma Inline_Always (Inst);
10174 if Is_Generic_Instance (Spec_Id) then
10175 Init_Decl := Parent (Parent (Spec_Decl));
10176 pragma Assert (Nkind (Init_Decl) = N_Package_Declaration);
10177 else
10178 Init_Decl := Spec_Decl;
10179 end if;
10181 if Is_List_Member (Init_Decl) and then Is_List_Member (N) then
10182 Init_List := List_Containing (Init_Decl);
10183 Prag_List := List_Containing (N);
10185 -- The pragma and then initial declaration appear within the
10186 -- same declarative list.
10188 if Init_List = Prag_List then
10189 return True;
10191 -- A special case of the above is when both the pragma and
10192 -- the initial declaration appear in different lists of a
10193 -- package spec, protected definition, or a task definition.
10195 -- package Pack is
10196 -- procedure Proc;
10197 -- private
10198 -- pragma Inline_Always (Proc);
10199 -- end Pack;
10201 elsif Nkind (Context) in N_Package_Specification
10202 | N_Protected_Definition
10203 | N_Task_Definition
10204 and then Init_List = Visible_Declarations (Context)
10205 and then Prag_List = Private_Declarations (Context)
10206 then
10207 return True;
10208 end if;
10209 end if;
10211 return False;
10212 end Declarative_List_OK;
10214 ------------------------
10215 -- Subprogram_Body_OK --
10216 ------------------------
10218 function Subprogram_Body_OK return Boolean is
10219 Body_Decl : Node_Id;
10221 begin
10222 -- The pragma appears within the declarative list of a stand-
10223 -- alone subprogram body.
10225 -- procedure Stand_Alone_Body is
10226 -- pragma Inline_Always (Stand_Alone_Body);
10227 -- begin
10228 -- ...
10229 -- end Stand_Alone_Body;
10231 -- The compiler creates a dummy spec in this case, however the
10232 -- pragma remains within the declarative list of the body.
10234 if Nkind (Spec_Decl) = N_Subprogram_Declaration
10235 and then not Comes_From_Source (Spec_Decl)
10236 and then Present (Corresponding_Body (Spec_Decl))
10237 then
10238 Body_Decl :=
10239 Unit_Declaration_Node (Corresponding_Body (Spec_Decl));
10241 if Present (Declarations (Body_Decl))
10242 and then Is_List_Member (N)
10243 and then List_Containing (N) = Declarations (Body_Decl)
10244 then
10245 return True;
10246 end if;
10247 end if;
10249 return False;
10250 end Subprogram_Body_OK;
10252 -- Start of processing for Check_Inline_Always_Placement
10254 begin
10255 -- This check is relevant only for pragma Inline_Always
10257 if Pname /= Name_Inline_Always then
10258 return;
10260 -- Nothing to do when the pragma is internally generated on the
10261 -- assumption that it is properly placed.
10263 elsif not Comes_From_Source (N) then
10264 return;
10266 -- Nothing to do for internally generated subprograms that act
10267 -- as accidental homonyms of a source subprogram being inlined.
10269 elsif not Comes_From_Source (Spec_Id) then
10270 return;
10272 -- Nothing to do for generic formal subprograms that act as
10273 -- homonyms of another source subprogram being inlined.
10275 elsif Is_Formal_Subprogram (Spec_Id) then
10276 return;
10278 elsif Compilation_Unit_OK
10279 or else Declarative_List_OK
10280 or else Subprogram_Body_OK
10281 then
10282 return;
10283 end if;
10285 -- At this point it is known that the pragma applies to or appears
10286 -- within a completing body, a completing stub, or a subunit.
10288 Error_Msg_Name_1 := Pname;
10289 Error_Msg_Name_2 := Chars (Spec_Id);
10290 Error_Msg_Sloc := Sloc (Spec_Id);
10292 Error_Msg_N
10293 ("pragma % must appear on initial declaration of subprogram "
10294 & "% defined #", N);
10295 end Check_Inline_Always_Placement;
10297 ---------------------------
10298 -- Inlining_Not_Possible --
10299 ---------------------------
10301 function Inlining_Not_Possible (Subp : Entity_Id) return Boolean is
10302 Decl : constant Node_Id := Unit_Declaration_Node (Subp);
10303 Stats : Node_Id;
10305 begin
10306 if Nkind (Decl) = N_Subprogram_Body then
10307 Stats := Handled_Statement_Sequence (Decl);
10308 return Present (Exception_Handlers (Stats))
10309 or else Present (At_End_Proc (Stats));
10311 elsif Nkind (Decl) = N_Subprogram_Declaration
10312 and then Present (Corresponding_Body (Decl))
10313 then
10314 if Analyzed (Corresponding_Body (Decl)) then
10315 Error_Msg_N ("pragma appears too late, ignored??", N);
10316 return True;
10318 -- If the subprogram is a renaming as body, the body is just a
10319 -- call to the renamed subprogram, and inlining is trivially
10320 -- possible.
10322 elsif
10323 Nkind (Unit_Declaration_Node (Corresponding_Body (Decl))) =
10324 N_Subprogram_Renaming_Declaration
10325 then
10326 return False;
10328 else
10329 Stats :=
10330 Handled_Statement_Sequence
10331 (Unit_Declaration_Node (Corresponding_Body (Decl)));
10333 return
10334 Present (Exception_Handlers (Stats))
10335 or else Present (At_End_Proc (Stats));
10336 end if;
10338 else
10339 -- If body is not available, assume the best, the check is
10340 -- performed again when compiling enclosing package bodies.
10342 return False;
10343 end if;
10344 end Inlining_Not_Possible;
10346 -----------------
10347 -- Make_Inline --
10348 -----------------
10350 procedure Make_Inline (Subp : Entity_Id) is
10351 Kind : constant Entity_Kind := Ekind (Subp);
10352 Inner_Subp : Entity_Id := Subp;
10354 begin
10355 -- Ignore if bad type, avoid cascaded error
10357 if Etype (Subp) = Any_Type then
10358 Applies := True;
10359 return;
10361 -- If inlining is not possible, for now do not treat as an error
10363 elsif Status /= Suppressed
10364 and then Front_End_Inlining
10365 and then Inlining_Not_Possible (Subp)
10366 then
10367 Applies := True;
10368 return;
10370 -- Here we have a candidate for inlining, but we must exclude
10371 -- derived operations. Otherwise we would end up trying to inline
10372 -- a phantom declaration, and the result would be to drag in a
10373 -- body which has no direct inlining associated with it. That
10374 -- would not only be inefficient but would also result in the
10375 -- backend doing cross-unit inlining in cases where it was
10376 -- definitely inappropriate to do so.
10378 -- However, a simple Comes_From_Source test is insufficient, since
10379 -- we do want to allow inlining of generic instances which also do
10380 -- not come from source. We also need to recognize specs generated
10381 -- by the front-end for bodies that carry the pragma. Finally,
10382 -- predefined operators do not come from source but are not
10383 -- inlineable either.
10385 elsif Is_Generic_Instance (Subp)
10386 or else Parent_Kind (Parent (Subp)) = N_Subprogram_Declaration
10387 then
10388 null;
10390 elsif not Comes_From_Source (Subp)
10391 and then Scope (Subp) /= Standard_Standard
10392 then
10393 Applies := True;
10394 return;
10395 end if;
10397 -- The referenced entity must either be the enclosing entity, or
10398 -- an entity declared within the current open scope.
10400 if Present (Scope (Subp))
10401 and then Scope (Subp) /= Current_Scope
10402 and then Subp /= Current_Scope
10403 then
10404 Error_Pragma_Arg
10405 ("argument of% must be entity in current scope", Assoc);
10406 end if;
10408 -- Processing for procedure, operator or function. If subprogram
10409 -- is aliased (as for an instance) indicate that the renamed
10410 -- entity (if declared in the same unit) is inlined.
10411 -- If this is the anonymous subprogram created for a subprogram
10412 -- instance, the inlining applies to it directly. Otherwise we
10413 -- retrieve it as the alias of the visible subprogram instance.
10415 if Is_Subprogram (Subp) then
10417 -- Ensure that pragma Inline_Always is associated with the
10418 -- initial declaration of the subprogram.
10420 Check_Inline_Always_Placement (Subp);
10422 if Is_Wrapper_Package (Scope (Subp)) then
10423 Inner_Subp := Subp;
10424 else
10425 Inner_Subp := Ultimate_Alias (Inner_Subp);
10426 end if;
10428 if In_Same_Source_Unit (Subp, Inner_Subp) then
10429 Set_Inline_Flags (Inner_Subp);
10431 if Present (Parent (Inner_Subp)) then
10432 Decl := Parent (Parent (Inner_Subp));
10433 else
10434 Decl := Empty;
10435 end if;
10437 if Nkind (Decl) = N_Subprogram_Declaration
10438 and then Present (Corresponding_Body (Decl))
10439 then
10440 Set_Inline_Flags (Corresponding_Body (Decl));
10442 elsif Is_Generic_Instance (Subp)
10443 and then Comes_From_Source (Subp)
10444 then
10445 -- Indicate that the body needs to be created for
10446 -- inlining subsequent calls. The instantiation node
10447 -- follows the declaration of the wrapper package
10448 -- created for it. The subprogram that requires the
10449 -- body is the anonymous one in the wrapper package.
10451 if Scope (Subp) /= Standard_Standard
10452 and then
10453 Need_Subprogram_Instance_Body
10454 (Next (Unit_Declaration_Node
10455 (Scope (Alias (Subp)))), Subp)
10456 then
10457 null;
10458 end if;
10460 -- Inline is a program unit pragma (RM 10.1.5) and cannot
10461 -- appear in a formal part to apply to a formal subprogram.
10462 -- Do not apply check within an instance or a formal package
10463 -- the test will have been applied to the original generic.
10465 elsif Nkind (Decl) in N_Formal_Subprogram_Declaration
10466 and then In_Same_List (Decl, N)
10467 and then not In_Instance
10468 then
10469 Error_Msg_N
10470 ("Inline cannot apply to a formal subprogram", N);
10471 end if;
10472 end if;
10474 Applies := True;
10476 -- For a generic subprogram set flag as well, for use at the point
10477 -- of instantiation, to determine whether the body should be
10478 -- generated.
10480 elsif Is_Generic_Subprogram (Subp) then
10481 Set_Inline_Flags (Subp);
10482 Applies := True;
10484 -- Literals are by definition inlined
10486 elsif Kind = E_Enumeration_Literal then
10487 null;
10489 -- Anything else is an error
10491 else
10492 Error_Pragma_Arg
10493 ("expect subprogram name for pragma%", Assoc);
10494 end if;
10495 end Make_Inline;
10497 ----------------------
10498 -- Set_Inline_Flags --
10499 ----------------------
10501 procedure Set_Inline_Flags (Subp : Entity_Id) is
10502 begin
10503 -- First set the Has_Pragma_XXX flags and issue the appropriate
10504 -- errors and warnings for suspicious combinations.
10506 if Prag_Id = Pragma_No_Inline then
10507 if Has_Pragma_Inline_Always (Subp) then
10508 Error_Msg_N
10509 ("Inline_Always and No_Inline are mutually exclusive", N);
10510 elsif Has_Pragma_Inline (Subp) then
10511 Error_Msg_NE
10512 ("Inline and No_Inline both specified for& ??",
10513 N, Entity (Subp_Id));
10514 end if;
10516 Set_Has_Pragma_No_Inline (Subp);
10517 else
10518 if Prag_Id = Pragma_Inline_Always then
10519 if Has_Pragma_No_Inline (Subp) then
10520 Error_Msg_N
10521 ("Inline_Always and No_Inline are mutually exclusive",
10523 end if;
10525 Set_Has_Pragma_Inline_Always (Subp);
10526 else
10527 if Has_Pragma_No_Inline (Subp) then
10528 Error_Msg_NE
10529 ("Inline and No_Inline both specified for& ??",
10530 N, Entity (Subp_Id));
10531 end if;
10532 end if;
10534 Set_Has_Pragma_Inline (Subp);
10535 end if;
10537 -- Then adjust the Is_Inlined flag. It can never be set if the
10538 -- subprogram is subject to pragma No_Inline.
10540 case Status is
10541 when Suppressed =>
10542 Set_Is_Inlined (Subp, False);
10544 when Disabled =>
10545 null;
10547 when Enabled =>
10548 if not Has_Pragma_No_Inline (Subp) then
10549 Set_Is_Inlined (Subp, True);
10550 end if;
10551 end case;
10553 -- A pragma that applies to a Ghost entity becomes Ghost for the
10554 -- purposes of legality checks and removal of ignored Ghost code.
10556 Mark_Ghost_Pragma (N, Subp);
10558 -- Capture the entity of the first Ghost subprogram being
10559 -- processed for error detection purposes.
10561 if Is_Ghost_Entity (Subp) then
10562 if No (Ghost_Id) then
10563 Ghost_Id := Subp;
10564 end if;
10566 -- Otherwise the subprogram is non-Ghost. It is illegal to mix
10567 -- references to Ghost and non-Ghost entities (SPARK RM 6.9).
10569 elsif Present (Ghost_Id) and then not Ghost_Error_Posted then
10570 Ghost_Error_Posted := True;
10572 Error_Msg_Name_1 := Pname;
10573 Error_Msg_N
10574 ("pragma % cannot mention ghost and non-ghost subprograms",
10577 Error_Msg_Sloc := Sloc (Ghost_Id);
10578 Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
10580 Error_Msg_Sloc := Sloc (Subp);
10581 Error_Msg_NE ("\& # declared as non-ghost", N, Subp);
10582 end if;
10583 end Set_Inline_Flags;
10585 -- Start of processing for Process_Inline
10587 begin
10588 -- An inlined subprogram may grant access to its private enclosing
10589 -- context depending on the placement of its body. From elaboration
10590 -- point of view, the flow of execution may enter this private
10591 -- context, and then reach an external unit, thus producing a
10592 -- dependency on that external unit. For such a path to be properly
10593 -- discovered and encoded in the ALI file of the main unit, let the
10594 -- ABE mechanism process the body of the main unit, and encode all
10595 -- relevant invocation constructs and the relations between them.
10597 Mark_Save_Invocation_Graph_Of_Body;
10599 Check_No_Identifiers;
10600 Check_At_Least_N_Arguments (1);
10602 if Status = Enabled then
10603 Inline_Processing_Required := True;
10604 end if;
10606 Assoc := Arg1;
10607 while Present (Assoc) loop
10608 Subp_Id := Get_Pragma_Arg (Assoc);
10609 Analyze (Subp_Id);
10610 Applies := False;
10612 if Is_Entity_Name (Subp_Id) then
10613 Subp := Entity (Subp_Id);
10615 if Subp = Any_Id then
10617 -- If previous error, avoid cascaded errors
10619 Check_Error_Detected;
10620 Applies := True;
10622 else
10623 -- Check for RM 13.1(9.2/4): If a [...] aspect_specification
10624 -- is given that directly specifies an aspect of an entity,
10625 -- then it is illegal to give another [...]
10626 -- aspect_specification that directly specifies the same
10627 -- aspect of the entity.
10628 -- We only check Subp directly as per "directly specifies"
10629 -- above and because the case of pragma Inline is really
10630 -- special given its pre aspect usage.
10632 Check_Duplicate_Pragma (Subp);
10633 Record_Rep_Item (Subp, N);
10635 Make_Inline (Subp);
10637 -- For the pragma case, climb homonym chain. This is
10638 -- what implements allowing the pragma in the renaming
10639 -- case, with the result applying to the ancestors, and
10640 -- also allows Inline to apply to all previous homonyms.
10642 if not From_Aspect_Specification (N) then
10643 while Present (Homonym (Subp))
10644 and then Scope (Homonym (Subp)) = Current_Scope
10645 loop
10646 Subp := Homonym (Subp);
10647 Make_Inline (Subp);
10648 end loop;
10649 end if;
10650 end if;
10651 end if;
10653 if not Applies then
10654 Error_Pragma_Arg ("inappropriate argument for pragma%", Assoc);
10655 end if;
10657 Next (Assoc);
10658 end loop;
10660 -- If the context is a package declaration, the pragma indicates
10661 -- that inlining will require the presence of the corresponding
10662 -- body. (this may be further refined).
10664 if not In_Instance
10665 and then Nkind (Unit (Cunit (Current_Sem_Unit))) =
10666 N_Package_Declaration
10667 then
10668 Set_Body_Needed_For_Inlining (Cunit_Entity (Current_Sem_Unit));
10669 end if;
10670 end Process_Inline;
10672 ----------------------------
10673 -- Process_Interface_Name --
10674 ----------------------------
10676 procedure Process_Interface_Name
10677 (Subprogram_Def : Entity_Id;
10678 Ext_Arg : Node_Id;
10679 Link_Arg : Node_Id;
10680 Prag : Node_Id)
10682 Ext_Nam : Node_Id;
10683 Link_Nam : Node_Id;
10684 String_Val : String_Id;
10686 procedure Check_Form_Of_Interface_Name (SN : Node_Id);
10687 -- SN is a string literal node for an interface name. This routine
10688 -- performs some minimal checks that the name is reasonable. In
10689 -- particular that no spaces or other obviously incorrect characters
10690 -- appear. This is only a warning, since any characters are allowed.
10692 ----------------------------------
10693 -- Check_Form_Of_Interface_Name --
10694 ----------------------------------
10696 procedure Check_Form_Of_Interface_Name (SN : Node_Id) is
10697 S : constant String_Id := Strval (Expr_Value_S (SN));
10698 SL : constant Nat := String_Length (S);
10699 C : Char_Code;
10701 begin
10702 if SL = 0 then
10703 Error_Msg_N ("interface name cannot be null string", SN);
10704 end if;
10706 for J in 1 .. SL loop
10707 C := Get_String_Char (S, J);
10709 -- Look for dubious character and issue unconditional warning.
10710 -- Definitely dubious if not in character range.
10712 if not In_Character_Range (C)
10714 -- Commas, spaces and (back)slashes are dubious
10716 or else Get_Character (C) = ','
10717 or else Get_Character (C) = '\'
10718 or else Get_Character (C) = ' '
10719 or else Get_Character (C) = '/'
10720 then
10721 Error_Msg
10722 ("??interface name contains illegal character",
10723 Sloc (SN) + Source_Ptr (J));
10724 end if;
10725 end loop;
10726 end Check_Form_Of_Interface_Name;
10728 -- Start of processing for Process_Interface_Name
10730 begin
10731 -- If we are looking at a pragma that comes from an aspect then it
10732 -- needs to have its corresponding aspect argument expressions
10733 -- analyzed in addition to the generated pragma so that aspects
10734 -- within generic units get properly resolved.
10736 if Present (Prag) and then From_Aspect_Specification (Prag) then
10737 declare
10738 Asp : constant Node_Id := Corresponding_Aspect (Prag);
10739 Dummy_1 : Node_Id;
10740 Dummy_2 : Node_Id;
10741 Dummy_3 : Node_Id;
10742 EN : Node_Id;
10743 LN : Node_Id;
10745 begin
10746 -- Obtain all interfacing aspects used to construct the pragma
10748 Get_Interfacing_Aspects
10749 (Asp, Dummy_1, EN, Dummy_2, Dummy_3, LN);
10751 -- Analyze the expression of aspect External_Name
10753 if Present (EN) then
10754 Analyze (Expression (EN));
10755 end if;
10757 -- Analyze the expressio of aspect Link_Name
10759 if Present (LN) then
10760 Analyze (Expression (LN));
10761 end if;
10762 end;
10763 end if;
10765 if No (Link_Arg) then
10766 if No (Ext_Arg) then
10767 return;
10769 elsif Chars (Ext_Arg) = Name_Link_Name then
10770 Ext_Nam := Empty;
10771 Link_Nam := Expression (Ext_Arg);
10773 else
10774 Check_Optional_Identifier (Ext_Arg, Name_External_Name);
10775 Ext_Nam := Expression (Ext_Arg);
10776 Link_Nam := Empty;
10777 end if;
10779 else
10780 Check_Optional_Identifier (Ext_Arg, Name_External_Name);
10781 Check_Optional_Identifier (Link_Arg, Name_Link_Name);
10782 Ext_Nam := Expression (Ext_Arg);
10783 Link_Nam := Expression (Link_Arg);
10784 end if;
10786 -- Check expressions for external name and link name are static
10788 if Present (Ext_Nam) then
10789 Check_Arg_Is_OK_Static_Expression (Ext_Nam, Standard_String);
10790 Check_Form_Of_Interface_Name (Ext_Nam);
10792 -- Verify that external name is not the name of a local entity,
10793 -- which would hide the imported one and could lead to run-time
10794 -- surprises. The problem can only arise for entities declared in
10795 -- a package body (otherwise the external name is fully qualified
10796 -- and will not conflict).
10798 declare
10799 Nam : Name_Id;
10800 E : Entity_Id;
10801 Par : Node_Id;
10803 begin
10804 if Prag_Id = Pragma_Import then
10805 Nam := String_To_Name (Strval (Expr_Value_S (Ext_Nam)));
10806 E := Entity_Id (Get_Name_Table_Int (Nam));
10808 if Nam /= Chars (Subprogram_Def)
10809 and then Present (E)
10810 and then not Is_Overloadable (E)
10811 and then Is_Immediately_Visible (E)
10812 and then not Is_Imported (E)
10813 and then Ekind (Scope (E)) = E_Package
10814 then
10815 Par := Parent (E);
10816 while Present (Par) loop
10817 if Nkind (Par) = N_Package_Body then
10818 Error_Msg_Sloc := Sloc (E);
10819 Error_Msg_NE
10820 ("imported entity is hidden by & declared#",
10821 Ext_Arg, E);
10822 exit;
10823 end if;
10825 Par := Parent (Par);
10826 end loop;
10827 end if;
10828 end if;
10829 end;
10830 end if;
10832 if Present (Link_Nam) then
10833 Check_Arg_Is_OK_Static_Expression (Link_Nam, Standard_String);
10834 Check_Form_Of_Interface_Name (Link_Nam);
10835 end if;
10837 -- If there is no link name, just set the external name
10839 if No (Link_Nam) then
10840 Link_Nam := Adjust_External_Name_Case (Expr_Value_S (Ext_Nam));
10842 -- For the Link_Name case, the given literal is preceded by an
10843 -- asterisk, which indicates to GCC that the given name should be
10844 -- taken literally, and in particular that no prepending of
10845 -- underlines should occur, even in systems where this is the
10846 -- normal default.
10848 else
10849 Start_String;
10850 Store_String_Char (Get_Char_Code ('*'));
10851 String_Val := Strval (Expr_Value_S (Link_Nam));
10852 Store_String_Chars (String_Val);
10853 Link_Nam :=
10854 Make_String_Literal (Sloc (Link_Nam),
10855 Strval => End_String);
10856 end if;
10858 -- Set the interface name. If the entity is a generic instance, use
10859 -- its alias, which is the callable entity.
10861 if Is_Generic_Instance (Subprogram_Def) then
10862 Set_Encoded_Interface_Name
10863 (Alias (Get_Base_Subprogram (Subprogram_Def)), Link_Nam);
10864 else
10865 Set_Encoded_Interface_Name
10866 (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
10867 end if;
10869 Check_Duplicated_Export_Name (Link_Nam);
10870 end Process_Interface_Name;
10872 -----------------------------------------
10873 -- Process_Interrupt_Or_Attach_Handler --
10874 -----------------------------------------
10876 procedure Process_Interrupt_Or_Attach_Handler is
10877 Handler : constant Entity_Id := Entity (Get_Pragma_Arg (Arg1));
10878 Prot_Typ : constant Entity_Id := Scope (Handler);
10880 begin
10881 -- A pragma that applies to a Ghost entity becomes Ghost for the
10882 -- purposes of legality checks and removal of ignored Ghost code.
10884 Mark_Ghost_Pragma (N, Handler);
10885 Set_Is_Interrupt_Handler (Handler);
10887 pragma Assert (Ekind (Prot_Typ) = E_Protected_Type);
10889 Record_Rep_Item (Prot_Typ, N);
10891 -- Chain the pragma on the contract for completeness
10893 Add_Contract_Item (N, Handler);
10894 end Process_Interrupt_Or_Attach_Handler;
10896 --------------------------------------------------
10897 -- Process_Restrictions_Or_Restriction_Warnings --
10898 --------------------------------------------------
10900 -- Note: some of the simple identifier cases were handled in par-prag,
10901 -- but it is harmless (and more straightforward) to simply handle all
10902 -- cases here, even if it means we repeat a bit of work in some cases.
10904 procedure Process_Restrictions_Or_Restriction_Warnings
10905 (Warn : Boolean)
10907 Arg : Node_Id;
10908 R_Id : Restriction_Id;
10909 Id : Name_Id;
10910 Expr : Node_Id;
10911 Val : Uint;
10913 procedure Process_No_Specification_of_Aspect;
10914 -- Process the No_Specification_of_Aspect restriction
10916 procedure Process_No_Use_Of_Attribute;
10917 -- Process the No_Use_Of_Attribute restriction
10919 ----------------------------------------
10920 -- Process_No_Specification_of_Aspect --
10921 ----------------------------------------
10923 procedure Process_No_Specification_of_Aspect is
10924 Name : constant Name_Id := Chars (Expr);
10925 begin
10926 if Nkind (Expr) = N_Identifier
10927 and then Is_Aspect_Id (Name)
10928 then
10929 Set_Restriction_No_Specification_Of_Aspect (Expr, Warn);
10930 else
10931 Bad_Aspect (Expr, Name, Warn => True);
10933 raise Pragma_Exit;
10934 end if;
10935 end Process_No_Specification_of_Aspect;
10937 ---------------------------------
10938 -- Process_No_Use_Of_Attribute --
10939 ---------------------------------
10941 procedure Process_No_Use_Of_Attribute is
10942 Name : constant Name_Id := Chars (Expr);
10943 begin
10944 if Nkind (Expr) = N_Identifier
10945 and then Is_Attribute_Name (Name)
10946 then
10947 Set_Restriction_No_Use_Of_Attribute (Expr, Warn);
10948 else
10949 Bad_Attribute (Expr, Name, Warn => True);
10950 end if;
10952 end Process_No_Use_Of_Attribute;
10954 -- Start of processing for Process_Restrictions_Or_Restriction_Warnings
10956 begin
10957 -- Ignore all Restrictions pragmas in CodePeer mode
10959 if CodePeer_Mode then
10960 return;
10961 end if;
10963 Check_Ada_83_Warning;
10964 Check_At_Least_N_Arguments (1);
10965 Check_Valid_Configuration_Pragma;
10967 Arg := Arg1;
10968 while Present (Arg) loop
10969 Id := Chars (Arg);
10970 Expr := Get_Pragma_Arg (Arg);
10972 -- Case of no restriction identifier present
10974 if Id = No_Name then
10975 if Nkind (Expr) /= N_Identifier then
10976 Error_Pragma_Arg
10977 ("invalid form for restriction", Arg);
10978 end if;
10980 R_Id :=
10981 Get_Restriction_Id
10982 (Process_Restriction_Synonyms (Expr));
10984 if R_Id not in All_Boolean_Restrictions then
10985 Error_Msg_Name_1 := Pname;
10986 Error_Msg_N
10987 ("invalid restriction identifier&", Get_Pragma_Arg (Arg));
10989 -- Check for possible misspelling
10991 for J in All_Restrictions loop
10992 declare
10993 Rnm : constant String := Restriction_Id'Image (J);
10995 begin
10996 Name_Buffer (1 .. Rnm'Length) := Rnm;
10997 Name_Len := Rnm'Length;
10998 Set_Casing (All_Lower_Case);
11000 if Is_Bad_Spelling_Of (Chars (Expr), Name_Enter) then
11001 Set_Casing
11002 (Identifier_Casing
11003 (Source_Index (Current_Sem_Unit)));
11004 Error_Msg_String (1 .. Rnm'Length) :=
11005 Name_Buffer (1 .. Name_Len);
11006 Error_Msg_Strlen := Rnm'Length;
11007 Error_Msg_N -- CODEFIX
11008 ("\possible misspelling of ""~""",
11009 Get_Pragma_Arg (Arg));
11010 exit;
11011 end if;
11012 end;
11013 end loop;
11015 raise Pragma_Exit;
11016 end if;
11018 if Implementation_Restriction (R_Id) then
11019 Check_Restriction (No_Implementation_Restrictions, Arg);
11020 end if;
11022 -- Special processing for No_Elaboration_Code restriction
11024 if R_Id = No_Elaboration_Code then
11026 -- Restriction is only recognized within a configuration
11027 -- pragma file, or within a unit of the main extended
11028 -- program. Note: the test for Main_Unit is needed to
11029 -- properly include the case of configuration pragma files.
11031 if not (Current_Sem_Unit = Main_Unit
11032 or else In_Extended_Main_Source_Unit (N))
11033 then
11034 return;
11036 -- Don't allow in a subunit unless already specified in
11037 -- body or spec.
11039 elsif Nkind (Parent (N)) = N_Compilation_Unit
11040 and then Nkind (Unit (Parent (N))) = N_Subunit
11041 and then not Restriction_Active (No_Elaboration_Code)
11042 then
11043 Error_Msg_N
11044 ("invalid specification of ""No_Elaboration_Code""",
11046 Error_Msg_N
11047 ("\restriction cannot be specified in a subunit", N);
11048 Error_Msg_N
11049 ("\unless also specified in body or spec", N);
11050 return;
11052 -- If we accept a No_Elaboration_Code restriction, then it
11053 -- needs to be added to the configuration restriction set so
11054 -- that we get proper application to other units in the main
11055 -- extended source as required.
11057 else
11058 Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
11059 end if;
11061 -- Special processing for No_Dynamic_Accessibility_Checks to
11062 -- disallow exclusive specification in a body or subunit.
11064 elsif R_Id = No_Dynamic_Accessibility_Checks
11065 -- Check if the restriction is within configuration pragma
11066 -- in a similar way to No_Elaboration_Code.
11068 and then not (Current_Sem_Unit = Main_Unit
11069 or else In_Extended_Main_Source_Unit (N))
11071 and then Nkind (Unit (Parent (N))) = N_Compilation_Unit
11073 and then (Nkind (Unit (Parent (N))) = N_Package_Body
11074 or else Nkind (Unit (Parent (N))) = N_Subunit)
11076 and then not Restriction_Active
11077 (No_Dynamic_Accessibility_Checks)
11078 then
11079 Error_Msg_N
11080 ("invalid specification of " &
11081 """No_Dynamic_Accessibility_Checks""", N);
11083 if Nkind (Unit (Parent (N))) = N_Package_Body then
11084 Error_Msg_N
11085 ("\restriction cannot be specified in a package " &
11086 "body", N);
11088 elsif Nkind (Unit (Parent (N))) = N_Subunit then
11089 Error_Msg_N
11090 ("\restriction cannot be specified in a subunit", N);
11091 end if;
11093 Error_Msg_N
11094 ("\unless also specified in spec", N);
11096 -- Special processing for No_Tasking restriction (not just a
11097 -- warning) when it appears as a configuration pragma.
11099 elsif R_Id = No_Tasking
11100 and then No (Cunit (Main_Unit))
11101 and then not Warn
11102 then
11103 Set_Global_No_Tasking;
11104 end if;
11106 Set_Restriction (R_Id, N, Warn);
11108 if R_Id = No_Dynamic_CPU_Assignment
11109 or else R_Id = No_Tasks_Unassigned_To_CPU
11110 then
11111 -- These imply No_Dependence =>
11112 -- "System.Multiprocessors.Dispatching_Domains".
11113 -- This is not strictly what the AI says, but it eliminates
11114 -- the need for run-time checks, which are undesirable in
11115 -- this context.
11117 Set_Restriction_No_Dependence
11118 (Sel_Comp
11119 (Sel_Comp ("system", "multiprocessors", Loc),
11120 "dispatching_domains"),
11121 Warn);
11122 end if;
11124 if R_Id = No_Tasks_Unassigned_To_CPU then
11125 -- Likewise, imply No_Dynamic_CPU_Assignment
11127 Set_Restriction (No_Dynamic_CPU_Assignment, N, Warn);
11128 end if;
11130 -- Check for obsolescent restrictions in Ada 2005 mode
11132 if not Warn
11133 and then Ada_Version >= Ada_2005
11134 and then (R_Id = No_Asynchronous_Control
11135 or else
11136 R_Id = No_Unchecked_Deallocation
11137 or else
11138 R_Id = No_Unchecked_Conversion)
11139 then
11140 Check_Restriction (No_Obsolescent_Features, N);
11141 end if;
11143 -- A very special case that must be processed here: pragma
11144 -- Restrictions (No_Exceptions) turns off all run-time
11145 -- checking. This is a bit dubious in terms of the formal
11146 -- language definition, but it is what is intended by RM
11147 -- H.4(12). Restriction_Warnings never affects generated code
11148 -- so this is done only in the real restriction case.
11150 -- Atomic_Synchronization is not a real check, so it is not
11151 -- affected by this processing).
11153 -- Ignore the effect of pragma Restrictions (No_Exceptions) on
11154 -- run-time checks in CodePeer and GNATprove modes: we want to
11155 -- generate checks for analysis purposes, as set respectively
11156 -- by -gnatC and -gnatd.F
11158 if not Warn
11159 and then not (CodePeer_Mode or GNATprove_Mode)
11160 and then R_Id = No_Exceptions
11161 then
11162 for J in Scope_Suppress.Suppress'Range loop
11163 if J /= Atomic_Synchronization then
11164 Scope_Suppress.Suppress (J) := True;
11165 end if;
11166 end loop;
11167 end if;
11169 -- Case of No_Dependence => unit-name. Note that the parser
11170 -- already made the necessary entry in the No_Dependence table.
11172 elsif Id = Name_No_Dependence then
11173 if not OK_No_Dependence_Unit_Name (Expr) then
11174 raise Pragma_Exit;
11175 end if;
11177 -- Case of No_Specification_Of_Aspect => aspect-identifier
11179 elsif Id = Name_No_Specification_Of_Aspect then
11180 Process_No_Specification_of_Aspect;
11182 -- Case of No_Use_Of_Attribute => attribute-identifier
11184 elsif Id = Name_No_Use_Of_Attribute then
11185 Process_No_Use_Of_Attribute;
11187 -- Case of No_Use_Of_Entity => fully-qualified-name
11189 elsif Id = Name_No_Use_Of_Entity then
11191 -- Restriction is only recognized within a configuration
11192 -- pragma file, or within a unit of the main extended
11193 -- program. Note: the test for Main_Unit is needed to
11194 -- properly include the case of configuration pragma files.
11196 if Current_Sem_Unit = Main_Unit
11197 or else In_Extended_Main_Source_Unit (N)
11198 then
11199 if not OK_No_Dependence_Unit_Name (Expr) then
11200 Error_Msg_N ("wrong form for entity name", Expr);
11201 else
11202 Set_Restriction_No_Use_Of_Entity
11203 (Expr, Warn, No_Profile);
11204 end if;
11205 end if;
11207 -- Case of No_Use_Of_Pragma => pragma-identifier
11209 elsif Id = Name_No_Use_Of_Pragma then
11210 if Nkind (Expr) /= N_Identifier
11211 or else not Is_Pragma_Name (Chars (Expr))
11212 then
11213 Error_Msg_N ("unknown pragma name??", Expr);
11214 else
11215 Set_Restriction_No_Use_Of_Pragma (Expr, Warn);
11216 end if;
11218 -- All other cases of restriction identifier present
11220 else
11221 R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
11223 if R_Id not in All_Parameter_Restrictions then
11224 Error_Pragma_Arg
11225 ("invalid restriction parameter identifier", Arg);
11226 end if;
11228 Analyze_And_Resolve (Expr, Any_Integer);
11230 if not Is_OK_Static_Expression (Expr) then
11231 Flag_Non_Static_Expr
11232 ("value must be static expression!", Expr);
11233 raise Pragma_Exit;
11235 elsif not Is_Integer_Type (Etype (Expr))
11236 or else Expr_Value (Expr) < 0
11237 then
11238 Error_Pragma_Arg
11239 ("value must be non-negative integer", Arg);
11240 end if;
11242 -- Restriction pragma is active
11244 Val := Expr_Value (Expr);
11246 if not UI_Is_In_Int_Range (Val) then
11247 Error_Pragma_Arg
11248 ("pragma ignored, value too large??", Arg);
11249 end if;
11251 Set_Restriction (R_Id, N, Warn, Integer (UI_To_Int (Val)));
11252 end if;
11254 Next (Arg);
11255 end loop;
11256 end Process_Restrictions_Or_Restriction_Warnings;
11258 ---------------------------------
11259 -- Process_Suppress_Unsuppress --
11260 ---------------------------------
11262 -- Note: this procedure makes entries in the check suppress data
11263 -- structures managed by Sem. See spec of package Sem for full
11264 -- details on how we handle recording of check suppression.
11266 procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
11267 C : Check_Id;
11268 E : Entity_Id;
11269 E_Id : Node_Id;
11271 In_Package_Spec : constant Boolean :=
11272 Is_Package_Or_Generic_Package (Current_Scope)
11273 and then not In_Package_Body (Current_Scope);
11275 procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
11276 -- Used to suppress a single check on the given entity
11278 --------------------------------
11279 -- Suppress_Unsuppress_Echeck --
11280 --------------------------------
11282 procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
11283 begin
11284 -- Check for error of trying to set atomic synchronization for
11285 -- a non-atomic variable.
11287 if C = Atomic_Synchronization
11288 and then not (Is_Atomic (E) or else Has_Atomic_Components (E))
11289 then
11290 Error_Msg_N
11291 ("pragma & requires atomic type or variable",
11292 Pragma_Identifier (Original_Node (N)));
11293 end if;
11295 Set_Checks_May_Be_Suppressed (E);
11297 if In_Package_Spec then
11298 Push_Global_Suppress_Stack_Entry
11299 (Entity => E,
11300 Check => C,
11301 Suppress => Suppress_Case);
11302 else
11303 Push_Local_Suppress_Stack_Entry
11304 (Entity => E,
11305 Check => C,
11306 Suppress => Suppress_Case);
11307 end if;
11309 -- If this is a first subtype, and the base type is distinct,
11310 -- then also set the suppress flags on the base type.
11312 if Is_First_Subtype (E) and then Etype (E) /= E then
11313 Suppress_Unsuppress_Echeck (Etype (E), C);
11314 end if;
11315 end Suppress_Unsuppress_Echeck;
11317 -- Start of processing for Process_Suppress_Unsuppress
11319 begin
11320 -- Ignore pragma Suppress/Unsuppress in CodePeer and GNATprove modes
11321 -- on user code: we want to generate checks for analysis purposes, as
11322 -- set respectively by -gnatC and -gnatd.F
11324 if Comes_From_Source (N)
11325 and then (CodePeer_Mode or GNATprove_Mode)
11326 then
11327 return;
11328 end if;
11330 -- Suppress/Unsuppress can appear as a configuration pragma, or in a
11331 -- declarative part or a package spec (RM 11.5(5)).
11333 if not Is_Configuration_Pragma then
11334 Check_Is_In_Decl_Part_Or_Package_Spec;
11335 end if;
11337 Check_At_Least_N_Arguments (1);
11338 Check_At_Most_N_Arguments (2);
11339 Check_No_Identifier (Arg1);
11340 Check_Arg_Is_Identifier (Arg1);
11342 C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
11344 if C = No_Check_Id then
11345 Error_Pragma_Arg
11346 ("argument of pragma% is not valid check name", Arg1);
11347 end if;
11349 -- Warn that suppress of Elaboration_Check has no effect in SPARK
11351 if C = Elaboration_Check
11352 and then Suppress_Case
11353 and then SPARK_Mode = On
11354 then
11355 Error_Pragma_Arg
11356 ("Suppress of Elaboration_Check ignored in SPARK??",
11357 "\elaboration checking rules are statically enforced "
11358 & "(SPARK RM 7.7)", Arg1);
11359 end if;
11361 -- One-argument case
11363 if Arg_Count = 1 then
11365 -- Make an entry in the local scope suppress table. This is the
11366 -- table that directly shows the current value of the scope
11367 -- suppress check for any check id value.
11369 if C = All_Checks then
11371 -- For All_Checks, we set all specific predefined checks with
11372 -- the exception of Elaboration_Check, which is handled
11373 -- specially because of not wanting All_Checks to have the
11374 -- effect of deactivating static elaboration order processing.
11375 -- Atomic_Synchronization is also not affected, since this is
11376 -- not a real check.
11378 for J in Scope_Suppress.Suppress'Range loop
11379 if J /= Elaboration_Check
11380 and then
11381 J /= Atomic_Synchronization
11382 then
11383 Scope_Suppress.Suppress (J) := Suppress_Case;
11384 end if;
11385 end loop;
11387 -- If not All_Checks, and predefined check, then set appropriate
11388 -- scope entry. Note that we will set Elaboration_Check if this
11389 -- is explicitly specified. Atomic_Synchronization is allowed
11390 -- only if internally generated and entity is atomic.
11392 elsif C in Predefined_Check_Id
11393 and then (not Comes_From_Source (N)
11394 or else C /= Atomic_Synchronization)
11395 then
11396 Scope_Suppress.Suppress (C) := Suppress_Case;
11397 end if;
11399 -- Also push an entry in the local suppress stack
11401 Push_Local_Suppress_Stack_Entry
11402 (Entity => Empty,
11403 Check => C,
11404 Suppress => Suppress_Case);
11406 -- Case of two arguments present, where the check is suppressed for
11407 -- a specified entity (given as the second argument of the pragma)
11409 else
11410 -- This is obsolescent in Ada 2005 mode
11412 if Ada_Version >= Ada_2005 then
11413 Check_Restriction (No_Obsolescent_Features, Arg2);
11414 end if;
11416 Check_Optional_Identifier (Arg2, Name_On);
11417 E_Id := Get_Pragma_Arg (Arg2);
11418 Analyze (E_Id);
11420 if not Is_Entity_Name (E_Id) then
11421 Error_Pragma_Arg
11422 ("second argument of pragma% must be entity name", Arg2);
11423 end if;
11425 E := Entity (E_Id);
11427 if E = Any_Id then
11428 return;
11429 end if;
11431 -- A pragma that applies to a Ghost entity becomes Ghost for the
11432 -- purposes of legality checks and removal of ignored Ghost code.
11434 Mark_Ghost_Pragma (N, E);
11436 -- Enforce RM 11.5(7) which requires that for a pragma that
11437 -- appears within a package spec, the named entity must be
11438 -- within the package spec. We allow the package name itself
11439 -- to be mentioned since that makes sense, although it is not
11440 -- strictly allowed by 11.5(7).
11442 if In_Package_Spec
11443 and then E /= Current_Scope
11444 and then Scope (E) /= Current_Scope
11445 then
11446 Error_Pragma_Arg
11447 ("entity in pragma% is not in package spec (RM 11.5(7))",
11448 Arg2);
11449 end if;
11451 -- Loop through homonyms. As noted below, in the case of a package
11452 -- spec, only homonyms within the package spec are considered.
11454 loop
11455 Suppress_Unsuppress_Echeck (E, C);
11457 if Is_Generic_Instance (E)
11458 and then Is_Subprogram (E)
11459 and then Present (Alias (E))
11460 then
11461 Suppress_Unsuppress_Echeck (Alias (E), C);
11462 end if;
11464 -- Move to next homonym if not aspect spec case
11466 exit when From_Aspect_Specification (N);
11467 E := Homonym (E);
11468 exit when No (E);
11470 -- If we are within a package specification, the pragma only
11471 -- applies to homonyms in the same scope.
11473 exit when In_Package_Spec
11474 and then Scope (E) /= Current_Scope;
11475 end loop;
11476 end if;
11477 end Process_Suppress_Unsuppress;
11479 -------------------------------
11480 -- Record_Independence_Check --
11481 -------------------------------
11483 procedure Record_Independence_Check (N : Node_Id; E : Entity_Id) is
11484 pragma Unreferenced (N, E);
11485 begin
11486 -- For GCC back ends the validation is done a priori. This code is
11487 -- dead, but might be useful in the future.
11489 -- if not AAMP_On_Target then
11490 -- return;
11491 -- end if;
11493 -- Independence_Checks.Append ((N, E));
11495 return;
11496 end Record_Independence_Check;
11498 ------------------
11499 -- Set_Exported --
11500 ------------------
11502 procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
11503 begin
11504 if Is_Imported (E) then
11505 Error_Pragma_Arg
11506 ("cannot export entity& that was previously imported", Arg);
11508 elsif Present (Address_Clause (E))
11509 and then not Relaxed_RM_Semantics
11510 then
11511 Error_Pragma_Arg
11512 ("cannot export entity& that has an address clause", Arg);
11513 end if;
11515 Set_Is_Exported (E);
11517 -- Generate a reference for entity explicitly, because the
11518 -- identifier may be overloaded and name resolution will not
11519 -- generate one.
11521 Generate_Reference (E, Arg);
11523 -- Deal with exporting non-library level entity
11525 if not Is_Library_Level_Entity (E) then
11527 -- Not allowed at all for subprograms
11529 if Is_Subprogram (E) then
11530 Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
11532 -- Otherwise set public and statically allocated
11534 else
11535 Set_Is_Public (E);
11536 Set_Is_Statically_Allocated (E);
11538 -- Warn if the corresponding W flag is set
11540 if Warn_On_Export_Import
11542 -- Only do this for something that was in the source. Not
11543 -- clear if this can be False now (there used for sure to be
11544 -- cases on some systems where it was False), but anyway the
11545 -- test is harmless if not needed, so it is retained.
11547 and then Comes_From_Source (Arg)
11548 then
11549 Error_Msg_NE
11550 ("?x?& has been made static as a result of Export",
11551 Arg, E);
11552 Error_Msg_N
11553 ("\?x?this usage is non-standard and non-portable",
11554 Arg);
11555 end if;
11556 end if;
11557 end if;
11559 if Warn_On_Export_Import and Inside_A_Generic then
11560 Error_Msg_NE
11561 ("all instances of& will have the same external name?x?",
11562 Arg, E);
11563 end if;
11564 end Set_Exported;
11566 ----------------------------------------------
11567 -- Set_Extended_Import_Export_External_Name --
11568 ----------------------------------------------
11570 procedure Set_Extended_Import_Export_External_Name
11571 (Internal_Ent : Entity_Id;
11572 Arg_External : Node_Id)
11574 Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
11575 New_Name : Node_Id;
11577 begin
11578 if No (Arg_External) then
11579 return;
11580 end if;
11582 Check_Arg_Is_External_Name (Arg_External);
11584 if Nkind (Arg_External) = N_String_Literal then
11585 if String_Length (Strval (Arg_External)) = 0 then
11586 return;
11587 else
11588 New_Name := Adjust_External_Name_Case (Arg_External);
11589 end if;
11591 elsif Nkind (Arg_External) = N_Identifier then
11592 New_Name := Get_Default_External_Name (Arg_External);
11594 -- Check_Arg_Is_External_Name should let through only identifiers and
11595 -- string literals or static string expressions (which are folded to
11596 -- string literals).
11598 else
11599 raise Program_Error;
11600 end if;
11602 -- If we already have an external name set (by a prior normal Import
11603 -- or Export pragma), then the external names must match
11605 if Present (Interface_Name (Internal_Ent)) then
11607 -- Ignore mismatching names in CodePeer mode, to support some
11608 -- old compilers which would export the same procedure under
11609 -- different names, e.g:
11610 -- procedure P;
11611 -- pragma Export_Procedure (P, "a");
11612 -- pragma Export_Procedure (P, "b");
11614 if CodePeer_Mode then
11615 return;
11616 end if;
11618 Check_Matching_Internal_Names : declare
11619 S1 : constant String_Id := Strval (Old_Name);
11620 S2 : constant String_Id := Strval (New_Name);
11622 procedure Mismatch;
11623 pragma No_Return (Mismatch);
11624 -- Called if names do not match
11626 --------------
11627 -- Mismatch --
11628 --------------
11630 procedure Mismatch is
11631 begin
11632 Error_Msg_Sloc := Sloc (Old_Name);
11633 Error_Pragma_Arg
11634 ("external name does not match that given #",
11635 Arg_External);
11636 end Mismatch;
11638 -- Start of processing for Check_Matching_Internal_Names
11640 begin
11641 if String_Length (S1) /= String_Length (S2) then
11642 Mismatch;
11644 else
11645 for J in 1 .. String_Length (S1) loop
11646 if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
11647 Mismatch;
11648 end if;
11649 end loop;
11650 end if;
11651 end Check_Matching_Internal_Names;
11653 -- Otherwise set the given name
11655 else
11656 Set_Encoded_Interface_Name (Internal_Ent, New_Name);
11657 Check_Duplicated_Export_Name (New_Name);
11658 end if;
11659 end Set_Extended_Import_Export_External_Name;
11661 ------------------
11662 -- Set_Imported --
11663 ------------------
11665 procedure Set_Imported (E : Entity_Id) is
11666 begin
11667 -- Error message if already imported or exported
11669 if Is_Exported (E) or else Is_Imported (E) then
11671 -- Error if being set Exported twice
11673 if Is_Exported (E) then
11674 Error_Msg_NE ("entity& was previously exported", N, E);
11676 -- Ignore error in CodePeer mode where we treat all imported
11677 -- subprograms as unknown.
11679 elsif CodePeer_Mode then
11680 goto OK;
11682 -- OK if Import/Interface case
11684 elsif Import_Interface_Present (N) then
11685 goto OK;
11687 -- Error if being set Imported twice
11689 else
11690 Error_Msg_NE ("entity& was previously imported", N, E);
11691 end if;
11693 Error_Msg_Name_1 := Pname;
11694 Error_Msg_N
11695 ("\(pragma% applies to all previous entities)", N);
11697 Error_Msg_Sloc := Sloc (E);
11698 Error_Msg_NE ("\import not allowed for& declared#", N, E);
11700 -- Here if not previously imported or exported, OK to import
11702 else
11703 Set_Is_Imported (E);
11705 -- For subprogram, set Import_Pragma field
11707 if Is_Subprogram (E) then
11708 Set_Import_Pragma (E, N);
11709 end if;
11711 -- If the entity is an object that is not at the library level,
11712 -- then it is statically allocated. We do not worry about objects
11713 -- with address clauses in this context since they are not really
11714 -- imported in the linker sense.
11716 if Is_Object (E)
11717 and then not Is_Library_Level_Entity (E)
11718 and then No (Address_Clause (E))
11719 then
11720 Set_Is_Statically_Allocated (E);
11721 end if;
11722 end if;
11724 <<OK>> null;
11725 end Set_Imported;
11727 -------------------------
11728 -- Set_Mechanism_Value --
11729 -------------------------
11731 -- Note: the mechanism name has not been analyzed (and cannot indeed be
11732 -- analyzed, since it is semantic nonsense), so we get it in the exact
11733 -- form created by the parser.
11735 procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
11736 procedure Bad_Mechanism;
11737 pragma No_Return (Bad_Mechanism);
11738 -- Signal bad mechanism name
11740 -------------------
11741 -- Bad_Mechanism --
11742 -------------------
11744 procedure Bad_Mechanism is
11745 begin
11746 Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
11747 end Bad_Mechanism;
11749 -- Start of processing for Set_Mechanism_Value
11751 begin
11752 if Mechanism (Ent) /= Default_Mechanism then
11753 Error_Msg_NE
11754 ("mechanism for & has already been set", Mech_Name, Ent);
11755 end if;
11757 -- MECHANISM_NAME ::= value | reference
11759 if Nkind (Mech_Name) = N_Identifier then
11760 if Chars (Mech_Name) = Name_Value then
11761 Set_Mechanism (Ent, By_Copy);
11762 return;
11764 elsif Chars (Mech_Name) = Name_Reference then
11765 Set_Mechanism (Ent, By_Reference);
11766 return;
11768 elsif Chars (Mech_Name) = Name_Copy then
11769 Error_Pragma_Arg
11770 ("bad mechanism name, Value assumed", Mech_Name);
11772 else
11773 Bad_Mechanism;
11774 end if;
11776 else
11777 Bad_Mechanism;
11778 end if;
11779 end Set_Mechanism_Value;
11781 --------------------------
11782 -- Set_Rational_Profile --
11783 --------------------------
11785 -- The Rational profile includes Implicit_Packing, Use_Vads_Size, and
11786 -- extension to the semantics of renaming declarations.
11788 procedure Set_Rational_Profile is
11789 begin
11790 Implicit_Packing := True;
11791 Overriding_Renamings := True;
11792 Use_VADS_Size := True;
11793 end Set_Rational_Profile;
11795 ---------------------------
11796 -- Set_Ravenscar_Profile --
11797 ---------------------------
11799 -- The tasks to be done here are
11801 -- Set required policies
11803 -- pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
11804 -- (For Ravenscar, Jorvik, and GNAT_Extended_Ravenscar profiles)
11805 -- pragma Task_Dispatching_Policy (EDF_Across_Priorities)
11806 -- (For GNAT_Ravenscar_EDF profile)
11807 -- pragma Locking_Policy (Ceiling_Locking)
11809 -- Set Detect_Blocking mode
11811 -- Set required restrictions (see System.Rident for detailed list)
11813 -- Set the No_Dependence rules
11814 -- No_Dependence => Ada.Asynchronous_Task_Control
11815 -- No_Dependence => Ada.Calendar
11816 -- No_Dependence => Ada.Execution_Time.Group_Budget
11817 -- No_Dependence => Ada.Execution_Time.Timers
11818 -- No_Dependence => Ada.Task_Attributes
11819 -- No_Dependence => System.Multiprocessors.Dispatching_Domains
11821 procedure Set_Ravenscar_Profile (Profile : Profile_Name; N : Node_Id) is
11822 procedure Set_Error_Msg_To_Profile_Name;
11823 -- Set Error_Msg_String and Error_Msg_Strlen to the name of the
11824 -- profile.
11826 -----------------------------------
11827 -- Set_Error_Msg_To_Profile_Name --
11828 -----------------------------------
11830 procedure Set_Error_Msg_To_Profile_Name is
11831 Prof_Nam : constant Node_Id :=
11832 Get_Pragma_Arg
11833 (First (Pragma_Argument_Associations (N)));
11835 begin
11836 Get_Name_String (Chars (Prof_Nam));
11837 Adjust_Name_Case (Global_Name_Buffer, Sloc (Prof_Nam));
11838 Error_Msg_Strlen := Name_Len;
11839 Error_Msg_String (1 .. Name_Len) := Name_Buffer (1 .. Name_Len);
11840 end Set_Error_Msg_To_Profile_Name;
11842 Profile_Dispatching_Policy : Character;
11844 -- Start of processing for Set_Ravenscar_Profile
11846 begin
11847 -- pragma Task_Dispatching_Policy (EDF_Across_Priorities)
11849 if Profile = GNAT_Ravenscar_EDF then
11850 Profile_Dispatching_Policy := 'E';
11852 -- pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
11854 else
11855 Profile_Dispatching_Policy := 'F';
11856 end if;
11858 if Task_Dispatching_Policy /= ' '
11859 and then Task_Dispatching_Policy /= Profile_Dispatching_Policy
11860 then
11861 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
11862 Set_Error_Msg_To_Profile_Name;
11863 Error_Pragma ("Profile (~) incompatible with policy#");
11865 -- Set the FIFO_Within_Priorities policy, but always preserve
11866 -- System_Location since we like the error message with the run time
11867 -- name.
11869 else
11870 Task_Dispatching_Policy := Profile_Dispatching_Policy;
11872 if Task_Dispatching_Policy_Sloc /= System_Location then
11873 Task_Dispatching_Policy_Sloc := Loc;
11874 end if;
11875 end if;
11877 -- pragma Locking_Policy (Ceiling_Locking)
11879 if Locking_Policy /= ' '
11880 and then Locking_Policy /= 'C'
11881 then
11882 Error_Msg_Sloc := Locking_Policy_Sloc;
11883 Set_Error_Msg_To_Profile_Name;
11884 Error_Pragma ("Profile (~) incompatible with policy#");
11886 -- Set the Ceiling_Locking policy, but preserve System_Location since
11887 -- we like the error message with the run time name.
11889 else
11890 Locking_Policy := 'C';
11892 if Locking_Policy_Sloc /= System_Location then
11893 Locking_Policy_Sloc := Loc;
11894 end if;
11895 end if;
11897 -- pragma Detect_Blocking
11899 Detect_Blocking := True;
11901 -- Set the corresponding restrictions
11903 Set_Profile_Restrictions
11904 (Profile, N, Warn => Treat_Restrictions_As_Warnings);
11906 -- Set the No_Dependence restrictions
11908 -- The following No_Dependence restrictions:
11909 -- No_Dependence => Ada.Asynchronous_Task_Control
11910 -- No_Dependence => Ada.Calendar
11911 -- No_Dependence => Ada.Task_Attributes
11912 -- are already set by previous call to Set_Profile_Restrictions.
11913 -- Really???
11915 -- Set the following restrictions which were added to Ada 2005:
11916 -- No_Dependence => Ada.Execution_Time.Group_Budget
11917 -- No_Dependence => Ada.Execution_Time.Timers
11919 if Ada_Version >= Ada_2005 then
11920 declare
11921 Execution_Time : constant Node_Id :=
11922 Sel_Comp ("ada", "execution_time", Loc);
11923 Group_Budgets : constant Node_Id :=
11924 Sel_Comp (Execution_Time, "group_budgets");
11925 Timers : constant Node_Id :=
11926 Sel_Comp (Execution_Time, "timers");
11927 begin
11928 Set_Restriction_No_Dependence
11929 (Unit => Group_Budgets,
11930 Warn => Treat_Restrictions_As_Warnings,
11931 Profile => Ravenscar);
11932 Set_Restriction_No_Dependence
11933 (Unit => Timers,
11934 Warn => Treat_Restrictions_As_Warnings,
11935 Profile => Ravenscar);
11936 end;
11937 end if;
11939 -- Set the following restriction which was added to Ada 2012 (see
11940 -- AI05-0171):
11941 -- No_Dependence => System.Multiprocessors.Dispatching_Domains
11943 if Ada_Version >= Ada_2012 then
11944 Set_Restriction_No_Dependence
11945 (Sel_Comp
11946 (Sel_Comp ("system", "multiprocessors", Loc),
11947 "dispatching_domains"),
11948 Warn => Treat_Restrictions_As_Warnings,
11949 Profile => Ravenscar);
11951 -- Set the following restriction which was added to Ada 2022,
11952 -- but as a binding interpretation:
11953 -- No_Dependence => Ada.Synchronous_Barriers
11954 -- for Ravenscar (and therefore for Ravenscar variants) but not
11955 -- for Jorvik. The unit Ada.Synchronous_Barriers was introduced
11956 -- in Ada2012 (AI05-0174).
11958 if Profile /= Jorvik then
11959 Set_Restriction_No_Dependence
11960 (Sel_Comp ("ada", "synchronous_barriers", Loc),
11961 Warn => Treat_Restrictions_As_Warnings,
11962 Profile => Ravenscar);
11963 end if;
11964 end if;
11966 end Set_Ravenscar_Profile;
11968 -- Start of processing for Analyze_Pragma
11970 begin
11971 -- The following code is a defense against recursion. Not clear that
11972 -- this can happen legitimately, but perhaps some error situations can
11973 -- cause it, and we did see this recursion during testing.
11975 if Analyzed (N) then
11976 return;
11977 else
11978 Set_Analyzed (N);
11979 end if;
11981 Check_Restriction_No_Use_Of_Pragma (N);
11983 if Is_Aspect_Id (Chars (Pragma_Identifier (N))) then
11984 -- 6.1/3 No_Specification_of_Aspect: Identifies an aspect for which
11985 -- no aspect_specification, attribute_definition_clause, or pragma
11986 -- is given.
11987 Check_Restriction_No_Specification_Of_Aspect (N);
11988 end if;
11990 -- Ignore pragma if Ignore_Pragma applies. Also ignore pragma
11991 -- Default_Scalar_Storage_Order if the -gnatI switch was given.
11993 if Should_Ignore_Pragma_Sem (N)
11994 or else (Prag_Id = Pragma_Default_Scalar_Storage_Order
11995 and then Ignore_Rep_Clauses)
11996 then
11997 return;
11998 end if;
12000 -- Deal with unrecognized pragma
12002 if not Is_Pragma_Name (Pname) then
12003 declare
12004 Msg_Issued : Boolean := False;
12005 begin
12006 Check_Restriction
12007 (Msg_Issued, No_Unrecognized_Pragmas, Pragma_Identifier (N));
12008 if not Msg_Issued and then Warn_On_Unrecognized_Pragma then
12009 Error_Msg_Name_1 := Pname;
12010 Error_Msg_N ("?g?unrecognized pragma%!", Pragma_Identifier (N));
12012 for PN in First_Pragma_Name .. Last_Pragma_Name loop
12013 if Is_Bad_Spelling_Of (Pname, PN) then
12014 Error_Msg_Name_1 := PN;
12015 Error_Msg_N -- CODEFIX
12016 ("\?g?possible misspelling of %!",
12017 Pragma_Identifier (N));
12018 exit;
12019 end if;
12020 end loop;
12021 end if;
12022 end;
12024 return;
12025 end if;
12027 -- Here to start processing for recognized pragma
12029 Pname := Original_Aspect_Pragma_Name (N);
12031 -- Capture setting of Opt.Uneval_Old
12033 case Opt.Uneval_Old is
12034 when 'A' =>
12035 Set_Uneval_Old_Accept (N);
12037 when 'E' =>
12038 null;
12040 when 'W' =>
12041 Set_Uneval_Old_Warn (N);
12043 when others =>
12044 raise Program_Error;
12045 end case;
12047 -- Check applicable policy. We skip this if Is_Checked or Is_Ignored
12048 -- is already set, indicating that we have already checked the policy
12049 -- at the right point. This happens for example in the case of a pragma
12050 -- that is derived from an Aspect.
12052 if Is_Ignored (N) or else Is_Checked (N) then
12053 null;
12055 -- For a pragma that is a rewriting of another pragma, copy the
12056 -- Is_Checked/Is_Ignored status from the rewritten pragma.
12058 elsif Is_Rewrite_Substitution (N)
12059 and then Nkind (Original_Node (N)) = N_Pragma
12060 then
12061 Set_Is_Ignored (N, Is_Ignored (Original_Node (N)));
12062 Set_Is_Checked (N, Is_Checked (Original_Node (N)));
12064 -- Skip querying the applicable policy at this point for dynamic
12065 -- predicate checks since they rely on the policy applicable in
12066 -- the context of their associated type declaration (and this
12067 -- pragma check has been internally added by the frontend at the
12068 -- point where the runtime check must be performed).
12070 elsif not Comes_From_Source (N)
12071 and then Chars (Pragma_Identifier (N)) = Name_Check
12072 and then Pname = Name_Dynamic_Predicate
12073 then
12074 null;
12076 -- Otherwise query the applicable policy at this point
12078 else
12079 Check_Applicable_Policy (N);
12081 -- If pragma is disabled, rewrite as NULL and skip analysis
12083 if Is_Disabled (N) then
12084 Rewrite (N, Make_Null_Statement (Loc));
12085 Analyze (N);
12086 raise Pragma_Exit;
12087 end if;
12088 end if;
12090 -- Mark assertion pragmas as Ghost depending on their enclosing context
12092 if Assertion_Expression_Pragma (Prag_Id) then
12093 Mark_Ghost_Pragma (N, Current_Scope);
12094 end if;
12096 -- Preset arguments
12098 Arg_Count := List_Length (Pragma_Argument_Associations (N));
12099 Arg1 := First (Pragma_Argument_Associations (N));
12100 Arg2 := Empty;
12101 Arg3 := Empty;
12102 Arg4 := Empty;
12103 Arg5 := Empty;
12105 if Present (Arg1) then
12106 Arg2 := Next (Arg1);
12108 if Present (Arg2) then
12109 Arg3 := Next (Arg2);
12111 if Present (Arg3) then
12112 Arg4 := Next (Arg3);
12114 if Present (Arg4) then
12115 Arg5 := Next (Arg4);
12116 end if;
12117 end if;
12118 end if;
12119 end if;
12121 -- An enumeration type defines the pragmas that are supported by the
12122 -- implementation. Get_Pragma_Id (in package Prag) transforms a name
12123 -- into the corresponding enumeration value for the following case.
12125 case Prag_Id is
12127 -----------------
12128 -- Abort_Defer --
12129 -----------------
12131 -- pragma Abort_Defer;
12133 when Pragma_Abort_Defer =>
12134 GNAT_Pragma;
12135 Check_Arg_Count (0);
12137 -- The only required semantic processing is to check the
12138 -- placement. This pragma must appear at the start of the
12139 -- statement sequence of a handled sequence of statements.
12141 if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
12142 or else N /= First (Statements (Parent (N)))
12143 then
12144 Pragma_Misplaced;
12145 end if;
12147 --------------------
12148 -- Abstract_State --
12149 --------------------
12151 -- pragma Abstract_State (ABSTRACT_STATE_LIST);
12153 -- ABSTRACT_STATE_LIST ::=
12154 -- null
12155 -- | STATE_NAME_WITH_OPTIONS
12156 -- | (STATE_NAME_WITH_OPTIONS {, STATE_NAME_WITH_OPTIONS})
12158 -- STATE_NAME_WITH_OPTIONS ::=
12159 -- STATE_NAME
12160 -- | (STATE_NAME with OPTION_LIST)
12162 -- OPTION_LIST ::= OPTION {, OPTION}
12164 -- OPTION ::=
12165 -- SIMPLE_OPTION
12166 -- | NAME_VALUE_OPTION
12168 -- SIMPLE_OPTION ::= Ghost | Relaxed_Initialization | Synchronous
12170 -- NAME_VALUE_OPTION ::=
12171 -- Part_Of => ABSTRACT_STATE
12172 -- | External [=> EXTERNAL_PROPERTY_LIST]
12174 -- EXTERNAL_PROPERTY_LIST ::=
12175 -- EXTERNAL_PROPERTY
12176 -- | (EXTERNAL_PROPERTY {, EXTERNAL_PROPERTY})
12178 -- EXTERNAL_PROPERTY ::=
12179 -- Async_Readers [=> boolean_EXPRESSION]
12180 -- | Async_Writers [=> boolean_EXPRESSION]
12181 -- | Effective_Reads [=> boolean_EXPRESSION]
12182 -- | Effective_Writes [=> boolean_EXPRESSION]
12183 -- others => boolean_EXPRESSION
12185 -- STATE_NAME ::= defining_identifier
12187 -- ABSTRACT_STATE ::= name
12189 -- Characteristics:
12191 -- * Analysis - The annotation is fully analyzed immediately upon
12192 -- elaboration as it cannot forward reference entities.
12194 -- * Expansion - None.
12196 -- * Template - The annotation utilizes the generic template of the
12197 -- related package declaration.
12199 -- * Globals - The annotation cannot reference global entities.
12201 -- * Instance - The annotation is instantiated automatically when
12202 -- the related generic package is instantiated.
12204 when Pragma_Abstract_State => Abstract_State : declare
12205 Missing_Parentheses : Boolean := False;
12206 -- Flag set when a state declaration with options is not properly
12207 -- parenthesized.
12209 -- Flags used to verify the consistency of states
12211 Non_Null_Seen : Boolean := False;
12212 Null_Seen : Boolean := False;
12214 procedure Analyze_Abstract_State
12215 (State : Node_Id;
12216 Pack_Id : Entity_Id);
12217 -- Verify the legality of a single state declaration. Create and
12218 -- decorate a state abstraction entity and introduce it into the
12219 -- visibility chain. Pack_Id denotes the entity or the related
12220 -- package where pragma Abstract_State appears.
12222 procedure Malformed_State_Error (State : Node_Id);
12223 -- Emit an error concerning the illegal declaration of abstract
12224 -- state State. This routine diagnoses syntax errors that lead to
12225 -- a different parse tree. The error is issued regardless of the
12226 -- SPARK mode in effect.
12228 ----------------------------
12229 -- Analyze_Abstract_State --
12230 ----------------------------
12232 procedure Analyze_Abstract_State
12233 (State : Node_Id;
12234 Pack_Id : Entity_Id)
12236 -- Flags used to verify the consistency of options
12238 AR_Seen : Boolean := False;
12239 AW_Seen : Boolean := False;
12240 ER_Seen : Boolean := False;
12241 EW_Seen : Boolean := False;
12242 External_Seen : Boolean := False;
12243 Ghost_Seen : Boolean := False;
12244 Others_Seen : Boolean := False;
12245 Part_Of_Seen : Boolean := False;
12246 Synchronous_Seen : Boolean := False;
12248 -- Flags used to store the static value of all external states'
12249 -- expressions.
12251 AR_Val : Boolean := False;
12252 AW_Val : Boolean := False;
12253 ER_Val : Boolean := False;
12254 EW_Val : Boolean := False;
12256 State_Id : Entity_Id := Empty;
12257 -- The entity to be generated for the current state declaration
12259 procedure Analyze_External_Option (Opt : Node_Id);
12260 -- Verify the legality of option External
12262 procedure Analyze_External_Property
12263 (Prop : Node_Id;
12264 Expr : Node_Id := Empty);
12265 -- Verify the legailty of a single external property. Prop
12266 -- denotes the external property. Expr is the expression used
12267 -- to set the property.
12269 procedure Analyze_Part_Of_Option (Opt : Node_Id);
12270 -- Verify the legality of option Part_Of
12272 procedure Check_Duplicate_Option
12273 (Opt : Node_Id;
12274 Status : in out Boolean);
12275 -- Flag Status denotes whether a particular option has been
12276 -- seen while processing a state. This routine verifies that
12277 -- Opt is not a duplicate option and sets the flag Status
12278 -- (SPARK RM 7.1.4(1)).
12280 procedure Check_Duplicate_Property
12281 (Prop : Node_Id;
12282 Status : in out Boolean);
12283 -- Flag Status denotes whether a particular property has been
12284 -- seen while processing option External. This routine verifies
12285 -- that Prop is not a duplicate property and sets flag Status.
12286 -- Opt is not a duplicate property and sets the flag Status.
12287 -- (SPARK RM 7.1.4(2))
12289 procedure Check_Ghost_Synchronous;
12290 -- Ensure that the abstract state is not subject to both Ghost
12291 -- and Synchronous simple options. Emit an error if this is the
12292 -- case.
12294 procedure Create_Abstract_State
12295 (Nam : Name_Id;
12296 Decl : Node_Id;
12297 Loc : Source_Ptr;
12298 Is_Null : Boolean);
12299 -- Generate an abstract state entity with name Nam and enter it
12300 -- into visibility. Decl is the "declaration" of the state as
12301 -- it appears in pragma Abstract_State. Loc is the location of
12302 -- the related state "declaration". Flag Is_Null should be set
12303 -- when the associated Abstract_State pragma defines a null
12304 -- state.
12306 -----------------------------
12307 -- Analyze_External_Option --
12308 -----------------------------
12310 procedure Analyze_External_Option (Opt : Node_Id) is
12311 Errors : constant Nat := Serious_Errors_Detected;
12312 Prop : Node_Id;
12313 Props : Node_Id := Empty;
12315 begin
12316 if Nkind (Opt) = N_Component_Association then
12317 Props := Expression (Opt);
12318 end if;
12320 -- External state with properties
12322 if Present (Props) then
12324 -- Multiple properties appear as an aggregate
12326 if Nkind (Props) = N_Aggregate then
12328 -- Simple property form
12330 Prop := First (Expressions (Props));
12331 while Present (Prop) loop
12332 Analyze_External_Property (Prop);
12333 Next (Prop);
12334 end loop;
12336 -- Property with expression form
12338 Prop := First (Component_Associations (Props));
12339 while Present (Prop) loop
12340 Analyze_External_Property
12341 (Prop => First (Choices (Prop)),
12342 Expr => Expression (Prop));
12344 Next (Prop);
12345 end loop;
12347 -- Single property
12349 else
12350 Analyze_External_Property (Props);
12351 end if;
12353 -- An external state defined without any properties defaults
12354 -- all properties to True.
12356 else
12357 AR_Val := True;
12358 AW_Val := True;
12359 ER_Val := True;
12360 EW_Val := True;
12361 end if;
12363 -- Once all external properties have been processed, verify
12364 -- their mutual interaction. Do not perform the check when
12365 -- at least one of the properties is illegal as this will
12366 -- produce a bogus error.
12368 if Errors = Serious_Errors_Detected then
12369 Check_External_Properties
12370 (State, AR_Val, AW_Val, ER_Val, EW_Val);
12371 end if;
12372 end Analyze_External_Option;
12374 -------------------------------
12375 -- Analyze_External_Property --
12376 -------------------------------
12378 procedure Analyze_External_Property
12379 (Prop : Node_Id;
12380 Expr : Node_Id := Empty)
12382 Expr_Val : Boolean;
12384 begin
12385 -- Check the placement of "others" (if available)
12387 if Nkind (Prop) = N_Others_Choice then
12388 if Others_Seen then
12389 SPARK_Msg_N
12390 ("only one OTHERS choice allowed in option External",
12391 Prop);
12392 else
12393 Others_Seen := True;
12394 end if;
12396 elsif Others_Seen then
12397 SPARK_Msg_N
12398 ("OTHERS must be the last property in option External",
12399 Prop);
12401 -- The only remaining legal options are the four predefined
12402 -- external properties.
12404 elsif Nkind (Prop) = N_Identifier
12405 and then Chars (Prop) in Name_Async_Readers
12406 | Name_Async_Writers
12407 | Name_Effective_Reads
12408 | Name_Effective_Writes
12409 then
12410 null;
12412 -- Otherwise the construct is not a valid property
12414 else
12415 SPARK_Msg_N ("invalid external state property", Prop);
12416 return;
12417 end if;
12419 -- Ensure that the expression of the external state property
12420 -- is static Boolean (if applicable) (SPARK RM 7.1.2(5)).
12422 if Present (Expr) then
12423 Analyze_And_Resolve (Expr, Standard_Boolean);
12425 if Is_OK_Static_Expression (Expr) then
12426 Expr_Val := Is_True (Expr_Value (Expr));
12427 else
12428 SPARK_Msg_N
12429 ("expression of external state property must be "
12430 & "static", Expr);
12431 return;
12432 end if;
12434 -- The lack of expression defaults the property to True
12436 else
12437 Expr_Val := True;
12438 end if;
12440 -- Named properties
12442 if Nkind (Prop) = N_Identifier then
12443 if Chars (Prop) = Name_Async_Readers then
12444 Check_Duplicate_Property (Prop, AR_Seen);
12445 AR_Val := Expr_Val;
12447 elsif Chars (Prop) = Name_Async_Writers then
12448 Check_Duplicate_Property (Prop, AW_Seen);
12449 AW_Val := Expr_Val;
12451 elsif Chars (Prop) = Name_Effective_Reads then
12452 Check_Duplicate_Property (Prop, ER_Seen);
12453 ER_Val := Expr_Val;
12455 else
12456 Check_Duplicate_Property (Prop, EW_Seen);
12457 EW_Val := Expr_Val;
12458 end if;
12460 -- The handling of property "others" must take into account
12461 -- all other named properties that have been encountered so
12462 -- far. Only those that have not been seen are affected by
12463 -- "others".
12465 else
12466 if not AR_Seen then
12467 AR_Val := Expr_Val;
12468 end if;
12470 if not AW_Seen then
12471 AW_Val := Expr_Val;
12472 end if;
12474 if not ER_Seen then
12475 ER_Val := Expr_Val;
12476 end if;
12478 if not EW_Seen then
12479 EW_Val := Expr_Val;
12480 end if;
12481 end if;
12482 end Analyze_External_Property;
12484 ----------------------------
12485 -- Analyze_Part_Of_Option --
12486 ----------------------------
12488 procedure Analyze_Part_Of_Option (Opt : Node_Id) is
12489 Encap : constant Node_Id := Expression (Opt);
12490 Constits : Elist_Id;
12491 Encap_Id : Entity_Id;
12492 Legal : Boolean;
12494 begin
12495 Check_Duplicate_Option (Opt, Part_Of_Seen);
12497 Analyze_Part_Of
12498 (Indic => First (Choices (Opt)),
12499 Item_Id => State_Id,
12500 Encap => Encap,
12501 Encap_Id => Encap_Id,
12502 Legal => Legal);
12504 -- The Part_Of indicator transforms the abstract state into
12505 -- a constituent of the encapsulating state or single
12506 -- concurrent type.
12508 if Legal then
12509 pragma Assert (Present (Encap_Id));
12510 Constits := Part_Of_Constituents (Encap_Id);
12512 if No (Constits) then
12513 Constits := New_Elmt_List;
12514 Set_Part_Of_Constituents (Encap_Id, Constits);
12515 end if;
12517 Append_Elmt (State_Id, Constits);
12518 Set_Encapsulating_State (State_Id, Encap_Id);
12519 end if;
12520 end Analyze_Part_Of_Option;
12522 ----------------------------
12523 -- Check_Duplicate_Option --
12524 ----------------------------
12526 procedure Check_Duplicate_Option
12527 (Opt : Node_Id;
12528 Status : in out Boolean)
12530 begin
12531 if Status then
12532 SPARK_Msg_N ("duplicate state option", Opt);
12533 end if;
12535 Status := True;
12536 end Check_Duplicate_Option;
12538 ------------------------------
12539 -- Check_Duplicate_Property --
12540 ------------------------------
12542 procedure Check_Duplicate_Property
12543 (Prop : Node_Id;
12544 Status : in out Boolean)
12546 begin
12547 if Status then
12548 SPARK_Msg_N ("duplicate external property", Prop);
12549 end if;
12551 Status := True;
12552 end Check_Duplicate_Property;
12554 -----------------------------
12555 -- Check_Ghost_Synchronous --
12556 -----------------------------
12558 procedure Check_Ghost_Synchronous is
12559 begin
12560 -- A synchronized abstract state cannot be Ghost and vice
12561 -- versa (SPARK RM 6.9(21)).
12563 if Ghost_Seen and Synchronous_Seen then
12564 SPARK_Msg_N ("synchronized state cannot be ghost", State);
12565 end if;
12566 end Check_Ghost_Synchronous;
12568 ---------------------------
12569 -- Create_Abstract_State --
12570 ---------------------------
12572 procedure Create_Abstract_State
12573 (Nam : Name_Id;
12574 Decl : Node_Id;
12575 Loc : Source_Ptr;
12576 Is_Null : Boolean)
12578 begin
12579 -- The abstract state may be semi-declared when the related
12580 -- package was withed through a limited with clause. In that
12581 -- case reuse the entity to fully declare the state.
12583 if Present (Decl) and then Present (Entity (Decl)) then
12584 State_Id := Entity (Decl);
12586 -- Otherwise the elaboration of pragma Abstract_State
12587 -- declares the state.
12589 else
12590 State_Id := Make_Defining_Identifier (Loc, Nam);
12592 if Present (Decl) then
12593 Set_Entity (Decl, State_Id);
12594 end if;
12595 end if;
12597 -- Null states never come from source
12599 Set_Comes_From_Source (State_Id, not Is_Null);
12600 Set_Parent (State_Id, State);
12601 Mutate_Ekind (State_Id, E_Abstract_State);
12602 Set_Is_Not_Self_Hidden (State_Id);
12603 Set_Etype (State_Id, Standard_Void_Type);
12604 Set_Encapsulating_State (State_Id, Empty);
12606 -- Set the SPARK mode from the current context
12608 Set_SPARK_Pragma (State_Id, SPARK_Mode_Pragma);
12609 Set_SPARK_Pragma_Inherited (State_Id);
12611 -- An abstract state declared within a Ghost region becomes
12612 -- Ghost (SPARK RM 6.9(2)).
12614 if Ghost_Mode > None or else Is_Ghost_Entity (Pack_Id) then
12615 Set_Is_Ghost_Entity (State_Id);
12616 end if;
12618 -- Establish a link between the state declaration and the
12619 -- abstract state entity. Note that a null state remains as
12620 -- N_Null and does not carry any linkages.
12622 if not Is_Null then
12623 if Present (Decl) then
12624 Set_Entity (Decl, State_Id);
12625 Set_Etype (Decl, Standard_Void_Type);
12626 end if;
12628 -- Every non-null state must be defined, nameable and
12629 -- resolvable.
12631 Push_Scope (Pack_Id);
12632 Generate_Definition (State_Id);
12633 Enter_Name (State_Id);
12634 Pop_Scope;
12635 end if;
12636 end Create_Abstract_State;
12638 -- Local variables
12640 Opt : Node_Id;
12641 Opt_Nam : Node_Id;
12643 -- Start of processing for Analyze_Abstract_State
12645 begin
12646 -- A package with a null abstract state is not allowed to
12647 -- declare additional states.
12649 if Null_Seen then
12650 SPARK_Msg_NE
12651 ("package & has null abstract state", State, Pack_Id);
12653 -- Null states appear as internally generated entities
12655 elsif Nkind (State) = N_Null then
12656 Create_Abstract_State
12657 (Nam => New_Internal_Name ('S'),
12658 Decl => Empty,
12659 Loc => Sloc (State),
12660 Is_Null => True);
12661 Null_Seen := True;
12663 -- Catch a case where a null state appears in a list of
12664 -- non-null states.
12666 if Non_Null_Seen then
12667 SPARK_Msg_NE
12668 ("package & has non-null abstract state",
12669 State, Pack_Id);
12670 end if;
12672 -- Simple state declaration
12674 elsif Nkind (State) = N_Identifier then
12675 Create_Abstract_State
12676 (Nam => Chars (State),
12677 Decl => State,
12678 Loc => Sloc (State),
12679 Is_Null => False);
12680 Non_Null_Seen := True;
12682 -- State declaration with various options. This construct
12683 -- appears as an extension aggregate in the tree.
12685 elsif Nkind (State) = N_Extension_Aggregate then
12686 if Nkind (Ancestor_Part (State)) = N_Identifier then
12687 Create_Abstract_State
12688 (Nam => Chars (Ancestor_Part (State)),
12689 Decl => Ancestor_Part (State),
12690 Loc => Sloc (Ancestor_Part (State)),
12691 Is_Null => False);
12692 Non_Null_Seen := True;
12693 else
12694 SPARK_Msg_N
12695 ("state name must be an identifier",
12696 Ancestor_Part (State));
12697 end if;
12699 -- Options External, Ghost and Synchronous appear as
12700 -- expressions.
12702 Opt := First (Expressions (State));
12703 while Present (Opt) loop
12704 if Nkind (Opt) = N_Identifier then
12706 -- External
12708 if Chars (Opt) = Name_External then
12709 Check_Duplicate_Option (Opt, External_Seen);
12710 Analyze_External_Option (Opt);
12712 -- Ghost
12714 elsif Chars (Opt) = Name_Ghost then
12715 Check_Duplicate_Option (Opt, Ghost_Seen);
12716 Check_Ghost_Synchronous;
12718 if Present (State_Id) then
12719 Set_Is_Ghost_Entity (State_Id);
12720 end if;
12722 -- Synchronous
12724 elsif Chars (Opt) = Name_Synchronous then
12725 Check_Duplicate_Option (Opt, Synchronous_Seen);
12726 Check_Ghost_Synchronous;
12728 -- Option Part_Of without an encapsulating state is
12729 -- illegal (SPARK RM 7.1.4(8)).
12731 elsif Chars (Opt) = Name_Part_Of then
12732 SPARK_Msg_N
12733 ("indicator Part_Of must denote abstract state, "
12734 & "single protected type or single task type",
12735 Opt);
12737 -- Do not emit an error message when a previous state
12738 -- declaration with options was not parenthesized as
12739 -- the option is actually another state declaration.
12741 -- with Abstract_State
12742 -- (State_1 with ..., -- missing parentheses
12743 -- (State_2 with ...),
12744 -- State_3) -- ok state declaration
12746 elsif Missing_Parentheses then
12747 null;
12749 -- Otherwise the option is not allowed. Note that it
12750 -- is not possible to distinguish between an option
12751 -- and a state declaration when a previous state with
12752 -- options not properly parentheses.
12754 -- with Abstract_State
12755 -- (State_1 with ..., -- missing parentheses
12756 -- State_2); -- could be an option
12758 else
12759 SPARK_Msg_N
12760 ("simple option not allowed in state declaration",
12761 Opt);
12762 end if;
12764 -- Catch a case where missing parentheses around a state
12765 -- declaration with options cause a subsequent state
12766 -- declaration with options to be treated as an option.
12768 -- with Abstract_State
12769 -- (State_1 with ..., -- missing parentheses
12770 -- (State_2 with ...))
12772 elsif Nkind (Opt) = N_Extension_Aggregate then
12773 Missing_Parentheses := True;
12774 SPARK_Msg_N
12775 ("state declaration must be parenthesized",
12776 Ancestor_Part (State));
12778 -- Otherwise the option is malformed
12780 else
12781 SPARK_Msg_N ("malformed option", Opt);
12782 end if;
12784 Next (Opt);
12785 end loop;
12787 -- Options External and Part_Of appear as component
12788 -- associations.
12790 Opt := First (Component_Associations (State));
12791 while Present (Opt) loop
12792 Opt_Nam := First (Choices (Opt));
12794 if Nkind (Opt_Nam) = N_Identifier then
12795 if Chars (Opt_Nam) = Name_External then
12796 Analyze_External_Option (Opt);
12798 elsif Chars (Opt_Nam) = Name_Part_Of then
12799 Analyze_Part_Of_Option (Opt);
12801 else
12802 SPARK_Msg_N ("invalid state option", Opt);
12803 end if;
12804 else
12805 SPARK_Msg_N ("invalid state option", Opt);
12806 end if;
12808 Next (Opt);
12809 end loop;
12811 -- Any other attempt to declare a state is illegal
12813 else
12814 Malformed_State_Error (State);
12815 return;
12816 end if;
12818 -- Guard against a junk state. In such cases no entity is
12819 -- generated and the subsequent checks cannot be applied.
12821 if Present (State_Id) then
12823 -- Verify whether the state does not introduce an illegal
12824 -- hidden state within a package subject to a null abstract
12825 -- state.
12827 Check_No_Hidden_State (State_Id);
12829 -- Check whether the lack of option Part_Of agrees with the
12830 -- placement of the abstract state with respect to the state
12831 -- space.
12833 if not Part_Of_Seen then
12834 Check_Missing_Part_Of (State_Id);
12835 end if;
12837 -- Associate the state with its related package
12839 if No (Abstract_States (Pack_Id)) then
12840 Set_Abstract_States (Pack_Id, New_Elmt_List);
12841 end if;
12843 Append_Elmt (State_Id, Abstract_States (Pack_Id));
12844 end if;
12845 end Analyze_Abstract_State;
12847 ---------------------------
12848 -- Malformed_State_Error --
12849 ---------------------------
12851 procedure Malformed_State_Error (State : Node_Id) is
12852 begin
12853 Error_Msg_N ("malformed abstract state declaration", State);
12855 -- An abstract state with a simple option is being declared
12856 -- with "=>" rather than the legal "with". The state appears
12857 -- as a component association.
12859 if Nkind (State) = N_Component_Association then
12860 Error_Msg_N ("\use WITH to specify simple option", State);
12861 end if;
12862 end Malformed_State_Error;
12864 -- Local variables
12866 Pack_Decl : Node_Id;
12867 Pack_Id : Entity_Id;
12868 State : Node_Id;
12869 States : Node_Id;
12871 -- Start of processing for Abstract_State
12873 begin
12874 GNAT_Pragma;
12875 Check_No_Identifiers;
12876 Check_Arg_Count (1);
12878 Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
12880 if Nkind (Pack_Decl) not in
12881 N_Generic_Package_Declaration | N_Package_Declaration
12882 then
12883 Pragma_Misplaced;
12884 end if;
12886 Pack_Id := Defining_Entity (Pack_Decl);
12888 -- A pragma that applies to a Ghost entity becomes Ghost for the
12889 -- purposes of legality checks and removal of ignored Ghost code.
12891 Mark_Ghost_Pragma (N, Pack_Id);
12892 Ensure_Aggregate_Form (Get_Argument (N, Pack_Id));
12894 -- Chain the pragma on the contract for completeness
12896 Add_Contract_Item (N, Pack_Id);
12898 -- The legality checks of pragmas Abstract_State, Initializes, and
12899 -- Initial_Condition are affected by the SPARK mode in effect. In
12900 -- addition, these three pragmas are subject to an inherent order:
12902 -- 1) Abstract_State
12903 -- 2) Initializes
12904 -- 3) Initial_Condition
12906 -- Analyze all these pragmas in the order outlined above
12908 Analyze_If_Present (Pragma_SPARK_Mode);
12909 States := Expression (Get_Argument (N, Pack_Id));
12911 -- Multiple non-null abstract states appear as an aggregate
12913 if Nkind (States) = N_Aggregate then
12914 State := First (Expressions (States));
12915 while Present (State) loop
12916 Analyze_Abstract_State (State, Pack_Id);
12917 Next (State);
12918 end loop;
12920 -- An abstract state with a simple option is being illegaly
12921 -- declared with "=>" rather than "with". In this case the
12922 -- state declaration appears as a component association.
12924 if Present (Component_Associations (States)) then
12925 State := First (Component_Associations (States));
12926 while Present (State) loop
12927 Malformed_State_Error (State);
12928 Next (State);
12929 end loop;
12930 end if;
12932 -- Various forms of a single abstract state. Note that these may
12933 -- include malformed state declarations.
12935 else
12936 Analyze_Abstract_State (States, Pack_Id);
12937 end if;
12939 Analyze_If_Present (Pragma_Initializes);
12940 Analyze_If_Present (Pragma_Initial_Condition);
12941 end Abstract_State;
12943 ------------
12944 -- Ada_83 --
12945 ------------
12947 -- pragma Ada_83;
12949 -- Note: this pragma also has some specific processing in Par.Prag
12950 -- because we want to set the Ada version mode during parsing.
12952 when Pragma_Ada_83 =>
12953 GNAT_Pragma;
12954 Check_Arg_Count (0);
12956 -- We really should check unconditionally for proper configuration
12957 -- pragma placement, since we really don't want mixed Ada modes
12958 -- within a single unit, and the GNAT reference manual has always
12959 -- said this was a configuration pragma, but we did not check and
12960 -- are hesitant to add the check now.
12962 -- However, we really cannot tolerate mixing Ada 2005 or Ada 2012
12963 -- with Ada 83 or Ada 95, so we must check if we are in Ada 2005
12964 -- or Ada 2012 mode.
12966 if Ada_Version >= Ada_2005 then
12967 Check_Valid_Configuration_Pragma;
12968 end if;
12970 -- Now set Ada 83 mode
12972 if Latest_Ada_Only then
12973 Error_Pragma ("??pragma% ignored");
12974 else
12975 Ada_Version := Ada_83;
12976 Ada_Version_Explicit := Ada_83;
12977 Ada_Version_Pragma := N;
12978 end if;
12980 ------------
12981 -- Ada_95 --
12982 ------------
12984 -- pragma Ada_95;
12986 -- Note: this pragma also has some specific processing in Par.Prag
12987 -- because we want to set the Ada 83 version mode during parsing.
12989 when Pragma_Ada_95 =>
12990 GNAT_Pragma;
12991 Check_Arg_Count (0);
12993 -- We really should check unconditionally for proper configuration
12994 -- pragma placement, since we really don't want mixed Ada modes
12995 -- within a single unit, and the GNAT reference manual has always
12996 -- said this was a configuration pragma, but we did not check and
12997 -- are hesitant to add the check now.
12999 -- However, we really cannot tolerate mixing Ada 2005 with Ada 83
13000 -- or Ada 95, so we must check if we are in Ada 2005 mode.
13002 if Ada_Version >= Ada_2005 then
13003 Check_Valid_Configuration_Pragma;
13004 end if;
13006 -- Now set Ada 95 mode
13008 if Latest_Ada_Only then
13009 Error_Pragma ("??pragma% ignored");
13010 else
13011 Ada_Version := Ada_95;
13012 Ada_Version_Explicit := Ada_95;
13013 Ada_Version_Pragma := N;
13014 end if;
13016 ---------------------
13017 -- Ada_05/Ada_2005 --
13018 ---------------------
13020 -- pragma Ada_05;
13021 -- pragma Ada_05 (LOCAL_NAME);
13023 -- pragma Ada_2005;
13024 -- pragma Ada_2005 (LOCAL_NAME):
13026 -- Note: these pragmas also have some specific processing in Par.Prag
13027 -- because we want to set the Ada 2005 version mode during parsing.
13029 -- The one argument form is used for managing the transition from
13030 -- Ada 95 to Ada 2005 in the run-time library. If an entity is marked
13031 -- as Ada_2005 only, then referencing the entity in Ada_83 or Ada_95
13032 -- mode will generate a warning. In addition, in Ada_83 or Ada_95
13033 -- mode, a preference rule is established which does not choose
13034 -- such an entity unless it is unambiguously specified. This avoids
13035 -- extra subprograms marked this way from generating ambiguities in
13036 -- otherwise legal pre-Ada_2005 programs. The one argument form is
13037 -- intended for exclusive use in the GNAT run-time library.
13039 when Pragma_Ada_05
13040 | Pragma_Ada_2005
13042 declare
13043 E_Id : Node_Id;
13045 begin
13046 GNAT_Pragma;
13048 if Arg_Count = 1 then
13049 Check_Arg_Is_Local_Name (Arg1);
13050 E_Id := Get_Pragma_Arg (Arg1);
13052 if Etype (E_Id) = Any_Type then
13053 return;
13054 end if;
13056 Set_Is_Ada_2005_Only (Entity (E_Id));
13057 Record_Rep_Item (Entity (E_Id), N);
13059 else
13060 Check_Arg_Count (0);
13062 -- For Ada_2005 we unconditionally enforce the documented
13063 -- configuration pragma placement, since we do not want to
13064 -- tolerate mixed modes in a unit involving Ada 2005. That
13065 -- would cause real difficulties for those cases where there
13066 -- are incompatibilities between Ada 95 and Ada 2005.
13068 Check_Valid_Configuration_Pragma;
13070 -- Now set appropriate Ada mode
13072 if Latest_Ada_Only then
13073 Error_Pragma ("??pragma% ignored");
13074 else
13075 Ada_Version := Ada_2005;
13076 Ada_Version_Explicit := Ada_2005;
13077 Ada_Version_Pragma := N;
13078 end if;
13079 end if;
13080 end;
13082 ---------------------
13083 -- Ada_12/Ada_2012 --
13084 ---------------------
13086 -- pragma Ada_12;
13087 -- pragma Ada_12 (LOCAL_NAME);
13089 -- pragma Ada_2012;
13090 -- pragma Ada_2012 (LOCAL_NAME):
13092 -- Note: these pragmas also have some specific processing in Par.Prag
13093 -- because we want to set the Ada 2012 version mode during parsing.
13095 -- The one argument form is used for managing the transition from Ada
13096 -- 2005 to Ada 2012 in the run-time library. If an entity is marked
13097 -- as Ada_2012 only, then referencing the entity in any pre-Ada_2012
13098 -- mode will generate a warning. In addition, in any pre-Ada_2012
13099 -- mode, a preference rule is established which does not choose
13100 -- such an entity unless it is unambiguously specified. This avoids
13101 -- extra subprograms marked this way from generating ambiguities in
13102 -- otherwise legal pre-Ada_2012 programs. The one argument form is
13103 -- intended for exclusive use in the GNAT run-time library.
13105 when Pragma_Ada_12
13106 | Pragma_Ada_2012
13108 declare
13109 E_Id : Node_Id;
13111 begin
13112 GNAT_Pragma;
13114 if Arg_Count = 1 then
13115 Check_Arg_Is_Local_Name (Arg1);
13116 E_Id := Get_Pragma_Arg (Arg1);
13118 if Etype (E_Id) = Any_Type then
13119 return;
13120 end if;
13122 Set_Is_Ada_2012_Only (Entity (E_Id));
13123 Record_Rep_Item (Entity (E_Id), N);
13125 else
13126 Check_Arg_Count (0);
13128 -- For Ada_2012 we unconditionally enforce the documented
13129 -- configuration pragma placement, since we do not want to
13130 -- tolerate mixed modes in a unit involving Ada 2012. That
13131 -- would cause real difficulties for those cases where there
13132 -- are incompatibilities between Ada 95 and Ada 2012. We could
13133 -- allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
13135 Check_Valid_Configuration_Pragma;
13137 -- Now set appropriate Ada mode
13139 Ada_Version := Ada_2012;
13140 Ada_Version_Explicit := Ada_2012;
13141 Ada_Version_Pragma := N;
13142 end if;
13143 end;
13145 --------------
13146 -- Ada_2022 --
13147 --------------
13149 -- pragma Ada_2022;
13150 -- pragma Ada_2022 (LOCAL_NAME):
13152 -- Note: this pragma also has some specific processing in Par.Prag
13153 -- because we want to set the Ada 2022 version mode during parsing.
13155 -- The one argument form is used for managing the transition from Ada
13156 -- 2012 to Ada 2022 in the run-time library. If an entity is marked
13157 -- as Ada_2022 only, then referencing the entity in any pre-Ada_2022
13158 -- mode will generate a warning;for calls to Ada_2022 only primitives
13159 -- that require overriding an error will be reported. In addition, in
13160 -- any pre-Ada_2022 mode, a preference rule is established which does
13161 -- not choose such an entity unless it is unambiguously specified.
13162 -- This avoids extra subprograms marked this way from generating
13163 -- ambiguities in otherwise legal pre-Ada 2022 programs. The one
13164 -- argument form is intended for exclusive use in the GNAT run-time
13165 -- library.
13167 when Pragma_Ada_2022 =>
13168 declare
13169 E_Id : Node_Id;
13171 begin
13172 GNAT_Pragma;
13174 if Arg_Count = 1 then
13175 Check_Arg_Is_Local_Name (Arg1);
13176 E_Id := Get_Pragma_Arg (Arg1);
13178 if Etype (E_Id) = Any_Type then
13179 return;
13180 end if;
13182 Set_Is_Ada_2022_Only (Entity (E_Id));
13183 Record_Rep_Item (Entity (E_Id), N);
13185 else
13186 Check_Arg_Count (0);
13188 -- For Ada_2022 we unconditionally enforce the documented
13189 -- configuration pragma placement, since we do not want to
13190 -- tolerate mixed modes in a unit involving Ada 2022. That
13191 -- would cause real difficulties for those cases where there
13192 -- are incompatibilities between Ada 2012 and Ada 2022. We
13193 -- could allow mixing of Ada 2012 and Ada 2022 but it's not
13194 -- worth it.
13196 Check_Valid_Configuration_Pragma;
13198 -- Now set appropriate Ada mode
13200 Ada_Version := Ada_2022;
13201 Ada_Version_Explicit := Ada_2022;
13202 Ada_Version_Pragma := N;
13203 end if;
13204 end;
13206 -------------------------------------
13207 -- Aggregate_Individually_Assign --
13208 -------------------------------------
13210 -- pragma Aggregate_Individually_Assign;
13212 when Pragma_Aggregate_Individually_Assign =>
13213 GNAT_Pragma;
13214 Check_Arg_Count (0);
13215 Check_Valid_Configuration_Pragma;
13216 Aggregate_Individually_Assign := True;
13218 ----------------------
13219 -- All_Calls_Remote --
13220 ----------------------
13222 -- pragma All_Calls_Remote [(library_package_NAME)];
13224 when Pragma_All_Calls_Remote => All_Calls_Remote : declare
13225 Lib_Entity : Entity_Id;
13227 begin
13228 Check_Ada_83_Warning;
13229 Check_Valid_Library_Unit_Pragma;
13231 -- If N was rewritten as a null statement there is nothing more
13232 -- to do.
13234 if Nkind (N) = N_Null_Statement then
13235 return;
13236 end if;
13238 Lib_Entity := Find_Lib_Unit_Name;
13240 -- A pragma that applies to a Ghost entity becomes Ghost for the
13241 -- purposes of legality checks and removal of ignored Ghost code.
13243 Mark_Ghost_Pragma (N, Lib_Entity);
13245 -- This pragma should only apply to a RCI unit (RM E.2.3(23))
13247 if Present (Lib_Entity) and then not Debug_Flag_U then
13248 if not Is_Remote_Call_Interface (Lib_Entity) then
13249 Error_Pragma ("pragma% only apply to rci unit");
13251 -- Set flag for entity of the library unit
13253 else
13254 Set_Has_All_Calls_Remote (Lib_Entity);
13255 end if;
13256 end if;
13257 end All_Calls_Remote;
13259 ---------------------------
13260 -- Allow_Integer_Address --
13261 ---------------------------
13263 -- pragma Allow_Integer_Address;
13265 when Pragma_Allow_Integer_Address =>
13266 GNAT_Pragma;
13267 Check_Valid_Configuration_Pragma;
13268 Check_Arg_Count (0);
13270 -- If Address is a private type, then set the flag to allow
13271 -- integer address values. If Address is not private, then this
13272 -- pragma has no purpose, so it is simply ignored. Not clear if
13273 -- there are any such targets now.
13275 if Opt.Address_Is_Private then
13276 Opt.Allow_Integer_Address := True;
13277 end if;
13279 -----------------------
13280 -- Always_Terminates --
13281 -----------------------
13283 -- pragma Always_Terminates [ (boolean_EXPRESSION) ];
13285 -- Characteristics:
13287 -- * Analysis - The annotation undergoes initial checks to verify
13288 -- the legal placement and context. Secondary checks preanalyze the
13289 -- expressions in:
13291 -- Analyze_Always_Terminates_Cases_In_Decl_Part
13293 -- * Expansion - The annotation is expanded during the expansion of
13294 -- the related subprogram [body] contract as performed in:
13296 -- Expand_Subprogram_Contract
13298 -- * Template - The annotation utilizes the generic template of the
13299 -- related subprogram [body] when it is:
13301 -- aspect on subprogram declaration
13302 -- aspect on stand-alone subprogram body
13303 -- pragma on stand-alone subprogram body
13305 -- The annotation must prepare its own template when it is:
13307 -- pragma on subprogram declaration
13309 -- * Globals - Capture of global references must occur after full
13310 -- analysis.
13312 -- * Instance - The annotation is instantiated automatically when
13313 -- the related generic subprogram [body] is instantiated except for
13314 -- the "pragma on subprogram declaration" case. In that scenario
13315 -- the annotation must instantiate itself.
13317 when Pragma_Always_Terminates => Always_Terminates : declare
13318 Spec_Id : Entity_Id;
13319 Subp_Decl : Node_Id;
13320 Subp_Spec : Node_Id;
13322 begin
13323 GNAT_Pragma;
13324 Check_No_Identifiers;
13325 Check_At_Most_N_Arguments (1);
13327 -- Ensure the proper placement of the pragma. Always_Terminates
13328 -- must be associated with a subprogram declaration or a body that
13329 -- acts as a spec.
13331 Subp_Decl :=
13332 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
13334 -- Generic subprogram and package declaration
13336 if Nkind (Subp_Decl) in N_Generic_Declaration then
13337 null;
13339 -- Package declaration
13341 elsif Nkind (Subp_Decl) = N_Package_Declaration then
13342 null;
13344 -- Body acts as spec
13346 elsif Nkind (Subp_Decl) = N_Subprogram_Body
13347 and then No (Corresponding_Spec (Subp_Decl))
13348 then
13349 null;
13351 -- Body stub acts as spec
13353 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
13354 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
13355 then
13356 null;
13358 -- Subprogram
13360 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
13361 Subp_Spec := Specification (Subp_Decl);
13363 -- Pragma Always_Terminates is forbidden on null procedures,
13364 -- as this may lead to potential ambiguities in behavior
13365 -- when interface null procedures are involved. Also, it
13366 -- just wouldn't make sense, because null procedures always
13367 -- terminate anyway.
13369 if Nkind (Subp_Spec) = N_Procedure_Specification
13370 and then Null_Present (Subp_Spec)
13371 then
13372 Error_Msg_N (Fix_Error
13373 ("pragma % cannot apply to null procedure"), N);
13374 return;
13375 end if;
13377 -- Entry
13379 elsif Nkind (Subp_Decl) = N_Entry_Declaration then
13380 null;
13382 else
13383 Pragma_Misplaced;
13384 end if;
13386 Spec_Id := Unique_Defining_Entity (Subp_Decl);
13388 -- In order to call Is_Function_With_Side_Effects, analyze pragma
13389 -- Side_Effects if present.
13391 Analyze_If_Present (Pragma_Side_Effects);
13393 -- Pragma Always_Terminates is not allowed on functions without
13394 -- side effects.
13396 if Ekind (Spec_Id) in E_Function | E_Generic_Function
13397 and then not Is_Function_With_Side_Effects (Spec_Id)
13398 then
13399 Error_Msg_Code := GEC_Always_Terminates_On_Function;
13401 if Ekind (Spec_Id) = E_Function then
13402 Error_Msg_N (Fix_Error
13403 ("pragma % cannot apply to function '[[]']"), N);
13404 return;
13406 elsif Ekind (Spec_Id) = E_Generic_Function then
13407 Error_Msg_N (Fix_Error
13408 ("pragma % cannot apply to generic function '[[]']"), N);
13409 return;
13410 end if;
13411 end if;
13413 -- Pragma Always_Terminates applied to packages doesn't allow any
13414 -- expression.
13416 if Is_Package_Or_Generic_Package (Spec_Id)
13417 and then Arg_Count /= 0
13418 then
13419 Error_Msg_N (Fix_Error
13420 ("pragma % applied to package cannot have arguments"), N);
13421 return;
13422 end if;
13424 -- A pragma that applies to a Ghost entity becomes Ghost for the
13425 -- purposes of legality checks and removal of ignored Ghost code.
13427 Mark_Ghost_Pragma (N, Spec_Id);
13429 -- Chain the pragma on the contract for further processing by
13430 -- Analyze_Always_Terminates_In_Decl_Part.
13432 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
13434 -- Fully analyze the pragma when it appears inside a subprogram
13435 -- body because it cannot benefit from forward references.
13437 if Nkind (Subp_Decl) in N_Subprogram_Body
13438 | N_Subprogram_Body_Stub
13439 then
13440 -- The legality checks of pragma Always_Terminates are affected
13441 -- by the SPARK mode in effect and the volatility of the
13442 -- context. Analyze all pragmas in a specific order.
13444 Analyze_If_Present (Pragma_SPARK_Mode);
13445 Analyze_If_Present (Pragma_Volatile_Function);
13446 Analyze_Always_Terminates_In_Decl_Part (N);
13447 end if;
13448 end Always_Terminates;
13450 --------------
13451 -- Annotate --
13452 --------------
13454 -- pragma Annotate
13455 -- (IDENTIFIER [, IDENTIFIER {, ARG}] [,Entity => local_NAME]);
13456 -- ARG ::= NAME | EXPRESSION
13458 -- The first two arguments are by convention intended to refer to an
13459 -- external tool and a tool-specific function. These arguments are
13460 -- not analyzed.
13462 when Pragma_Annotate | Pragma_GNAT_Annotate => Annotate : declare
13463 Arg : Node_Id;
13464 Expr : Node_Id;
13465 Nam_Arg : Node_Id;
13467 --------------------------
13468 -- Inferred_String_Type --
13469 --------------------------
13471 function Preferred_String_Type (Expr : Node_Id) return Entity_Id;
13472 -- Infer the type to use for a string literal or a concatentation
13473 -- of operands whose types can be inferred. For such expressions,
13474 -- returns the "narrowest" of the three predefined string types
13475 -- that can represent the characters occurring in the expression.
13476 -- For other expressions, returns Empty.
13478 function Preferred_String_Type (Expr : Node_Id) return Entity_Id is
13479 begin
13480 case Nkind (Expr) is
13481 when N_String_Literal =>
13482 if Has_Wide_Wide_Character (Expr) then
13483 return Standard_Wide_Wide_String;
13484 elsif Has_Wide_Character (Expr) then
13485 return Standard_Wide_String;
13486 else
13487 return Standard_String;
13488 end if;
13490 when N_Op_Concat =>
13491 declare
13492 L_Type : constant Entity_Id :=
13493 Preferred_String_Type (Left_Opnd (Expr));
13494 R_Type : constant Entity_Id :=
13495 Preferred_String_Type (Right_Opnd (Expr));
13497 Type_Table : constant array (1 .. 4) of Entity_Id :=
13498 (Empty,
13499 Standard_Wide_Wide_String,
13500 Standard_Wide_String,
13501 Standard_String);
13502 begin
13503 for Idx in Type_Table'Range loop
13504 if L_Type = Type_Table (Idx) or
13505 R_Type = Type_Table (Idx)
13506 then
13507 return Type_Table (Idx);
13508 end if;
13509 end loop;
13510 raise Program_Error;
13511 end;
13513 when others =>
13514 return Empty;
13515 end case;
13516 end Preferred_String_Type;
13517 begin
13518 GNAT_Pragma;
13519 Check_At_Least_N_Arguments (1);
13521 Nam_Arg := Last (Pragma_Argument_Associations (N));
13523 -- Determine whether the last argument is "Entity => local_NAME"
13524 -- and if it is, perform the required semantic checks. Remove the
13525 -- argument from further processing.
13527 if Nkind (Nam_Arg) = N_Pragma_Argument_Association
13528 and then Chars (Nam_Arg) = Name_Entity
13529 then
13530 Check_Arg_Is_Local_Name (Nam_Arg);
13531 Arg_Count := Arg_Count - 1;
13533 -- A pragma that applies to a Ghost entity becomes Ghost for
13534 -- the purposes of legality checks and removal of ignored Ghost
13535 -- code.
13537 if Is_Entity_Name (Get_Pragma_Arg (Nam_Arg))
13538 and then Present (Entity (Get_Pragma_Arg (Nam_Arg)))
13539 then
13540 Mark_Ghost_Pragma (N, Entity (Get_Pragma_Arg (Nam_Arg)));
13541 end if;
13542 end if;
13544 -- Continue the processing with last argument removed for now
13546 Check_Arg_Is_Identifier (Arg1);
13547 Check_No_Identifiers;
13548 Store_Note (N);
13550 -- The second parameter is optional, it is never analyzed
13552 if No (Arg2) then
13553 null;
13555 -- Otherwise there is a second parameter
13557 else
13558 -- The second parameter must be an identifier
13560 Check_Arg_Is_Identifier (Arg2);
13562 -- Process the remaining parameters (if any)
13564 Arg := Next (Arg2);
13565 while Present (Arg) loop
13566 Expr := Get_Pragma_Arg (Arg);
13567 Analyze (Expr);
13569 if Is_Entity_Name (Expr) then
13570 null;
13572 -- For string literals and concatenations of string literals
13573 -- we assume Standard_String as the type, unless the string
13574 -- contains wide or wide_wide characters.
13576 elsif Present (Preferred_String_Type (Expr)) then
13577 Resolve (Expr, Preferred_String_Type (Expr));
13579 elsif Is_Overloaded (Expr) then
13580 Error_Pragma_Arg ("ambiguous argument for pragma%", Expr);
13582 else
13583 Resolve (Expr);
13584 end if;
13586 Next (Arg);
13587 end loop;
13588 end if;
13589 end Annotate;
13591 -------------------------------------------------
13592 -- Assert/Assert_And_Cut/Assume/Loop_Invariant --
13593 -------------------------------------------------
13595 -- pragma Assert
13596 -- ( [Check => ] Boolean_EXPRESSION
13597 -- [, [Message =>] Static_String_EXPRESSION]);
13599 -- pragma Assert_And_Cut
13600 -- ( [Check => ] Boolean_EXPRESSION
13601 -- [, [Message =>] Static_String_EXPRESSION]);
13603 -- pragma Assume
13604 -- ( [Check => ] Boolean_EXPRESSION
13605 -- [, [Message =>] Static_String_EXPRESSION]);
13607 -- pragma Loop_Invariant
13608 -- ( [Check => ] Boolean_EXPRESSION
13609 -- [, [Message =>] Static_String_EXPRESSION]);
13611 when Pragma_Assert
13612 | Pragma_Assert_And_Cut
13613 | Pragma_Assume
13614 | Pragma_Loop_Invariant
13616 Assert : declare
13617 function Contains_Loop_Entry (Expr : Node_Id) return Boolean;
13618 -- Determine whether expression Expr contains a Loop_Entry
13619 -- attribute reference.
13621 -------------------------
13622 -- Contains_Loop_Entry --
13623 -------------------------
13625 function Contains_Loop_Entry (Expr : Node_Id) return Boolean is
13626 Has_Loop_Entry : Boolean := False;
13628 function Process (N : Node_Id) return Traverse_Result;
13629 -- Process function for traversal to look for Loop_Entry
13631 -------------
13632 -- Process --
13633 -------------
13635 function Process (N : Node_Id) return Traverse_Result is
13636 begin
13637 if Nkind (N) = N_Attribute_Reference
13638 and then Attribute_Name (N) = Name_Loop_Entry
13639 then
13640 Has_Loop_Entry := True;
13641 return Abandon;
13642 else
13643 return OK;
13644 end if;
13645 end Process;
13647 procedure Traverse is new Traverse_Proc (Process);
13649 -- Start of processing for Contains_Loop_Entry
13651 begin
13652 Traverse (Expr);
13653 return Has_Loop_Entry;
13654 end Contains_Loop_Entry;
13656 -- Local variables
13658 Expr : Node_Id;
13659 New_Args : List_Id;
13661 -- Start of processing for Assert
13663 begin
13664 -- Assert is an Ada 2005 RM-defined pragma
13666 if Prag_Id = Pragma_Assert then
13667 Ada_2005_Pragma;
13669 -- The remaining ones are GNAT pragmas
13671 else
13672 GNAT_Pragma;
13673 end if;
13675 Check_At_Least_N_Arguments (1);
13676 Check_At_Most_N_Arguments (2);
13677 Check_Arg_Order ((Name_Check, Name_Message));
13678 Check_Optional_Identifier (Arg1, Name_Check);
13679 Expr := Get_Pragma_Arg (Arg1);
13681 -- Special processing for Loop_Invariant, Loop_Variant or for
13682 -- other cases where a Loop_Entry attribute is present. If the
13683 -- assertion pragma contains attribute Loop_Entry, ensure that
13684 -- the related pragma is within a loop.
13686 if Prag_Id = Pragma_Loop_Invariant
13687 or else Prag_Id = Pragma_Loop_Variant
13688 or else Contains_Loop_Entry (Expr)
13689 then
13690 Check_Loop_Pragma_Placement;
13692 -- Perform preanalysis to deal with embedded Loop_Entry
13693 -- attributes.
13695 Preanalyze_Assert_Expression (Expr, Any_Boolean);
13696 end if;
13698 -- Implement Assert[_And_Cut]/Assume/Loop_Invariant by generating
13699 -- a corresponding Check pragma:
13701 -- pragma Check (name, condition [, msg]);
13703 -- Where name is the identifier matching the pragma name. So
13704 -- rewrite pragma in this manner, transfer the message argument
13705 -- if present, and analyze the result
13707 -- Note: When dealing with a semantically analyzed tree, the
13708 -- information that a Check node N corresponds to a source Assert,
13709 -- Assume, or Assert_And_Cut pragma can be retrieved from the
13710 -- pragma kind of Original_Node(N).
13712 New_Args := New_List (
13713 Make_Pragma_Argument_Association (Loc,
13714 Expression => Make_Identifier (Loc, Pname)),
13715 Make_Pragma_Argument_Association (Sloc (Expr),
13716 Expression => Expr));
13718 if Arg_Count > 1 then
13719 Check_Optional_Identifier (Arg2, Name_Message);
13721 -- Provide semantic annotations for optional argument, for
13722 -- ASIS use, before rewriting.
13723 -- Is this still needed???
13725 Preanalyze_And_Resolve (Expression (Arg2), Standard_String);
13726 Append_To (New_Args, New_Copy_Tree (Arg2));
13727 end if;
13729 -- Rewrite as Check pragma
13731 Rewrite (N,
13732 Make_Pragma (Loc,
13733 Chars => Name_Check,
13734 Pragma_Argument_Associations => New_Args));
13736 Analyze (N);
13737 end Assert;
13739 ----------------------
13740 -- Assertion_Policy --
13741 ----------------------
13743 -- pragma Assertion_Policy (POLICY_IDENTIFIER);
13745 -- The following form is Ada 2012 only, but we allow it in all modes
13747 -- Pragma Assertion_Policy (
13748 -- ASSERTION_KIND => POLICY_IDENTIFIER
13749 -- {, ASSERTION_KIND => POLICY_IDENTIFIER});
13751 -- ASSERTION_KIND ::= RM_ASSERTION_KIND | ID_ASSERTION_KIND
13753 -- RM_ASSERTION_KIND ::= Assert |
13754 -- Static_Predicate |
13755 -- Dynamic_Predicate |
13756 -- Pre |
13757 -- Pre'Class |
13758 -- Post |
13759 -- Post'Class |
13760 -- Type_Invariant |
13761 -- Type_Invariant'Class |
13762 -- Default_Initial_Condition
13764 -- ID_ASSERTION_KIND ::= Assert_And_Cut |
13765 -- Assume |
13766 -- Contract_Cases |
13767 -- Debug |
13768 -- Ghost |
13769 -- Initial_Condition |
13770 -- Loop_Invariant |
13771 -- Loop_Variant |
13772 -- Postcondition |
13773 -- Precondition |
13774 -- Predicate |
13775 -- Refined_Post |
13776 -- Statement_Assertions |
13777 -- Subprogram_Variant
13779 -- Note: The RM_ASSERTION_KIND list is language-defined, and the
13780 -- ID_ASSERTION_KIND list contains implementation-defined additions
13781 -- recognized by GNAT. The effect is to control the behavior of
13782 -- identically named aspects and pragmas, depending on the specified
13783 -- policy identifier:
13785 -- POLICY_IDENTIFIER ::= Check | Disable | Ignore | Suppressible
13787 -- Note: Check and Ignore are language-defined. Disable is a GNAT
13788 -- implementation-defined addition that results in totally ignoring
13789 -- the corresponding assertion. If Disable is specified, then the
13790 -- argument of the assertion is not even analyzed. This is useful
13791 -- when the aspect/pragma argument references entities in a with'ed
13792 -- package that is replaced by a dummy package in the final build.
13794 -- Note: the attribute forms Pre'Class, Post'Class, Invariant'Class,
13795 -- and Type_Invariant'Class were recognized by the parser and
13796 -- transformed into references to the special internal identifiers
13797 -- _Pre, _Post, _Invariant, and _Type_Invariant, so no special
13798 -- processing is required here.
13800 when Pragma_Assertion_Policy => Assertion_Policy : declare
13801 procedure Resolve_Suppressible (Policy : Node_Id);
13802 -- Converts the assertion policy 'Suppressible' to either Check or
13803 -- Ignore based on whether checks are suppressed via -gnatp.
13805 --------------------------
13806 -- Resolve_Suppressible --
13807 --------------------------
13809 procedure Resolve_Suppressible (Policy : Node_Id) is
13810 Arg : constant Node_Id := Get_Pragma_Arg (Policy);
13811 Nam : Name_Id;
13813 begin
13814 -- Transform policy argument Suppressible into either Ignore or
13815 -- Check depending on whether checks are enabled or suppressed.
13817 if Chars (Arg) = Name_Suppressible then
13818 if Suppress_Checks then
13819 Nam := Name_Ignore;
13820 else
13821 Nam := Name_Check;
13822 end if;
13824 Rewrite (Arg, Make_Identifier (Sloc (Arg), Nam));
13825 end if;
13826 end Resolve_Suppressible;
13828 -- Local variables
13830 Arg : Node_Id;
13831 Kind : Name_Id;
13832 LocP : Source_Ptr;
13833 Policy : Node_Id;
13835 begin
13836 Ada_2005_Pragma;
13838 -- This can always appear as a configuration pragma
13840 if Is_Configuration_Pragma then
13841 null;
13843 -- It can also appear in a declarative part or package spec in Ada
13844 -- 2012 mode. We allow this in other modes, but in that case we
13845 -- consider that we have an Ada 2012 pragma on our hands.
13847 else
13848 Check_Is_In_Decl_Part_Or_Package_Spec;
13849 Ada_2012_Pragma;
13850 end if;
13852 -- One argument case with no identifier (first form above)
13854 if Arg_Count = 1
13855 and then (Nkind (Arg1) /= N_Pragma_Argument_Association
13856 or else Chars (Arg1) = No_Name)
13857 then
13858 Check_Arg_Is_One_Of (Arg1,
13859 Name_Check, Name_Disable, Name_Ignore, Name_Suppressible);
13861 Resolve_Suppressible (Arg1);
13863 -- Treat one argument Assertion_Policy as equivalent to:
13865 -- pragma Check_Policy (Assertion, policy)
13867 -- So rewrite pragma in that manner and link on to the chain
13868 -- of Check_Policy pragmas, marking the pragma as analyzed.
13870 Policy := Get_Pragma_Arg (Arg1);
13872 Rewrite (N,
13873 Make_Pragma (Loc,
13874 Chars => Name_Check_Policy,
13875 Pragma_Argument_Associations => New_List (
13876 Make_Pragma_Argument_Association (Loc,
13877 Expression => Make_Identifier (Loc, Name_Assertion)),
13879 Make_Pragma_Argument_Association (Loc,
13880 Expression =>
13881 Make_Identifier (Sloc (Policy), Chars (Policy))))));
13882 Analyze (N);
13884 -- Here if we have two or more arguments
13886 else
13887 Check_At_Least_N_Arguments (1);
13888 Ada_2012_Pragma;
13890 -- Loop through arguments
13892 Arg := Arg1;
13893 while Present (Arg) loop
13894 LocP := Sloc (Arg);
13896 -- Kind must be specified
13898 if Nkind (Arg) /= N_Pragma_Argument_Association
13899 or else Chars (Arg) = No_Name
13900 then
13901 Error_Pragma_Arg
13902 ("missing assertion kind for pragma%", Arg);
13903 end if;
13905 -- Check Kind and Policy have allowed forms
13907 Kind := Chars (Arg);
13908 Policy := Get_Pragma_Arg (Arg);
13910 if not Is_Valid_Assertion_Kind (Kind) then
13911 Error_Pragma_Arg
13912 ("invalid assertion kind for pragma%", Arg);
13913 end if;
13915 Check_Arg_Is_One_Of (Arg,
13916 Name_Check, Name_Disable, Name_Ignore, Name_Suppressible);
13918 Resolve_Suppressible (Arg);
13920 if Kind = Name_Ghost then
13922 -- The Ghost policy must be either Check or Ignore
13923 -- (SPARK RM 6.9(6)).
13925 if Chars (Policy) not in Name_Check | Name_Ignore then
13926 Error_Pragma_Arg
13927 ("argument of pragma % Ghost must be Check or "
13928 & "Ignore", Policy);
13929 end if;
13931 -- Pragma Assertion_Policy specifying a Ghost policy
13932 -- cannot occur within a Ghost subprogram or package
13933 -- (SPARK RM 6.9(16)).
13935 if Ghost_Mode > None then
13936 Error_Pragma
13937 ("pragma % cannot appear within ghost subprogram or "
13938 & "package");
13939 end if;
13940 end if;
13942 -- Rewrite the Assertion_Policy pragma as a series of
13943 -- Check_Policy pragmas of the form:
13945 -- Check_Policy (Kind, Policy);
13947 -- Note: the insertion of the pragmas cannot be done with
13948 -- Insert_Action because in the configuration case, there
13949 -- are no scopes on the scope stack and the mechanism will
13950 -- fail.
13952 Insert_Before_And_Analyze (N,
13953 Make_Pragma (LocP,
13954 Chars => Name_Check_Policy,
13955 Pragma_Argument_Associations => New_List (
13956 Make_Pragma_Argument_Association (LocP,
13957 Expression => Make_Identifier (LocP, Kind)),
13958 Make_Pragma_Argument_Association (LocP,
13959 Expression => Policy))));
13961 Arg := Next (Arg);
13962 end loop;
13964 -- Rewrite the Assertion_Policy pragma as null since we have
13965 -- now inserted all the equivalent Check pragmas.
13967 Rewrite (N, Make_Null_Statement (Loc));
13968 Analyze (N);
13969 end if;
13970 end Assertion_Policy;
13972 ------------------------------
13973 -- Assume_No_Invalid_Values --
13974 ------------------------------
13976 -- pragma Assume_No_Invalid_Values (On | Off);
13978 when Pragma_Assume_No_Invalid_Values =>
13979 GNAT_Pragma;
13980 Check_Valid_Configuration_Pragma;
13981 Check_Arg_Count (1);
13982 Check_No_Identifiers;
13983 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
13985 if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
13986 Assume_No_Invalid_Values := True;
13987 else
13988 Assume_No_Invalid_Values := False;
13989 end if;
13991 --------------------------
13992 -- Attribute_Definition --
13993 --------------------------
13995 -- pragma Attribute_Definition
13996 -- ([Attribute =>] ATTRIBUTE_DESIGNATOR,
13997 -- [Entity =>] LOCAL_NAME,
13998 -- [Expression =>] EXPRESSION | NAME);
14000 when Pragma_Attribute_Definition => Attribute_Definition : declare
14001 Attribute_Designator : constant Node_Id := Get_Pragma_Arg (Arg1);
14002 Aname : Name_Id;
14004 begin
14005 GNAT_Pragma;
14006 Check_Arg_Count (3);
14007 Check_Optional_Identifier (Arg1, "attribute");
14008 Check_Optional_Identifier (Arg2, "entity");
14009 Check_Optional_Identifier (Arg3, "expression");
14011 if Nkind (Attribute_Designator) /= N_Identifier then
14012 Error_Msg_N ("attribute name expected", Attribute_Designator);
14013 return;
14014 end if;
14016 Check_Arg_Is_Local_Name (Arg2);
14018 -- If the attribute is not recognized, then issue a warning (not
14019 -- an error), and ignore the pragma.
14021 Aname := Chars (Attribute_Designator);
14023 if not Is_Attribute_Name (Aname) then
14024 Bad_Attribute (Attribute_Designator, Aname, Warn => True);
14025 return;
14026 end if;
14028 -- Otherwise, rewrite the pragma as an attribute definition clause
14030 Rewrite (N,
14031 Make_Attribute_Definition_Clause (Loc,
14032 Name => Get_Pragma_Arg (Arg2),
14033 Chars => Aname,
14034 Expression => Get_Pragma_Arg (Arg3)));
14035 Analyze (N);
14036 end Attribute_Definition;
14038 ------------------------------------------------------------------
14039 -- Async_Readers/Async_Writers/Effective_Reads/Effective_Writes --
14040 -- No_Caching --
14041 ------------------------------------------------------------------
14043 -- pragma Async_Readers [ (static_boolean_EXPRESSION) ];
14044 -- pragma Async_Writers [ (static_boolean_EXPRESSION) ];
14045 -- pragma Effective_Reads [ (static_boolean_EXPRESSION) ];
14046 -- pragma Effective_Writes [ (static_boolean_EXPRESSION) ];
14047 -- pragma No_Caching [ (static_boolean_EXPRESSION) ];
14049 when Pragma_Async_Readers
14050 | Pragma_Async_Writers
14051 | Pragma_Effective_Reads
14052 | Pragma_Effective_Writes
14053 | Pragma_No_Caching
14055 Async_Effective : declare
14056 Obj_Or_Type_Decl : Node_Id;
14057 Obj_Or_Type_Id : Entity_Id;
14058 begin
14059 GNAT_Pragma;
14060 Check_No_Identifiers;
14061 Check_At_Most_N_Arguments (1);
14063 Obj_Or_Type_Decl := Find_Related_Context (N, Do_Checks => True);
14065 -- Pragma must apply to a object declaration or to a type
14066 -- declaration. Original_Node is necessary to account for
14067 -- untagged derived types that are rewritten as subtypes of
14068 -- their respective root types.
14070 if Nkind (Obj_Or_Type_Decl) /= N_Object_Declaration
14071 and then Nkind (Original_Node (Obj_Or_Type_Decl)) not in
14072 N_Full_Type_Declaration |
14073 N_Private_Type_Declaration |
14074 N_Formal_Type_Declaration |
14075 N_Task_Type_Declaration |
14076 N_Protected_Type_Declaration
14077 then
14078 Pragma_Misplaced;
14079 end if;
14081 Obj_Or_Type_Id := Defining_Entity (Obj_Or_Type_Decl);
14083 -- Perform minimal verification to ensure that the argument is at
14084 -- least an object or a type. Subsequent finer grained checks will
14085 -- be done at the end of the declarative region that contains the
14086 -- pragma.
14088 if Ekind (Obj_Or_Type_Id) in E_Constant | E_Variable
14089 or else Is_Type (Obj_Or_Type_Id)
14090 then
14092 -- In the case of a type, pragma is a type-related
14093 -- representation item and so requires checks common to
14094 -- all type-related representation items.
14096 if Is_Type (Obj_Or_Type_Id)
14097 and then Rep_Item_Too_Late (Obj_Or_Type_Id, N)
14098 then
14099 return;
14100 end if;
14102 -- A pragma that applies to a Ghost entity becomes Ghost for
14103 -- the purposes of legality checks and removal of ignored Ghost
14104 -- code.
14106 Mark_Ghost_Pragma (N, Obj_Or_Type_Id);
14108 -- Chain the pragma on the contract for further processing by
14109 -- Analyze_External_Property_In_Decl_Part.
14111 Add_Contract_Item (N, Obj_Or_Type_Id);
14113 -- Analyze the Boolean expression (if any)
14115 if Present (Arg1) then
14116 Check_Static_Boolean_Expression (Get_Pragma_Arg (Arg1));
14117 end if;
14119 -- Otherwise the external property applies to a constant
14121 else
14122 Error_Pragma
14123 ("pragma % must apply to a volatile type or object");
14124 end if;
14125 end Async_Effective;
14127 ------------------
14128 -- Asynchronous --
14129 ------------------
14131 -- pragma Asynchronous (LOCAL_NAME);
14133 when Pragma_Asynchronous => Asynchronous : declare
14134 C_Ent : Entity_Id;
14135 Decl : Node_Id;
14136 Formal : Entity_Id;
14137 L : List_Id;
14138 Nm : Entity_Id;
14139 S : Node_Id;
14141 procedure Process_Async_Pragma;
14142 -- Common processing for procedure and access-to-procedure case
14144 --------------------------
14145 -- Process_Async_Pragma --
14146 --------------------------
14148 procedure Process_Async_Pragma is
14149 begin
14150 if No (L) then
14151 Set_Is_Asynchronous (Nm);
14152 return;
14153 end if;
14155 -- The formals should be of mode IN (RM E.4.1(6))
14157 S := First (L);
14158 while Present (S) loop
14159 Formal := Defining_Identifier (S);
14161 if Nkind (Formal) = N_Defining_Identifier
14162 and then Ekind (Formal) /= E_In_Parameter
14163 then
14164 Error_Pragma_Arg
14165 ("pragma% procedure can only have IN parameter",
14166 Arg1);
14167 end if;
14169 Next (S);
14170 end loop;
14172 Set_Is_Asynchronous (Nm);
14173 end Process_Async_Pragma;
14175 -- Start of processing for pragma Asynchronous
14177 begin
14178 Check_Ada_83_Warning;
14179 Check_No_Identifiers;
14180 Check_Arg_Count (1);
14181 Check_Arg_Is_Local_Name (Arg1);
14183 if Debug_Flag_U then
14184 return;
14185 end if;
14187 C_Ent := Cunit_Entity (Current_Sem_Unit);
14188 Analyze (Get_Pragma_Arg (Arg1));
14189 Nm := Entity (Get_Pragma_Arg (Arg1));
14191 -- A pragma that applies to a Ghost entity becomes Ghost for the
14192 -- purposes of legality checks and removal of ignored Ghost code.
14194 Mark_Ghost_Pragma (N, Nm);
14196 if not Is_Remote_Call_Interface (C_Ent)
14197 and then not Is_Remote_Types (C_Ent)
14198 then
14199 -- This pragma should only appear in an RCI or Remote Types
14200 -- unit (RM E.4.1(4)).
14202 Error_Pragma
14203 ("pragma% not in Remote_Call_Interface or Remote_Types unit");
14204 end if;
14206 if Ekind (Nm) = E_Procedure
14207 and then Nkind (Parent (Nm)) = N_Procedure_Specification
14208 then
14209 if not Is_Remote_Call_Interface (Nm) then
14210 Error_Pragma_Arg
14211 ("pragma% cannot be applied on non-remote procedure",
14212 Arg1);
14213 end if;
14215 L := Parameter_Specifications (Parent (Nm));
14216 Process_Async_Pragma;
14217 return;
14219 elsif Ekind (Nm) = E_Function then
14220 Error_Pragma_Arg
14221 ("pragma% cannot be applied to function", Arg1);
14223 elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
14224 if Is_Record_Type (Nm) then
14226 -- A record type that is the Equivalent_Type for a remote
14227 -- access-to-subprogram type.
14229 Decl := Declaration_Node (Corresponding_Remote_Type (Nm));
14231 else
14232 -- A non-expanded RAS type (distribution is not enabled)
14234 Decl := Declaration_Node (Nm);
14235 end if;
14237 if Nkind (Decl) = N_Full_Type_Declaration
14238 and then Nkind (Type_Definition (Decl)) =
14239 N_Access_Procedure_Definition
14240 then
14241 L := Parameter_Specifications (Type_Definition (Decl));
14242 Process_Async_Pragma;
14244 if Is_Asynchronous (Nm)
14245 and then Expander_Active
14246 and then Get_PCS_Name /= Name_No_DSA
14247 then
14248 RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
14249 end if;
14251 else
14252 Error_Pragma_Arg
14253 ("pragma% cannot reference access-to-function type",
14254 Arg1);
14255 end if;
14257 -- Only other possibility is access-to-class-wide type
14259 elsif Is_Access_Type (Nm)
14260 and then Is_Class_Wide_Type (Designated_Type (Nm))
14261 then
14262 Check_First_Subtype (Arg1);
14263 Set_Is_Asynchronous (Nm);
14264 if Expander_Active then
14265 RACW_Type_Is_Asynchronous (Nm);
14266 end if;
14268 else
14269 Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
14270 end if;
14271 end Asynchronous;
14273 ------------
14274 -- Atomic --
14275 ------------
14277 -- pragma Atomic (LOCAL_NAME);
14279 when Pragma_Atomic =>
14280 Process_Atomic_Independent_Shared_Volatile;
14282 -----------------------
14283 -- Atomic_Components --
14284 -----------------------
14286 -- pragma Atomic_Components (array_LOCAL_NAME);
14288 -- This processing is shared by Volatile_Components
14290 when Pragma_Atomic_Components
14291 | Pragma_Volatile_Components
14293 Atomic_Components : declare
14294 D : Node_Id;
14295 E : Entity_Id;
14296 E_Id : Node_Id;
14298 begin
14299 Check_Ada_83_Warning;
14300 Check_No_Identifiers;
14301 Check_Arg_Count (1);
14302 Check_Arg_Is_Local_Name (Arg1);
14303 E_Id := Get_Pragma_Arg (Arg1);
14305 if Etype (E_Id) = Any_Type then
14306 return;
14307 end if;
14309 E := Entity (E_Id);
14311 -- A pragma that applies to a Ghost entity becomes Ghost for the
14312 -- purposes of legality checks and removal of ignored Ghost code.
14314 Mark_Ghost_Pragma (N, E);
14315 Check_Duplicate_Pragma (E);
14317 if Rep_Item_Too_Early (E, N)
14318 or else
14319 Rep_Item_Too_Late (E, N)
14320 then
14321 return;
14322 end if;
14324 D := Declaration_Node (E);
14326 if (Nkind (D) = N_Full_Type_Declaration and then Is_Array_Type (E))
14327 or else
14328 (Nkind (D) = N_Object_Declaration
14329 and then Ekind (E) in E_Constant | E_Variable
14330 and then Nkind (Object_Definition (D)) =
14331 N_Constrained_Array_Definition)
14332 or else
14333 (Ada_Version >= Ada_2022
14334 and then Nkind (D) = N_Formal_Type_Declaration)
14335 then
14336 -- The flag is set on the base type, or on the object
14338 if Nkind (D) = N_Full_Type_Declaration then
14339 E := Base_Type (E);
14340 end if;
14342 -- Atomic implies both Independent and Volatile
14344 if Prag_Id = Pragma_Atomic_Components then
14345 Set_Has_Atomic_Components (E);
14346 Set_Has_Independent_Components (E);
14347 end if;
14349 Set_Has_Volatile_Components (E);
14351 else
14352 Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
14353 end if;
14354 end Atomic_Components;
14356 --------------------
14357 -- Attach_Handler --
14358 --------------------
14360 -- pragma Attach_Handler (handler_NAME, EXPRESSION);
14362 when Pragma_Attach_Handler =>
14363 Check_Ada_83_Warning;
14364 Check_No_Identifiers;
14365 Check_Arg_Count (2);
14367 if No_Run_Time_Mode then
14368 Error_Msg_CRT ("Attach_Handler pragma", N);
14369 else
14370 Check_Interrupt_Or_Attach_Handler;
14372 -- The expression that designates the attribute may depend on a
14373 -- discriminant, and is therefore a per-object expression, to
14374 -- be expanded in the init proc. If expansion is enabled, then
14375 -- perform semantic checks on a copy only.
14377 declare
14378 Temp : Node_Id;
14379 Typ : Node_Id;
14380 Parg2 : constant Node_Id := Get_Pragma_Arg (Arg2);
14382 begin
14383 -- In Relaxed_RM_Semantics mode, we allow any static
14384 -- integer value, for compatibility with other compilers.
14386 if Relaxed_RM_Semantics
14387 and then Nkind (Parg2) = N_Integer_Literal
14388 then
14389 Typ := Standard_Integer;
14390 else
14391 Typ := RTE (RE_Interrupt_ID);
14392 end if;
14394 if Expander_Active then
14395 Temp := New_Copy_Tree (Parg2);
14396 Set_Parent (Temp, N);
14397 Preanalyze_And_Resolve (Temp, Typ);
14398 else
14399 Analyze (Parg2);
14400 Resolve (Parg2, Typ);
14401 end if;
14402 end;
14404 Process_Interrupt_Or_Attach_Handler;
14405 end if;
14407 --------------------
14408 -- C_Pass_By_Copy --
14409 --------------------
14411 -- pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
14413 when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
14414 Arg : Node_Id;
14415 Val : Uint;
14417 begin
14418 GNAT_Pragma;
14419 Check_Valid_Configuration_Pragma;
14420 Check_Arg_Count (1);
14421 Check_Optional_Identifier (Arg1, "max_size");
14423 Arg := Get_Pragma_Arg (Arg1);
14424 Check_Arg_Is_OK_Static_Expression (Arg, Any_Integer);
14426 Val := Expr_Value (Arg);
14428 if Val <= 0 then
14429 Error_Pragma_Arg
14430 ("maximum size for pragma% must be positive", Arg1);
14432 elsif UI_Is_In_Int_Range (Val) then
14433 Default_C_Record_Mechanism := UI_To_Int (Val);
14435 -- If a giant value is given, Int'Last will do well enough.
14436 -- If sometime someone complains that a record larger than
14437 -- two gigabytes is not copied, we will worry about it then.
14439 else
14440 Default_C_Record_Mechanism := Mechanism_Type'Last;
14441 end if;
14442 end C_Pass_By_Copy;
14444 -----------
14445 -- Check --
14446 -----------
14448 -- pragma Check ([Name =>] CHECK_KIND,
14449 -- [Check =>] Boolean_EXPRESSION
14450 -- [,[Message =>] String_EXPRESSION]);
14452 -- CHECK_KIND ::= IDENTIFIER |
14453 -- Pre'Class |
14454 -- Post'Class |
14455 -- Invariant'Class |
14456 -- Type_Invariant'Class
14458 -- The identifiers Assertions and Statement_Assertions are not
14459 -- allowed, since they have special meaning for Check_Policy.
14461 -- WARNING: The code below manages Ghost regions. Return statements
14462 -- must be replaced by gotos which jump to the end of the code and
14463 -- restore the Ghost mode.
14465 when Pragma_Check => Check : declare
14467 procedure Handle_Dynamic_Predicate_Check;
14468 -- Enable or ignore the pragma depending on whether dynamic
14469 -- checks are enabled in the context where the associated
14470 -- type declaration is defined.
14472 ------------------------------------
14473 -- Handle_Dynamic_Predicate_Check --
14474 ------------------------------------
14476 procedure Handle_Dynamic_Predicate_Check is
14477 Func_Call : constant Node_Id := Expression (Arg2);
14478 Func_Id : constant Entity_Id := Entity (Name (Func_Call));
14479 Typ : Entity_Id;
14481 begin
14482 -- Locate the type declaration associated with this runtime
14483 -- check. The 2nd parameter of this pragma is a call to an
14484 -- internally built function that has a single parameter;
14485 -- the type of that formal parameter is the type we are
14486 -- searching for.
14488 pragma Assert (Is_Predicate_Function (Func_Id));
14489 Typ := Etype (First_Entity (Func_Id));
14491 if not Has_Dynamic_Predicate_Aspect (Typ)
14492 and then Is_Private_Type (Typ)
14493 and then Present (Full_View (Typ))
14494 then
14495 Typ := Full_View (Typ);
14496 end if;
14498 pragma Assert (Has_Dynamic_Predicate_Aspect (Typ));
14500 if not Predicates_Ignored (Typ) then
14501 Set_Is_Checked (N, True);
14502 Set_Is_Ignored (N, False);
14504 else
14505 -- In CodePeer mode and GNATprove mode, we need to
14506 -- consider all assertions, unless they are disabled,
14507 -- because transformations of the AST may depend on
14508 -- assertions being checked.
14510 if CodePeer_Mode or GNATprove_Mode then
14511 Set_Is_Checked (N, True);
14512 Set_Is_Ignored (N, False);
14513 else
14514 Set_Is_Checked (N, False);
14515 Set_Is_Ignored (N, True);
14516 end if;
14517 end if;
14518 end Handle_Dynamic_Predicate_Check;
14520 -- Local variables
14522 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
14523 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
14524 -- Save the Ghost-related attributes to restore on exit
14526 Cname : Name_Id;
14527 Eloc : Source_Ptr;
14528 Expr : Node_Id;
14529 Str : Node_Id;
14530 pragma Warnings (Off, Str);
14532 -- Start of processing for Pragma_Check
14534 begin
14535 -- Pragma Check is Ghost when it applies to a Ghost entity. Set
14536 -- the mode now to ensure that any nodes generated during analysis
14537 -- and expansion are marked as Ghost.
14539 Set_Ghost_Mode (N);
14541 GNAT_Pragma;
14542 Check_At_Least_N_Arguments (2);
14543 Check_At_Most_N_Arguments (3);
14544 Check_Optional_Identifier (Arg1, Name_Name);
14545 Check_Optional_Identifier (Arg2, Name_Check);
14547 if Arg_Count = 3 then
14548 Check_Optional_Identifier (Arg3, Name_Message);
14549 Str := Get_Pragma_Arg (Arg3);
14550 end if;
14552 Rewrite_Assertion_Kind (Get_Pragma_Arg (Arg1));
14553 Check_Arg_Is_Identifier (Arg1);
14554 Cname := Chars (Get_Pragma_Arg (Arg1));
14556 -- Check forbidden name Assertions or Statement_Assertions
14558 case Cname is
14559 when Name_Assertions =>
14560 Error_Pragma_Arg
14561 ("""Assertions"" is not allowed as a check kind for "
14562 & "pragma%", Arg1);
14564 when Name_Statement_Assertions =>
14565 Error_Pragma_Arg
14566 ("""Statement_Assertions"" is not allowed as a check kind "
14567 & "for pragma%", Arg1);
14569 when others =>
14570 null;
14571 end case;
14573 -- Check applicable policy. We skip this if Checked/Ignored status
14574 -- is already set (e.g. in the case of a pragma from an aspect).
14576 if Is_Checked (N) or else Is_Ignored (N) then
14577 null;
14579 -- For a non-source pragma that is a rewriting of another pragma,
14580 -- copy the Is_Checked/Ignored status from the rewritten pragma.
14582 elsif Is_Rewrite_Substitution (N)
14583 and then Nkind (Original_Node (N)) = N_Pragma
14584 then
14585 Set_Is_Ignored (N, Is_Ignored (Original_Node (N)));
14586 Set_Is_Checked (N, Is_Checked (Original_Node (N)));
14588 -- Internally added dynamic predicate checks require checking the
14589 -- applicable policy at the point of the type declaration of their
14590 -- corresponding entity.
14592 elsif not Comes_From_Source (N)
14593 and then Chars (Pragma_Identifier (N)) = Name_Check
14594 and then Pname = Name_Dynamic_Predicate
14595 then
14596 Handle_Dynamic_Predicate_Check;
14598 -- Otherwise query the applicable policy at this point
14600 else
14601 case Check_Kind (Cname) is
14602 when Name_Ignore =>
14603 Set_Is_Ignored (N, True);
14604 Set_Is_Checked (N, False);
14606 when Name_Check =>
14607 Set_Is_Ignored (N, False);
14608 Set_Is_Checked (N, True);
14610 -- For disable, rewrite pragma as null statement and skip
14611 -- rest of the analysis of the pragma.
14613 when Name_Disable =>
14614 Rewrite (N, Make_Null_Statement (Loc));
14615 Analyze (N);
14616 raise Pragma_Exit;
14618 -- No other possibilities
14620 when others =>
14621 raise Program_Error;
14622 end case;
14623 end if;
14625 -- If check kind was not Disable, then continue pragma analysis
14627 Expr := Get_Pragma_Arg (Arg2);
14629 -- Mark the pragma (or, if rewritten from an aspect, the original
14630 -- aspect) as enabled. Nothing to do for an internally generated
14631 -- check for a dynamic predicate.
14633 if Is_Checked (N)
14634 and then Cname /= Name_Dynamic_Predicate
14635 then
14636 Set_SCO_Pragma_Enabled (Loc);
14637 end if;
14639 -- Deal with analyzing the string argument. If checks are not
14640 -- on we don't want any expansion (since such expansion would
14641 -- not get properly deleted) but we do want to analyze (to get
14642 -- proper references). The Preanalyze_And_Resolve routine does
14643 -- just what we want. Ditto if pragma is active, because it will
14644 -- be rewritten as an if-statement whose analysis will complete
14645 -- analysis and expansion of the string message. This makes a
14646 -- difference in the unusual case where the expression for the
14647 -- string may have a side effect, such as raising an exception.
14648 -- This is mandated by RM 11.4.2, which specifies that the string
14649 -- expression is only evaluated if the check fails and
14650 -- Assertion_Error is to be raised.
14652 if Arg_Count = 3 then
14653 Preanalyze_And_Resolve (Str, Standard_String);
14654 end if;
14656 -- Now you might think we could just do the same with the Boolean
14657 -- expression if checks are off (and expansion is on) and then
14658 -- rewrite the check as a null statement. This would work but we
14659 -- would lose the useful warnings about an assertion being bound
14660 -- to fail even if assertions are turned off.
14662 -- So instead we wrap the boolean expression in an if statement
14663 -- that looks like:
14665 -- if False and then condition then
14666 -- null;
14667 -- end if;
14669 -- The reason we do this rewriting during semantic analysis rather
14670 -- than as part of normal expansion is that we cannot analyze and
14671 -- expand the code for the boolean expression directly, or it may
14672 -- cause insertion of actions that would escape the attempt to
14673 -- suppress the check code.
14675 -- Note that the Sloc for the if statement corresponds to the
14676 -- argument condition, not the pragma itself. The reason for
14677 -- this is that we may generate a warning if the condition is
14678 -- False at compile time, and we do not want to delete this
14679 -- warning when we delete the if statement.
14681 if Expander_Active and Is_Ignored (N) then
14682 Eloc := Sloc (Expr);
14684 Rewrite (N,
14685 Make_If_Statement (Eloc,
14686 Condition =>
14687 Make_And_Then (Eloc,
14688 Left_Opnd => Make_Identifier (Eloc, Name_False),
14689 Right_Opnd => Expr),
14690 Then_Statements => New_List (
14691 Make_Null_Statement (Eloc))));
14693 -- Now go ahead and analyze the if statement
14695 In_Assertion_Expr := In_Assertion_Expr + 1;
14697 -- One rather special treatment. If we are now in Eliminated
14698 -- overflow mode, then suppress overflow checking since we do
14699 -- not want to drag in the bignum stuff if we are in Ignore
14700 -- mode anyway. This is particularly important if we are using
14701 -- a configurable run time that does not support bignum ops.
14703 if Scope_Suppress.Overflow_Mode_Assertions = Eliminated then
14704 declare
14705 Svo : constant Boolean :=
14706 Scope_Suppress.Suppress (Overflow_Check);
14707 begin
14708 Scope_Suppress.Overflow_Mode_Assertions := Strict;
14709 Scope_Suppress.Suppress (Overflow_Check) := True;
14710 Analyze (N);
14711 Scope_Suppress.Suppress (Overflow_Check) := Svo;
14712 Scope_Suppress.Overflow_Mode_Assertions := Eliminated;
14713 end;
14715 -- Not that special case
14717 else
14718 Analyze (N);
14719 end if;
14721 -- All done with this check
14723 In_Assertion_Expr := In_Assertion_Expr - 1;
14725 -- Check is active or expansion not active. In these cases we can
14726 -- just go ahead and analyze the boolean with no worries.
14728 else
14729 In_Assertion_Expr := In_Assertion_Expr + 1;
14730 Analyze_And_Resolve (Expr, Any_Boolean);
14731 In_Assertion_Expr := In_Assertion_Expr - 1;
14732 end if;
14734 Restore_Ghost_Region (Saved_GM, Saved_IGR);
14735 end Check;
14737 --------------------------
14738 -- Check_Float_Overflow --
14739 --------------------------
14741 -- pragma Check_Float_Overflow;
14743 when Pragma_Check_Float_Overflow =>
14744 GNAT_Pragma;
14745 Check_Valid_Configuration_Pragma;
14746 Check_Arg_Count (0);
14747 Check_Float_Overflow := not Machine_Overflows_On_Target;
14749 ----------------
14750 -- Check_Name --
14751 ----------------
14753 -- pragma Check_Name (check_IDENTIFIER);
14755 when Pragma_Check_Name =>
14756 GNAT_Pragma;
14757 Check_No_Identifiers;
14758 Check_Valid_Configuration_Pragma;
14759 Check_Arg_Count (1);
14760 Check_Arg_Is_Identifier (Arg1);
14762 declare
14763 Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
14765 begin
14766 for J in Check_Names.First .. Check_Names.Last loop
14767 if Check_Names.Table (J) = Nam then
14768 return;
14769 end if;
14770 end loop;
14772 Check_Names.Append (Nam);
14773 end;
14775 ------------------
14776 -- Check_Policy --
14777 ------------------
14779 -- This is the old style syntax, which is still allowed in all modes:
14781 -- pragma Check_Policy ([Name =>] CHECK_KIND
14782 -- [Policy =>] POLICY_IDENTIFIER);
14784 -- POLICY_IDENTIFIER ::= On | Off | Check | Disable | Ignore
14786 -- CHECK_KIND ::= IDENTIFIER |
14787 -- Pre'Class |
14788 -- Post'Class |
14789 -- Type_Invariant'Class |
14790 -- Invariant'Class
14792 -- This is the new style syntax, compatible with Assertion_Policy
14793 -- and also allowed in all modes.
14795 -- Pragma Check_Policy (
14796 -- CHECK_KIND => POLICY_IDENTIFIER
14797 -- {, CHECK_KIND => POLICY_IDENTIFIER});
14799 -- Note: the identifiers Name and Policy are not allowed as
14800 -- Check_Kind values. This avoids ambiguities between the old and
14801 -- new form syntax.
14803 when Pragma_Check_Policy => Check_Policy : declare
14804 Kind : Node_Id;
14806 begin
14807 GNAT_Pragma;
14808 Check_At_Least_N_Arguments (1);
14810 -- A Check_Policy pragma can appear either as a configuration
14811 -- pragma, or in a declarative part or a package spec (see RM
14812 -- 11.5(5) for rules for Suppress/Unsuppress which are also
14813 -- followed for Check_Policy).
14815 if not Is_Configuration_Pragma then
14816 Check_Is_In_Decl_Part_Or_Package_Spec;
14817 end if;
14819 -- Figure out if we have the old or new syntax. We have the
14820 -- old syntax if the first argument has no identifier, or the
14821 -- identifier is Name.
14823 if Nkind (Arg1) /= N_Pragma_Argument_Association
14824 or else Chars (Arg1) in No_Name | Name_Name
14825 then
14826 -- Old syntax
14828 Check_Arg_Count (2);
14829 Check_Optional_Identifier (Arg1, Name_Name);
14830 Kind := Get_Pragma_Arg (Arg1);
14831 Rewrite_Assertion_Kind (Kind,
14832 From_Policy => Comes_From_Source (N));
14833 Check_Arg_Is_Identifier (Arg1);
14835 -- Check forbidden check kind
14837 if Chars (Kind) in Name_Name | Name_Policy then
14838 Error_Msg_Name_2 := Chars (Kind);
14839 Error_Pragma_Arg
14840 ("pragma% does not allow% as check name", Arg1);
14841 end if;
14843 -- Check policy
14845 Check_Optional_Identifier (Arg2, Name_Policy);
14846 Check_Arg_Is_One_Of
14847 (Arg2,
14848 Name_On, Name_Off, Name_Check, Name_Disable, Name_Ignore);
14850 -- And chain pragma on the Check_Policy_List for search
14852 Set_Next_Pragma (N, Opt.Check_Policy_List);
14853 Opt.Check_Policy_List := N;
14855 -- For the new syntax, what we do is to convert each argument to
14856 -- an old syntax equivalent. We do that because we want to chain
14857 -- old style Check_Policy pragmas for the search (we don't want
14858 -- to have to deal with multiple arguments in the search).
14860 else
14861 declare
14862 Arg : Node_Id;
14863 Argx : Node_Id;
14864 LocP : Source_Ptr;
14865 New_P : Node_Id;
14867 begin
14868 Arg := Arg1;
14869 while Present (Arg) loop
14870 LocP := Sloc (Arg);
14871 Argx := Get_Pragma_Arg (Arg);
14873 -- Kind must be specified
14875 if Nkind (Arg) /= N_Pragma_Argument_Association
14876 or else Chars (Arg) = No_Name
14877 then
14878 Error_Pragma_Arg
14879 ("missing assertion kind for pragma%", Arg);
14880 end if;
14882 -- Construct equivalent old form syntax Check_Policy
14883 -- pragma and insert it to get remaining checks.
14885 New_P :=
14886 Make_Pragma (LocP,
14887 Chars => Name_Check_Policy,
14888 Pragma_Argument_Associations => New_List (
14889 Make_Pragma_Argument_Association (LocP,
14890 Expression =>
14891 Make_Identifier (LocP, Chars (Arg))),
14892 Make_Pragma_Argument_Association (Sloc (Argx),
14893 Expression => Argx)));
14895 Arg := Next (Arg);
14897 -- For a configuration pragma, insert old form in
14898 -- the corresponding file.
14900 if Is_Configuration_Pragma then
14901 Insert_After (N, New_P);
14902 Analyze (New_P);
14904 else
14905 Insert_Action (N, New_P);
14906 end if;
14907 end loop;
14909 -- Rewrite original Check_Policy pragma to null, since we
14910 -- have converted it into a series of old syntax pragmas.
14912 Rewrite (N, Make_Null_Statement (Loc));
14913 Analyze (N);
14914 end;
14915 end if;
14916 end Check_Policy;
14918 -------------
14919 -- Comment --
14920 -------------
14922 -- pragma Comment (static_string_EXPRESSION)
14924 -- Processing for pragma Comment shares the circuitry for pragma
14925 -- Ident. The only differences are that Ident enforces a limit of 31
14926 -- characters on its argument, and also enforces limitations on
14927 -- placement for DEC compatibility. Pragma Comment shares neither of
14928 -- these restrictions.
14930 -------------------
14931 -- Common_Object --
14932 -------------------
14934 -- pragma Common_Object (
14935 -- [Internal =>] LOCAL_NAME
14936 -- [, [External =>] EXTERNAL_SYMBOL]
14937 -- [, [Size =>] EXTERNAL_SYMBOL]);
14939 -- Processing for this pragma is shared with Psect_Object
14941 ----------------------------------------------
14942 -- Compile_Time_Error, Compile_Time_Warning --
14943 ----------------------------------------------
14945 -- pragma Compile_Time_Error
14946 -- (boolean_EXPRESSION, static_string_EXPRESSION);
14948 -- pragma Compile_Time_Warning
14949 -- (boolean_EXPRESSION, static_string_EXPRESSION);
14951 when Pragma_Compile_Time_Error | Pragma_Compile_Time_Warning =>
14952 GNAT_Pragma;
14954 Process_Compile_Time_Warning_Or_Error;
14956 -----------------------------
14957 -- Complete_Representation --
14958 -----------------------------
14960 -- pragma Complete_Representation;
14962 when Pragma_Complete_Representation =>
14963 GNAT_Pragma;
14964 Check_Arg_Count (0);
14966 if Nkind (Parent (N)) /= N_Record_Representation_Clause then
14967 Error_Pragma
14968 ("pragma & must appear within record representation clause");
14969 end if;
14971 ----------------------------
14972 -- Complex_Representation --
14973 ----------------------------
14975 -- pragma Complex_Representation ([Entity =>] LOCAL_NAME);
14977 when Pragma_Complex_Representation => Complex_Representation : declare
14978 E_Id : Node_Id;
14979 E : Entity_Id;
14980 Ent : Entity_Id;
14982 begin
14983 GNAT_Pragma;
14984 Check_Arg_Count (1);
14985 Check_Optional_Identifier (Arg1, Name_Entity);
14986 Check_Arg_Is_Local_Name (Arg1);
14987 E_Id := Get_Pragma_Arg (Arg1);
14989 if Etype (E_Id) = Any_Type then
14990 return;
14991 end if;
14993 E := Entity (E_Id);
14995 if not Is_Record_Type (E) then
14996 Error_Pragma_Arg
14997 ("argument for pragma% must be record type", Arg1);
14998 end if;
15000 Ent := First_Entity (E);
15002 if No (Ent)
15003 or else No (Next_Entity (Ent))
15004 or else Present (Next_Entity (Next_Entity (Ent)))
15005 or else not Is_Floating_Point_Type (Etype (Ent))
15006 or else Etype (Ent) /= Etype (Next_Entity (Ent))
15007 then
15008 Error_Pragma_Arg
15009 ("record for pragma% must have two fields of the same "
15010 & "floating-point type", Arg1);
15012 else
15013 Set_Has_Complex_Representation (Base_Type (E));
15015 -- We need to treat the type has having a non-standard
15016 -- representation, for back-end purposes, even though in
15017 -- general a complex will have the default representation
15018 -- of a record with two real components.
15020 Set_Has_Non_Standard_Rep (Base_Type (E));
15021 end if;
15022 end Complex_Representation;
15024 -------------------------
15025 -- Component_Alignment --
15026 -------------------------
15028 -- pragma Component_Alignment (
15029 -- [Form =>] ALIGNMENT_CHOICE
15030 -- [, [Name =>] type_LOCAL_NAME]);
15032 -- ALIGNMENT_CHOICE ::=
15033 -- Component_Size
15034 -- | Component_Size_4
15035 -- | Storage_Unit
15036 -- | Default
15038 when Pragma_Component_Alignment => Component_AlignmentP : declare
15039 Args : Args_List (1 .. 2);
15040 Names : constant Name_List (1 .. 2) := (
15041 Name_Form,
15042 Name_Name);
15044 Form : Node_Id renames Args (1);
15045 Name : Node_Id renames Args (2);
15047 Atype : Component_Alignment_Kind;
15048 Typ : Entity_Id;
15050 begin
15051 GNAT_Pragma;
15052 Gather_Associations (Names, Args);
15054 if No (Form) then
15055 Error_Pragma ("missing Form argument for pragma%");
15056 end if;
15058 Check_Arg_Is_Identifier (Form);
15060 -- Get proper alignment, note that Default = Component_Size on all
15061 -- machines we have so far, and we want to set this value rather
15062 -- than the default value to indicate that it has been explicitly
15063 -- set (and thus will not get overridden by the default component
15064 -- alignment for the current scope)
15066 if Chars (Form) = Name_Component_Size then
15067 Atype := Calign_Component_Size;
15069 elsif Chars (Form) = Name_Component_Size_4 then
15070 Atype := Calign_Component_Size_4;
15072 elsif Chars (Form) = Name_Default then
15073 Atype := Calign_Component_Size;
15075 elsif Chars (Form) = Name_Storage_Unit then
15076 Atype := Calign_Storage_Unit;
15078 else
15079 Error_Pragma_Arg
15080 ("invalid Form parameter for pragma%", Form);
15081 end if;
15083 -- The pragma appears in a configuration file
15085 if No (Parent (N)) then
15086 Check_Valid_Configuration_Pragma;
15088 -- Capture the component alignment in a global variable when
15089 -- the pragma appears in a configuration file. Note that the
15090 -- scope stack is empty at this point and cannot be used to
15091 -- store the alignment value.
15093 Configuration_Component_Alignment := Atype;
15095 -- Case with no name, supplied, affects scope table entry
15097 elsif No (Name) then
15098 Scope_Stack.Table
15099 (Scope_Stack.Last).Component_Alignment_Default := Atype;
15101 -- Case of name supplied
15103 else
15104 Check_Arg_Is_Local_Name (Name);
15105 Find_Type (Name);
15106 Typ := Entity (Name);
15108 if Typ = Any_Type
15109 or else Rep_Item_Too_Early (Typ, N)
15110 then
15111 return;
15112 else
15113 Typ := Underlying_Type (Typ);
15114 end if;
15116 if not Is_Record_Type (Typ)
15117 and then not Is_Array_Type (Typ)
15118 then
15119 Error_Pragma_Arg
15120 ("Name parameter of pragma% must identify record or "
15121 & "array type", Name);
15122 end if;
15124 -- An explicit Component_Alignment pragma overrides an
15125 -- implicit pragma Pack, but not an explicit one.
15127 if not Has_Pragma_Pack (Base_Type (Typ)) then
15128 Set_Is_Packed (Base_Type (Typ), False);
15129 Set_Component_Alignment (Base_Type (Typ), Atype);
15130 end if;
15131 end if;
15132 end Component_AlignmentP;
15134 --------------------------------
15135 -- Constant_After_Elaboration --
15136 --------------------------------
15138 -- pragma Constant_After_Elaboration [ (boolean_EXPRESSION) ];
15140 when Pragma_Constant_After_Elaboration => Constant_After_Elaboration :
15141 declare
15142 Obj_Decl : Node_Id;
15143 Obj_Id : Entity_Id;
15145 begin
15146 GNAT_Pragma;
15147 Check_No_Identifiers;
15148 Check_At_Most_N_Arguments (1);
15150 Obj_Decl := Find_Related_Context (N, Do_Checks => True);
15152 if Nkind (Obj_Decl) /= N_Object_Declaration then
15153 Pragma_Misplaced;
15154 end if;
15156 Obj_Id := Defining_Entity (Obj_Decl);
15158 -- The object declaration must be a library-level variable which
15159 -- is either explicitly initialized or obtains a value during the
15160 -- elaboration of a package body (SPARK RM 3.3.1).
15162 if Ekind (Obj_Id) = E_Variable then
15163 if not Is_Library_Level_Entity (Obj_Id) then
15164 Error_Pragma
15165 ("pragma % must apply to a library level variable");
15166 end if;
15168 -- Otherwise the pragma applies to a constant, which is illegal
15170 else
15171 Error_Pragma ("pragma % must apply to a variable declaration");
15172 end if;
15174 -- A pragma that applies to a Ghost entity becomes Ghost for the
15175 -- purposes of legality checks and removal of ignored Ghost code.
15177 Mark_Ghost_Pragma (N, Obj_Id);
15179 -- Chain the pragma on the contract for completeness
15181 Add_Contract_Item (N, Obj_Id);
15183 -- Analyze the Boolean expression (if any)
15185 if Present (Arg1) then
15186 Check_Static_Boolean_Expression (Get_Pragma_Arg (Arg1));
15187 end if;
15188 end Constant_After_Elaboration;
15190 --------------------
15191 -- Contract_Cases --
15192 --------------------
15194 -- pragma Contract_Cases ((CONTRACT_CASE {, CONTRACT_CASE));
15196 -- CONTRACT_CASE ::= CASE_GUARD => CONSEQUENCE
15198 -- CASE_GUARD ::= boolean_EXPRESSION | others
15200 -- CONSEQUENCE ::= boolean_EXPRESSION
15202 -- Characteristics:
15204 -- * Analysis - The annotation undergoes initial checks to verify
15205 -- the legal placement and context. Secondary checks preanalyze the
15206 -- expressions in:
15208 -- Analyze_Contract_Cases_In_Decl_Part
15210 -- * Expansion - The annotation is expanded during the expansion of
15211 -- the related subprogram [body] contract as performed in:
15213 -- Expand_Subprogram_Contract
15215 -- * Template - The annotation utilizes the generic template of the
15216 -- related subprogram [body] when it is:
15218 -- aspect on subprogram declaration
15219 -- aspect on stand-alone subprogram body
15220 -- pragma on stand-alone subprogram body
15222 -- The annotation must prepare its own template when it is:
15224 -- pragma on subprogram declaration
15226 -- * Globals - Capture of global references must occur after full
15227 -- analysis.
15229 -- * Instance - The annotation is instantiated automatically when
15230 -- the related generic subprogram [body] is instantiated except for
15231 -- the "pragma on subprogram declaration" case. In that scenario
15232 -- the annotation must instantiate itself.
15234 when Pragma_Contract_Cases => Contract_Cases : declare
15235 Spec_Id : Entity_Id;
15236 Subp_Decl : Node_Id;
15237 Subp_Spec : Node_Id;
15239 begin
15240 GNAT_Pragma;
15241 Check_No_Identifiers;
15242 Check_Arg_Count (1);
15244 -- Ensure the proper placement of the pragma. Contract_Cases must
15245 -- be associated with a subprogram declaration or a body that acts
15246 -- as a spec.
15248 Subp_Decl :=
15249 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
15251 -- Entry
15253 if Nkind (Subp_Decl) = N_Entry_Declaration then
15254 null;
15256 -- Generic subprogram
15258 elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
15259 null;
15261 -- Body acts as spec
15263 elsif Nkind (Subp_Decl) = N_Subprogram_Body
15264 and then No (Corresponding_Spec (Subp_Decl))
15265 then
15266 null;
15268 -- Body stub acts as spec
15270 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
15271 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
15272 then
15273 null;
15275 -- Subprogram
15277 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
15278 Subp_Spec := Specification (Subp_Decl);
15280 -- Pragma Contract_Cases is forbidden on null procedures, as
15281 -- this may lead to potential ambiguities in behavior when
15282 -- interface null procedures are involved.
15284 if Nkind (Subp_Spec) = N_Procedure_Specification
15285 and then Null_Present (Subp_Spec)
15286 then
15287 Error_Msg_N (Fix_Error
15288 ("pragma % cannot apply to null procedure"), N);
15289 return;
15290 end if;
15292 else
15293 Pragma_Misplaced;
15294 end if;
15296 Spec_Id := Unique_Defining_Entity (Subp_Decl);
15298 -- A pragma that applies to a Ghost entity becomes Ghost for the
15299 -- purposes of legality checks and removal of ignored Ghost code.
15301 Mark_Ghost_Pragma (N, Spec_Id);
15302 Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
15304 -- Chain the pragma on the contract for further processing by
15305 -- Analyze_Contract_Cases_In_Decl_Part.
15307 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
15309 -- Fully analyze the pragma when it appears inside an entry
15310 -- or subprogram body because it cannot benefit from forward
15311 -- references.
15313 if Nkind (Subp_Decl) in N_Entry_Body
15314 | N_Subprogram_Body
15315 | N_Subprogram_Body_Stub
15316 then
15317 -- The legality checks of pragma Contract_Cases are affected by
15318 -- the SPARK mode in effect and the volatility of the context.
15319 -- Analyze all pragmas in a specific order.
15321 Analyze_If_Present (Pragma_SPARK_Mode);
15322 Analyze_If_Present (Pragma_Volatile_Function);
15323 Analyze_Contract_Cases_In_Decl_Part (N);
15324 end if;
15325 end Contract_Cases;
15327 ----------------
15328 -- Controlled --
15329 ----------------
15331 -- pragma Controlled (first_subtype_LOCAL_NAME);
15333 when Pragma_Controlled => Controlled : declare
15334 Arg : Node_Id;
15336 begin
15337 Check_No_Identifiers;
15338 Check_Arg_Count (1);
15339 Check_Arg_Is_Local_Name (Arg1);
15340 Arg := Get_Pragma_Arg (Arg1);
15342 if not Is_Entity_Name (Arg)
15343 or else not Is_Access_Type (Entity (Arg))
15344 then
15345 Error_Pragma_Arg ("pragma% requires access type", Arg1);
15346 else
15347 Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
15348 end if;
15349 end Controlled;
15351 ----------------
15352 -- Convention --
15353 ----------------
15355 -- pragma Convention ([Convention =>] convention_IDENTIFIER,
15356 -- [Entity =>] LOCAL_NAME);
15358 when Pragma_Convention => Convention : declare
15359 C : Convention_Id;
15360 E : Entity_Id;
15361 pragma Warnings (Off, C);
15362 pragma Warnings (Off, E);
15364 begin
15365 Check_Arg_Order ((Name_Convention, Name_Entity));
15366 Check_Ada_83_Warning;
15367 Check_Arg_Count (2);
15368 Process_Convention (C, E);
15370 -- A pragma that applies to a Ghost entity becomes Ghost for the
15371 -- purposes of legality checks and removal of ignored Ghost code.
15373 Mark_Ghost_Pragma (N, E);
15374 end Convention;
15376 ---------------------------
15377 -- Convention_Identifier --
15378 ---------------------------
15380 -- pragma Convention_Identifier ([Name =>] IDENTIFIER,
15381 -- [Convention =>] convention_IDENTIFIER);
15383 when Pragma_Convention_Identifier => Convention_Identifier : declare
15384 Idnam : Name_Id;
15385 Cname : Name_Id;
15387 begin
15388 GNAT_Pragma;
15389 Check_Arg_Order ((Name_Name, Name_Convention));
15390 Check_Arg_Count (2);
15391 Check_Optional_Identifier (Arg1, Name_Name);
15392 Check_Optional_Identifier (Arg2, Name_Convention);
15393 Check_Arg_Is_Identifier (Arg1);
15394 Check_Arg_Is_Identifier (Arg2);
15395 Idnam := Chars (Get_Pragma_Arg (Arg1));
15396 Cname := Chars (Get_Pragma_Arg (Arg2));
15398 if Is_Convention_Name (Cname) then
15399 Record_Convention_Identifier
15400 (Idnam, Get_Convention_Id (Cname));
15401 else
15402 Error_Pragma_Arg
15403 ("second arg for % pragma must be convention", Arg2);
15404 end if;
15405 end Convention_Identifier;
15407 ---------------
15408 -- CPP_Class --
15409 ---------------
15411 -- pragma CPP_Class ([Entity =>] LOCAL_NAME)
15413 when Pragma_CPP_Class =>
15414 GNAT_Pragma;
15416 if Warn_On_Obsolescent_Feature then
15417 Error_Msg_N
15418 ("'G'N'A'T pragma cpp'_class is now obsolete and has no "
15419 & "effect; replace it by pragma import?j?", N);
15420 end if;
15422 Check_Arg_Count (1);
15424 Rewrite (N,
15425 Make_Pragma (Loc,
15426 Chars => Name_Import,
15427 Pragma_Argument_Associations => New_List (
15428 Make_Pragma_Argument_Association (Loc,
15429 Expression => Make_Identifier (Loc, Name_CPP)),
15430 New_Copy (First (Pragma_Argument_Associations (N))))));
15431 Analyze (N);
15433 ---------------------
15434 -- CPP_Constructor --
15435 ---------------------
15437 -- pragma CPP_Constructor ([Entity =>] LOCAL_NAME
15438 -- [, [External_Name =>] static_string_EXPRESSION ]
15439 -- [, [Link_Name =>] static_string_EXPRESSION ]);
15441 when Pragma_CPP_Constructor => CPP_Constructor : declare
15442 Id : Entity_Id;
15443 Def_Id : Entity_Id;
15444 Tag_Typ : Entity_Id;
15446 begin
15447 GNAT_Pragma;
15448 Check_At_Least_N_Arguments (1);
15449 Check_At_Most_N_Arguments (3);
15450 Check_Optional_Identifier (Arg1, Name_Entity);
15451 Check_Arg_Is_Local_Name (Arg1);
15453 Id := Get_Pragma_Arg (Arg1);
15454 Find_Program_Unit_Name (Id);
15456 -- If we did not find the name, we are done
15458 if Etype (Id) = Any_Type then
15459 return;
15460 end if;
15462 Def_Id := Entity (Id);
15464 -- Check if already defined as constructor
15466 if Is_Constructor (Def_Id) then
15467 Error_Msg_N
15468 ("??duplicate argument for pragma 'C'P'P_Constructor", Arg1);
15469 return;
15470 end if;
15472 if Ekind (Def_Id) = E_Function
15473 and then (Is_CPP_Class (Etype (Def_Id))
15474 or else (Is_Class_Wide_Type (Etype (Def_Id))
15475 and then
15476 Is_CPP_Class (Root_Type (Etype (Def_Id)))))
15477 then
15478 if Scope (Def_Id) /= Scope (Etype (Def_Id)) then
15479 Error_Msg_N
15480 ("'C'P'P constructor must be defined in the scope of "
15481 & "its returned type", Arg1);
15482 end if;
15484 if Arg_Count >= 2 then
15485 Set_Imported (Def_Id);
15486 Set_Is_Public (Def_Id);
15487 Process_Interface_Name (Def_Id, Arg2, Arg3, N);
15488 end if;
15490 Set_Has_Completion (Def_Id);
15491 Set_Is_Constructor (Def_Id);
15492 Set_Convention (Def_Id, Convention_CPP);
15494 -- Imported C++ constructors are not dispatching primitives
15495 -- because in C++ they don't have a dispatch table slot.
15496 -- However, in Ada the constructor has the profile of a
15497 -- function that returns a tagged type and therefore it has
15498 -- been treated as a primitive operation during semantic
15499 -- analysis. We now remove it from the list of primitive
15500 -- operations of the type.
15502 if Is_Tagged_Type (Etype (Def_Id))
15503 and then not Is_Class_Wide_Type (Etype (Def_Id))
15504 and then Is_Dispatching_Operation (Def_Id)
15505 then
15506 Tag_Typ := Etype (Def_Id);
15508 Remove (Primitive_Operations (Tag_Typ), Def_Id);
15509 Set_Is_Dispatching_Operation (Def_Id, False);
15510 end if;
15512 -- For backward compatibility, if the constructor returns a
15513 -- class wide type, and we internally change the return type to
15514 -- the corresponding root type.
15516 if Is_Class_Wide_Type (Etype (Def_Id)) then
15517 Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
15518 end if;
15519 else
15520 Error_Pragma_Arg
15521 ("pragma% requires function returning a 'C'P'P_Class type",
15522 Arg1);
15523 end if;
15524 end CPP_Constructor;
15526 -----------------
15527 -- CPP_Virtual --
15528 -----------------
15530 when Pragma_CPP_Virtual =>
15531 GNAT_Pragma;
15533 if Warn_On_Obsolescent_Feature then
15534 Error_Msg_N
15535 ("'G'N'A'T pragma Cpp'_Virtual is now obsolete and has no "
15536 & "effect?j?", N);
15537 end if;
15539 -----------------
15540 -- CUDA_Device --
15541 -----------------
15543 -- pragma CUDA_Device (LOCAL_NAME);
15545 when Pragma_CUDA_Device => CUDA_Device : declare
15546 Arg_Node : Node_Id;
15547 Device_Entity : Entity_Id;
15548 begin
15549 GNAT_Pragma;
15550 Check_Arg_Count (1);
15551 Check_Arg_Is_Library_Level_Local_Name (Arg1);
15553 Arg_Node := Get_Pragma_Arg (Arg1);
15554 Device_Entity := Entity (Arg_Node);
15556 if Ekind (Device_Entity) in E_Variable
15557 | E_Constant
15558 | E_Procedure
15559 | E_Function
15560 then
15561 Add_CUDA_Device_Entity
15562 (Package_Specification_Of_Scope (Scope (Device_Entity)),
15563 Device_Entity);
15565 else
15566 Error_Msg_NE ("& must be constant, variable or subprogram",
15568 Device_Entity);
15569 end if;
15571 end CUDA_Device;
15573 ------------------
15574 -- CUDA_Execute --
15575 ------------------
15577 -- pragma CUDA_Execute (PROCEDURE_CALL_STATEMENT,
15578 -- EXPRESSION,
15579 -- EXPRESSION,
15580 -- [, EXPRESSION
15581 -- [, EXPRESSION]]);
15583 when Pragma_CUDA_Execute => CUDA_Execute : declare
15585 function Is_Acceptable_Dim3 (N : Node_Id) return Boolean;
15586 -- Returns True if N is an acceptable argument for CUDA_Execute,
15587 -- False otherwise.
15589 ------------------------
15590 -- Is_Acceptable_Dim3 --
15591 ------------------------
15593 function Is_Acceptable_Dim3 (N : Node_Id) return Boolean is
15594 Expr : Node_Id;
15595 begin
15596 if Is_RTE (Etype (N), RE_Dim3)
15597 or else Is_Integer_Type (Etype (N))
15598 then
15599 return True;
15600 end if;
15602 if Nkind (N) = N_Aggregate
15603 and then not Null_Record_Present (N)
15604 and then No (Component_Associations (N))
15605 and then List_Length (Expressions (N)) = 3
15606 then
15607 Expr := First (Expressions (N));
15608 while Present (Expr) loop
15609 Analyze_And_Resolve (Expr, Any_Integer);
15610 Next (Expr);
15611 end loop;
15612 return True;
15613 end if;
15615 return False;
15616 end Is_Acceptable_Dim3;
15618 -- Local variables
15620 Block_Dimensions : constant Node_Id := Get_Pragma_Arg (Arg3);
15621 Grid_Dimensions : constant Node_Id := Get_Pragma_Arg (Arg2);
15622 Kernel_Call : constant Node_Id := Get_Pragma_Arg (Arg1);
15623 Shared_Memory : Node_Id;
15624 Stream : Node_Id;
15626 -- Start of processing for CUDA_Execute
15628 begin
15629 GNAT_Pragma;
15630 Check_At_Least_N_Arguments (3);
15631 Check_At_Most_N_Arguments (5);
15633 Analyze_And_Resolve (Kernel_Call);
15634 if Nkind (Kernel_Call) /= N_Function_Call
15635 or else Etype (Kernel_Call) /= Standard_Void_Type
15636 then
15637 -- In `pragma CUDA_Execute (Kernel_Call (...), ...)`,
15638 -- GNAT sees Kernel_Call as an N_Function_Call since
15639 -- Kernel_Call "looks" like an expression. However, only
15640 -- procedures can be kernels, so to make things easier for the
15641 -- user the error message complains about Kernel_Call not being
15642 -- a procedure call.
15644 Error_Msg_N ("first argument of & must be a procedure call", N);
15645 end if;
15647 Analyze (Grid_Dimensions);
15648 if not Is_Acceptable_Dim3 (Grid_Dimensions) then
15649 Error_Msg_N
15650 ("second argument of & must be an Integer, Dim3 or aggregate "
15651 & "containing 3 Integers", N);
15652 end if;
15654 Analyze (Block_Dimensions);
15655 if not Is_Acceptable_Dim3 (Block_Dimensions) then
15656 Error_Msg_N
15657 ("third argument of & must be an Integer, Dim3 or aggregate "
15658 & "containing 3 Integers", N);
15659 end if;
15661 if Present (Arg4) then
15662 Shared_Memory := Get_Pragma_Arg (Arg4);
15663 Analyze_And_Resolve (Shared_Memory, Any_Integer);
15665 if Present (Arg5) then
15666 Stream := Get_Pragma_Arg (Arg5);
15667 Analyze_And_Resolve (Stream, RTE (RE_Stream_T));
15668 end if;
15669 end if;
15670 end CUDA_Execute;
15672 -----------------
15673 -- CUDA_Global --
15674 -----------------
15676 -- pragma CUDA_Global ([Entity =>] procedure_LOCAL_NAME);
15678 when Pragma_CUDA_Global => CUDA_Global : declare
15679 Arg_Node : Node_Id;
15680 Kernel_Proc : Entity_Id;
15681 Pack_Id : Entity_Id;
15682 begin
15683 GNAT_Pragma;
15684 Check_Arg_Count (1);
15685 Check_Optional_Identifier (Arg1, Name_Entity);
15686 Check_Arg_Is_Local_Name (Arg1);
15688 Arg_Node := Get_Pragma_Arg (Arg1);
15689 Analyze (Arg_Node);
15691 Kernel_Proc := Entity (Arg_Node);
15692 Pack_Id := Scope (Kernel_Proc);
15694 if Ekind (Kernel_Proc) /= E_Procedure then
15695 Error_Msg_NE ("& must be a procedure", N, Kernel_Proc);
15697 elsif Ekind (Pack_Id) /= E_Package
15698 or else not Is_Library_Level_Entity (Pack_Id)
15699 then
15700 Error_Msg_NE
15701 ("& must reside in a library-level package", N, Kernel_Proc);
15703 else
15704 Set_Is_CUDA_Kernel (Kernel_Proc);
15705 Add_CUDA_Kernel (Pack_Id, Kernel_Proc);
15706 end if;
15707 end CUDA_Global;
15709 ----------------
15710 -- CPP_Vtable --
15711 ----------------
15713 when Pragma_CPP_Vtable =>
15714 GNAT_Pragma;
15716 if Warn_On_Obsolescent_Feature then
15717 Error_Msg_N
15718 ("'G'N'A'T pragma Cpp'_Vtable is now obsolete and has no "
15719 & "effect?j?", N);
15720 end if;
15722 ---------
15723 -- CPU --
15724 ---------
15726 -- pragma CPU (EXPRESSION);
15728 when Pragma_CPU => CPU : declare
15729 P : constant Node_Id := Parent (N);
15730 Arg : Node_Id;
15731 Ent : Entity_Id;
15733 begin
15734 Ada_2012_Pragma;
15735 Check_No_Identifiers;
15736 Check_Arg_Count (1);
15737 Arg := Get_Pragma_Arg (Arg1);
15739 -- Subprogram case
15741 if Nkind (P) = N_Subprogram_Body then
15742 Check_In_Main_Program;
15744 Analyze_And_Resolve (Arg, Any_Integer);
15746 Ent := Defining_Unit_Name (Specification (P));
15748 if Nkind (Ent) = N_Defining_Program_Unit_Name then
15749 Ent := Defining_Identifier (Ent);
15750 end if;
15752 -- Must be static
15754 if not Is_OK_Static_Expression (Arg) then
15755 Flag_Non_Static_Expr
15756 ("main subprogram affinity is not static!", Arg);
15757 raise Pragma_Exit;
15759 -- If constraint error, then we already signalled an error
15761 elsif Raises_Constraint_Error (Arg) then
15762 null;
15764 -- Otherwise check in range
15766 else
15767 declare
15768 CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
15769 -- This is the entity System.Multiprocessors.CPU_Range;
15771 Val : constant Uint := Expr_Value (Arg);
15773 begin
15774 if Val < Expr_Value (Type_Low_Bound (CPU_Id))
15775 or else
15776 Val > Expr_Value (Type_High_Bound (CPU_Id))
15777 then
15778 Error_Pragma_Arg
15779 ("main subprogram CPU is out of range", Arg1);
15780 end if;
15781 end;
15782 end if;
15784 Set_Main_CPU
15785 (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
15787 -- Task case
15789 elsif Nkind (P) = N_Task_Definition then
15790 Ent := Defining_Identifier (Parent (P));
15792 -- The expression must be analyzed in the special manner
15793 -- described in "Handling of Default and Per-Object
15794 -- Expressions" in sem.ads.
15796 Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
15798 -- See comment in Sem_Ch13 about the following restrictions
15800 if Is_OK_Static_Expression (Arg) then
15801 if Expr_Value (Arg) = Uint_0 then
15802 Check_Restriction (No_Tasks_Unassigned_To_CPU, N);
15803 end if;
15804 else
15805 Check_Restriction (No_Dynamic_CPU_Assignment, N);
15806 end if;
15808 -- Anything else is incorrect
15810 else
15811 Pragma_Misplaced;
15812 end if;
15814 -- Check duplicate pragma before we chain the pragma in the Rep
15815 -- Item chain of Ent.
15817 Check_Duplicate_Pragma (Ent);
15818 Record_Rep_Item (Ent, N);
15819 end CPU;
15821 --------------------
15822 -- Deadline_Floor --
15823 --------------------
15825 -- pragma Deadline_Floor (time_span_EXPRESSION);
15827 when Pragma_Deadline_Floor => Deadline_Floor : declare
15828 P : constant Node_Id := Parent (N);
15829 Arg : Node_Id;
15830 Ent : Entity_Id;
15832 begin
15833 GNAT_Pragma;
15834 Check_No_Identifiers;
15835 Check_Arg_Count (1);
15837 Arg := Get_Pragma_Arg (Arg1);
15839 -- The expression must be analyzed in the special manner described
15840 -- in "Handling of Default and Per-Object Expressions" in sem.ads.
15842 Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
15844 -- Only protected types allowed
15846 if Nkind (P) /= N_Protected_Definition then
15847 Pragma_Misplaced;
15849 else
15850 Ent := Defining_Identifier (Parent (P));
15852 -- Check duplicate pragma before we chain the pragma in the Rep
15853 -- Item chain of Ent.
15855 Check_Duplicate_Pragma (Ent);
15856 Record_Rep_Item (Ent, N);
15857 end if;
15858 end Deadline_Floor;
15860 -----------
15861 -- Debug --
15862 -----------
15864 -- pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
15866 when Pragma_Debug => Debug : declare
15867 Cond : Node_Id;
15868 Call : Node_Id;
15870 begin
15871 GNAT_Pragma;
15873 -- The condition for executing the call is that the expander
15874 -- is active and that we are not ignoring this debug pragma.
15876 Cond :=
15877 New_Occurrence_Of
15878 (Boolean_Literals
15879 (Expander_Active and then not Is_Ignored (N)),
15880 Loc);
15882 if not Is_Ignored (N) then
15883 Set_SCO_Pragma_Enabled (Loc);
15884 end if;
15886 if Arg_Count = 2 then
15887 Cond :=
15888 Make_And_Then (Loc,
15889 Left_Opnd => Relocate_Node (Cond),
15890 Right_Opnd => Get_Pragma_Arg (Arg1));
15891 Call := Get_Pragma_Arg (Arg2);
15892 else
15893 Call := Get_Pragma_Arg (Arg1);
15894 end if;
15896 if Nkind (Call) in N_Expanded_Name
15897 | N_Function_Call
15898 | N_Identifier
15899 | N_Indexed_Component
15900 | N_Selected_Component
15901 then
15902 -- If this pragma Debug comes from source, its argument was
15903 -- parsed as a name form (which is syntactically identical).
15904 -- In a generic context a parameterless call will be left as
15905 -- an expanded name (if global) or selected_component if local.
15906 -- Change it to a procedure call statement now.
15908 Change_Name_To_Procedure_Call_Statement (Call);
15910 elsif Nkind (Call) = N_Procedure_Call_Statement then
15912 -- Already in the form of a procedure call statement: nothing
15913 -- to do (could happen in case of an internally generated
15914 -- pragma Debug).
15916 null;
15918 else
15919 -- All other cases: diagnose error
15921 Error_Msg_N
15922 ("argument of pragma ""Debug"" is not procedure call", Call);
15923 return;
15924 end if;
15926 -- Rewrite into a conditional with an appropriate condition. We
15927 -- wrap the procedure call in a block so that overhead from e.g.
15928 -- use of the secondary stack does not generate execution overhead
15929 -- for suppressed conditions.
15931 -- Normally the analysis that follows will freeze the subprogram
15932 -- being called. However, if the call is to a null procedure,
15933 -- we want to freeze it before creating the block, because the
15934 -- analysis that follows may be done with expansion disabled, in
15935 -- which case the body will not be generated, leading to spurious
15936 -- errors.
15938 if Nkind (Call) = N_Procedure_Call_Statement
15939 and then Is_Entity_Name (Name (Call))
15940 then
15941 Analyze (Name (Call));
15942 Freeze_Before (N, Entity (Name (Call)));
15943 end if;
15945 Rewrite (N,
15946 Make_Implicit_If_Statement (N,
15947 Condition => Cond,
15948 Then_Statements => New_List (
15949 Make_Block_Statement (Loc,
15950 Handled_Statement_Sequence =>
15951 Make_Handled_Sequence_Of_Statements (Loc,
15952 Statements => New_List (Relocate_Node (Call)))))));
15953 Analyze (N);
15955 -- Ignore pragma Debug in GNATprove mode. Do this rewriting
15956 -- after analysis of the normally rewritten node, to capture all
15957 -- references to entities, which avoids issuing wrong warnings
15958 -- about unused entities.
15960 if GNATprove_Mode then
15961 Rewrite (N, Make_Null_Statement (Loc));
15962 end if;
15963 end Debug;
15965 ------------------
15966 -- Debug_Policy --
15967 ------------------
15969 -- pragma Debug_Policy (On | Off | Check | Disable | Ignore)
15971 when Pragma_Debug_Policy =>
15972 GNAT_Pragma;
15973 Check_Arg_Count (1);
15974 Check_No_Identifiers;
15975 Check_Arg_Is_Identifier (Arg1);
15977 -- Exactly equivalent to pragma Check_Policy (Debug, arg), so
15978 -- rewrite it that way, and let the rest of the checking come
15979 -- from analyzing the rewritten pragma.
15981 Rewrite (N,
15982 Make_Pragma (Loc,
15983 Chars => Name_Check_Policy,
15984 Pragma_Argument_Associations => New_List (
15985 Make_Pragma_Argument_Association (Loc,
15986 Expression => Make_Identifier (Loc, Name_Debug)),
15988 Make_Pragma_Argument_Association (Loc,
15989 Expression => Get_Pragma_Arg (Arg1)))));
15990 Analyze (N);
15992 -------------------------------
15993 -- Default_Initial_Condition --
15994 -------------------------------
15996 -- pragma Default_Initial_Condition [ (null | boolean_EXPRESSION) ];
15998 when Pragma_Default_Initial_Condition => DIC : declare
15999 Discard : Boolean;
16000 Stmt : Node_Id;
16001 Typ : Entity_Id;
16003 begin
16004 GNAT_Pragma;
16005 Check_No_Identifiers;
16006 Check_At_Most_N_Arguments (2); -- Accounts for implicit type arg
16008 Typ := Empty;
16009 Stmt := Prev (N);
16010 while Present (Stmt) loop
16012 -- Skip prior pragmas, but check for duplicates
16014 if Nkind (Stmt) = N_Pragma then
16015 if Pragma_Name (Stmt) = Pname then
16016 Duplication_Error
16017 (Prag => N,
16018 Prev => Stmt);
16019 raise Pragma_Exit;
16020 end if;
16022 -- Skip internally generated code. Note that derived type
16023 -- declarations of untagged types with discriminants are
16024 -- rewritten as private type declarations.
16026 elsif not Comes_From_Source (Stmt)
16027 and then Nkind (Stmt) /= N_Private_Type_Declaration
16028 then
16029 null;
16031 -- The associated private type [extension] has been found, stop
16032 -- the search.
16034 elsif Nkind (Stmt) in N_Private_Extension_Declaration
16035 | N_Private_Type_Declaration
16036 then
16037 Typ := Defining_Entity (Stmt);
16038 exit;
16040 -- The pragma does not apply to a legal construct, issue an
16041 -- error and stop the analysis.
16043 else
16044 Pragma_Misplaced;
16045 end if;
16047 Stmt := Prev (Stmt);
16048 end loop;
16050 -- The pragma does not apply to a legal construct, issue an error
16051 -- and stop the analysis.
16053 if No (Typ) then
16054 Pragma_Misplaced;
16055 end if;
16057 -- A pragma that applies to a Ghost entity becomes Ghost for the
16058 -- purposes of legality checks and removal of ignored Ghost code.
16060 Mark_Ghost_Pragma (N, Typ);
16062 -- The pragma signals that the type defines its own DIC assertion
16063 -- expression.
16065 Set_Has_Own_DIC (Typ);
16067 -- A type entity argument is appended to facilitate inheriting the
16068 -- aspect/pragma from parent types (see Build_DIC_Procedure_Body),
16069 -- though that extra argument isn't documented for the pragma.
16071 if No (Arg2) then
16072 -- When the pragma has no arguments, create an argument with
16073 -- the value Empty, so the type name argument can be appended
16074 -- following it (since it's expected as the second argument).
16076 if No (Arg1) then
16077 Set_Pragma_Argument_Associations (N, New_List (
16078 Make_Pragma_Argument_Association (Sloc (Typ),
16079 Expression => Empty)));
16080 end if;
16082 Append_To
16083 (Pragma_Argument_Associations (N),
16084 Make_Pragma_Argument_Association (Sloc (Typ),
16085 Expression => New_Occurrence_Of (Typ, Sloc (Typ))));
16086 end if;
16088 -- Chain the pragma on the rep item chain for further processing
16090 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
16092 -- Create the declaration of the procedure which verifies the
16093 -- assertion expression of pragma DIC at runtime.
16095 Build_DIC_Procedure_Declaration (Typ);
16096 end DIC;
16098 ----------------------------------
16099 -- Default_Scalar_Storage_Order --
16100 ----------------------------------
16102 -- pragma Default_Scalar_Storage_Order
16103 -- (High_Order_First | Low_Order_First);
16105 when Pragma_Default_Scalar_Storage_Order => DSSO : declare
16106 Default : Character;
16108 begin
16109 GNAT_Pragma;
16110 Check_Arg_Count (1);
16112 -- Default_Scalar_Storage_Order can appear as a configuration
16113 -- pragma, or in a declarative part of a package spec.
16115 if not Is_Configuration_Pragma then
16116 Check_Is_In_Decl_Part_Or_Package_Spec;
16117 end if;
16119 Check_No_Identifiers;
16120 Check_Arg_Is_One_Of
16121 (Arg1, Name_High_Order_First, Name_Low_Order_First);
16122 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
16123 Default := Fold_Upper (Name_Buffer (1));
16125 if not Support_Nondefault_SSO_On_Target
16126 and then Ttypes.Bytes_Big_Endian /= (Default = 'H')
16127 then
16128 if Warn_On_Unrecognized_Pragma then
16129 Error_Msg_N
16130 ("non-default Scalar_Storage_Order not supported "
16131 & "on target?g?", N);
16132 Error_Msg_N
16133 ("\pragma Default_Scalar_Storage_Order ignored?g?", N);
16134 end if;
16136 -- Here set the specified default
16138 else
16139 Opt.Default_SSO := Default;
16140 end if;
16141 end DSSO;
16143 --------------------------
16144 -- Default_Storage_Pool --
16145 --------------------------
16147 -- pragma Default_Storage_Pool (storage_pool_NAME | null | Standard);
16149 when Pragma_Default_Storage_Pool => Default_Storage_Pool : declare
16150 Pool : Node_Id;
16152 begin
16153 Ada_2012_Pragma;
16154 Check_Arg_Count (1);
16156 -- Default_Storage_Pool can appear as a configuration pragma, or
16157 -- in a declarative part of a package spec.
16159 if not Is_Configuration_Pragma then
16160 Check_Is_In_Decl_Part_Or_Package_Spec;
16161 end if;
16163 if From_Aspect_Specification (N) then
16164 declare
16165 E : constant Entity_Id := Entity (Corresponding_Aspect (N));
16166 begin
16167 if not In_Open_Scopes (E) then
16168 Error_Msg_N
16169 ("aspect must apply to package or subprogram", N);
16170 end if;
16171 end;
16172 end if;
16174 if Present (Arg1) then
16175 Pool := Get_Pragma_Arg (Arg1);
16177 -- Case of Default_Storage_Pool (null);
16179 if Nkind (Pool) = N_Null then
16180 Analyze (Pool);
16182 -- This is an odd case, this is not really an expression,
16183 -- so we don't have a type for it. So just set the type to
16184 -- Empty.
16186 Set_Etype (Pool, Empty);
16188 -- Case of Default_Storage_Pool (Standard);
16190 elsif Nkind (Pool) = N_Identifier
16191 and then Chars (Pool) = Name_Standard
16192 then
16193 Analyze (Pool);
16195 if Entity (Pool) /= Standard_Standard then
16196 Error_Pragma_Arg
16197 ("package Standard is not directly visible", Arg1);
16198 end if;
16200 -- Case of Default_Storage_Pool (storage_pool_NAME);
16202 else
16203 -- If it's a configuration pragma, then the only allowed
16204 -- argument is "null".
16206 if Is_Configuration_Pragma then
16207 Error_Pragma_Arg ("NULL or Standard expected", Arg1);
16208 end if;
16210 -- The expected type for a non-"null" argument is
16211 -- Root_Storage_Pool'Class, and the pool must be a variable.
16213 Analyze_And_Resolve
16214 (Pool, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
16216 if Is_Variable (Pool) then
16218 -- A pragma that applies to a Ghost entity becomes Ghost
16219 -- for the purposes of legality checks and removal of
16220 -- ignored Ghost code.
16222 Mark_Ghost_Pragma (N, Entity (Pool));
16224 else
16225 Error_Pragma_Arg
16226 ("default storage pool must be a variable", Arg1);
16227 end if;
16228 end if;
16230 -- Record the pool name (or null). Freeze.Freeze_Entity for an
16231 -- access type will use this information to set the appropriate
16232 -- attributes of the access type. If the pragma appears in a
16233 -- generic unit it is ignored, given that it may refer to a
16234 -- local entity.
16236 if not Inside_A_Generic then
16237 Default_Pool := Pool;
16238 end if;
16239 end if;
16240 end Default_Storage_Pool;
16242 -------------
16243 -- Depends --
16244 -------------
16246 -- pragma Depends (DEPENDENCY_RELATION);
16248 -- DEPENDENCY_RELATION ::=
16249 -- null
16250 -- | (DEPENDENCY_CLAUSE {, DEPENDENCY_CLAUSE})
16252 -- DEPENDENCY_CLAUSE ::=
16253 -- OUTPUT_LIST =>[+] INPUT_LIST
16254 -- | NULL_DEPENDENCY_CLAUSE
16256 -- NULL_DEPENDENCY_CLAUSE ::= null => INPUT_LIST
16258 -- OUTPUT_LIST ::= OUTPUT | (OUTPUT {, OUTPUT})
16260 -- INPUT_LIST ::= null | INPUT | (INPUT {, INPUT})
16262 -- OUTPUT ::= NAME | FUNCTION_RESULT
16263 -- INPUT ::= NAME
16265 -- where FUNCTION_RESULT is a function Result attribute_reference
16267 -- Characteristics:
16269 -- * Analysis - The annotation undergoes initial checks to verify
16270 -- the legal placement and context. Secondary checks fully analyze
16271 -- the dependency clauses in:
16273 -- Analyze_Depends_In_Decl_Part
16275 -- * Expansion - None.
16277 -- * Template - The annotation utilizes the generic template of the
16278 -- related subprogram [body] when it is:
16280 -- aspect on subprogram declaration
16281 -- aspect on stand-alone subprogram body
16282 -- pragma on stand-alone subprogram body
16284 -- The annotation must prepare its own template when it is:
16286 -- pragma on subprogram declaration
16288 -- * Globals - Capture of global references must occur after full
16289 -- analysis.
16291 -- * Instance - The annotation is instantiated automatically when
16292 -- the related generic subprogram [body] is instantiated except for
16293 -- the "pragma on subprogram declaration" case. In that scenario
16294 -- the annotation must instantiate itself.
16296 when Pragma_Depends => Depends : declare
16297 Legal : Boolean;
16298 Spec_Id : Entity_Id;
16299 Subp_Decl : Node_Id;
16301 begin
16302 Analyze_Depends_Global (Spec_Id, Subp_Decl, Legal);
16304 if Legal then
16306 -- Chain the pragma on the contract for further processing by
16307 -- Analyze_Depends_In_Decl_Part.
16309 Add_Contract_Item (N, Spec_Id);
16311 -- Fully analyze the pragma when it appears inside an entry
16312 -- or subprogram body because it cannot benefit from forward
16313 -- references.
16315 if Nkind (Subp_Decl) in N_Entry_Body
16316 | N_Subprogram_Body
16317 | N_Subprogram_Body_Stub
16318 then
16319 -- The legality checks of pragmas Depends and Global are
16320 -- affected by the SPARK mode in effect and the volatility
16321 -- of the context. In addition these two pragmas are subject
16322 -- to an inherent order:
16324 -- 1) Global
16325 -- 2) Depends
16327 -- Analyze all these pragmas in the order outlined above
16329 Analyze_If_Present (Pragma_SPARK_Mode);
16330 Analyze_If_Present (Pragma_Volatile_Function);
16331 Analyze_If_Present (Pragma_Side_Effects);
16332 Analyze_If_Present (Pragma_Global);
16333 Analyze_Depends_In_Decl_Part (N);
16334 end if;
16335 end if;
16336 end Depends;
16338 ---------------------
16339 -- Detect_Blocking --
16340 ---------------------
16342 -- pragma Detect_Blocking;
16344 when Pragma_Detect_Blocking =>
16345 Ada_2005_Pragma;
16346 Check_Arg_Count (0);
16347 Check_Valid_Configuration_Pragma;
16348 Detect_Blocking := True;
16350 ------------------------------------
16351 -- Disable_Atomic_Synchronization --
16352 ------------------------------------
16354 -- pragma Disable_Atomic_Synchronization [(Entity)];
16356 when Pragma_Disable_Atomic_Synchronization =>
16357 GNAT_Pragma;
16358 Process_Disable_Enable_Atomic_Sync (Name_Suppress);
16360 -------------------
16361 -- Discard_Names --
16362 -------------------
16364 -- pragma Discard_Names [([On =>] LOCAL_NAME)];
16366 when Pragma_Discard_Names => Discard_Names : declare
16367 E : Entity_Id;
16368 E_Id : Node_Id;
16370 begin
16371 Check_Ada_83_Warning;
16373 -- Deal with configuration pragma case
16375 if Is_Configuration_Pragma then
16376 if Arg_Count /= 0 then
16377 Error_Pragma
16378 ("nonzero number of arguments for configuration pragma%");
16379 else
16380 Global_Discard_Names := True;
16381 end if;
16382 return;
16384 -- Otherwise, check correct appropriate context
16386 else
16387 Check_Is_In_Decl_Part_Or_Package_Spec;
16389 if Arg_Count = 0 then
16391 -- If there is no parameter, then from now on this pragma
16392 -- applies to any enumeration, exception or tagged type
16393 -- defined in the current declarative part, and recursively
16394 -- to any nested scope.
16396 Set_Discard_Names (Current_Scope);
16397 return;
16399 else
16400 Check_Arg_Count (1);
16401 Check_Optional_Identifier (Arg1, Name_On);
16402 Check_Arg_Is_Local_Name (Arg1);
16404 E_Id := Get_Pragma_Arg (Arg1);
16406 if Etype (E_Id) = Any_Type then
16407 return;
16408 end if;
16410 E := Entity (E_Id);
16412 -- A pragma that applies to a Ghost entity becomes Ghost for
16413 -- the purposes of legality checks and removal of ignored
16414 -- Ghost code.
16416 Mark_Ghost_Pragma (N, E);
16418 if (Is_First_Subtype (E)
16419 and then
16420 (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
16421 or else Ekind (E) = E_Exception
16422 then
16423 Set_Discard_Names (E);
16424 Record_Rep_Item (E, N);
16426 else
16427 Error_Pragma_Arg
16428 ("inappropriate entity for pragma%", Arg1);
16429 end if;
16430 end if;
16431 end if;
16432 end Discard_Names;
16434 ------------------------
16435 -- Dispatching_Domain --
16436 ------------------------
16438 -- pragma Dispatching_Domain (EXPRESSION);
16440 when Pragma_Dispatching_Domain => Dispatching_Domain : declare
16441 P : constant Node_Id := Parent (N);
16442 Arg : Node_Id;
16443 Ent : Entity_Id;
16445 begin
16446 Ada_2012_Pragma;
16447 Check_No_Identifiers;
16448 Check_Arg_Count (1);
16450 -- This pragma is born obsolete, but not the aspect
16452 if not From_Aspect_Specification (N) then
16453 Check_Restriction
16454 (No_Obsolescent_Features, Pragma_Identifier (N));
16455 end if;
16457 if Nkind (P) = N_Task_Definition then
16458 Arg := Get_Pragma_Arg (Arg1);
16459 Ent := Defining_Identifier (Parent (P));
16461 -- A pragma that applies to a Ghost entity becomes Ghost for
16462 -- the purposes of legality checks and removal of ignored Ghost
16463 -- code.
16465 Mark_Ghost_Pragma (N, Ent);
16467 -- The expression must be analyzed in the special manner
16468 -- described in "Handling of Default and Per-Object
16469 -- Expressions" in sem.ads.
16471 Preanalyze_Spec_Expression (Arg, RTE (RE_Dispatching_Domain));
16473 -- Check duplicate pragma before we chain the pragma in the Rep
16474 -- Item chain of Ent.
16476 Check_Duplicate_Pragma (Ent);
16477 Record_Rep_Item (Ent, N);
16479 -- Anything else is incorrect
16481 else
16482 Pragma_Misplaced;
16483 end if;
16484 end Dispatching_Domain;
16486 ---------------
16487 -- Elaborate --
16488 ---------------
16490 -- pragma Elaborate (library_unit_NAME {, library_unit_NAME});
16492 when Pragma_Elaborate => Elaborate : declare
16493 Arg : Node_Id;
16494 Citem : Node_Id;
16496 begin
16497 -- Pragma must be in context items list of a compilation unit
16499 if not Is_In_Context_Clause then
16500 Pragma_Misplaced;
16501 end if;
16503 -- Must be at least one argument
16505 if Arg_Count = 0 then
16506 Error_Pragma ("pragma% requires at least one argument");
16507 end if;
16509 -- In Ada 83 mode, there can be no items following it in the
16510 -- context list except other pragmas and implicit with clauses
16511 -- (e.g. those added by use of Rtsfind). In Ada 95 mode, this
16512 -- placement rule does not apply.
16514 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
16515 Citem := Next (N);
16516 while Present (Citem) loop
16517 if Nkind (Citem) = N_Pragma
16518 or else (Nkind (Citem) = N_With_Clause
16519 and then Implicit_With (Citem))
16520 then
16521 null;
16522 else
16523 Error_Pragma
16524 ("(Ada 83) pragma% must be at end of context clause");
16525 end if;
16527 Next (Citem);
16528 end loop;
16529 end if;
16531 -- Finally, the arguments must all be units mentioned in a with
16532 -- clause in the same context clause. Note we already checked (in
16533 -- Par.Prag) that the arguments are all identifiers or selected
16534 -- components.
16536 Arg := Arg1;
16537 Outer : while Present (Arg) loop
16538 Citem := First (List_Containing (N));
16539 Inner : while Citem /= N loop
16540 if Nkind (Citem) = N_With_Clause
16541 and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
16542 then
16543 Set_Elaborate_Present (Citem, True);
16544 Set_Elab_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
16546 -- With the pragma present, elaboration calls on
16547 -- subprograms from the named unit need no further
16548 -- checks, as long as the pragma appears in the current
16549 -- compilation unit. If the pragma appears in some unit
16550 -- in the context, there might still be a need for an
16551 -- Elaborate_All_Desirable from the current compilation
16552 -- to the named unit, so we keep the check enabled. This
16553 -- does not apply in SPARK mode, where we allow pragma
16554 -- Elaborate, but we don't trust it to be right so we
16555 -- will still insist on the Elaborate_All.
16557 if Legacy_Elaboration_Checks
16558 and then In_Extended_Main_Source_Unit (N)
16559 and then SPARK_Mode /= On
16560 then
16561 Set_Suppress_Elaboration_Warnings
16562 (Entity (Name (Citem)));
16563 end if;
16565 exit Inner;
16566 end if;
16568 Next (Citem);
16569 end loop Inner;
16571 if Citem = N then
16572 Error_Pragma_Arg
16573 ("argument of pragma% is not withed unit", Arg);
16574 end if;
16576 Next (Arg);
16577 end loop Outer;
16578 end Elaborate;
16580 -------------------
16581 -- Elaborate_All --
16582 -------------------
16584 -- pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
16586 when Pragma_Elaborate_All => Elaborate_All : declare
16587 Arg : Node_Id;
16588 Citem : Node_Id;
16590 begin
16591 Check_Ada_83_Warning;
16593 -- Pragma must be in context items list of a compilation unit
16595 if not Is_In_Context_Clause then
16596 Pragma_Misplaced;
16597 end if;
16599 -- Must be at least one argument
16601 if Arg_Count = 0 then
16602 Error_Pragma ("pragma% requires at least one argument");
16603 end if;
16605 -- Note: unlike pragma Elaborate, pragma Elaborate_All does not
16606 -- have to appear at the end of the context clause, but may
16607 -- appear mixed in with other items, even in Ada 83 mode.
16609 -- Final check: the arguments must all be units mentioned in
16610 -- a with clause in the same context clause. Note that we
16611 -- already checked (in Par.Prag) that all the arguments are
16612 -- either identifiers or selected components.
16614 Arg := Arg1;
16615 Outr : while Present (Arg) loop
16616 Citem := First (List_Containing (N));
16617 Innr : while Citem /= N loop
16618 if Nkind (Citem) = N_With_Clause
16619 and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
16620 then
16621 Set_Elaborate_All_Present (Citem, True);
16622 Set_Elab_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
16624 -- Suppress warnings and elaboration checks on the named
16625 -- unit if the pragma is in the current compilation, as
16626 -- for pragma Elaborate.
16628 if Legacy_Elaboration_Checks
16629 and then In_Extended_Main_Source_Unit (N)
16630 then
16631 Set_Suppress_Elaboration_Warnings
16632 (Entity (Name (Citem)));
16633 end if;
16635 exit Innr;
16636 end if;
16638 Next (Citem);
16639 end loop Innr;
16641 if Citem = N then
16642 Error_Pragma_Arg
16643 ("argument of pragma% is not withed unit", Arg);
16644 end if;
16646 Next (Arg);
16647 end loop Outr;
16648 end Elaborate_All;
16650 --------------------
16651 -- Elaborate_Body --
16652 --------------------
16654 -- pragma Elaborate_Body [( library_unit_NAME )];
16656 when Pragma_Elaborate_Body => Elaborate_Body : declare
16657 Cunit_Node : Node_Id;
16658 Cunit_Ent : Entity_Id;
16660 begin
16661 Check_Ada_83_Warning;
16662 Check_Valid_Library_Unit_Pragma;
16664 -- If N was rewritten as a null statement there is nothing more
16665 -- to do.
16667 if Nkind (N) = N_Null_Statement then
16668 return;
16669 end if;
16671 Cunit_Node := Cunit (Current_Sem_Unit);
16672 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
16674 -- A pragma that applies to a Ghost entity becomes Ghost for the
16675 -- purposes of legality checks and removal of ignored Ghost code.
16677 Mark_Ghost_Pragma (N, Cunit_Ent);
16679 if Nkind (Unit (Cunit_Node)) in
16680 N_Package_Body | N_Subprogram_Body
16681 then
16682 Error_Pragma ("pragma% must refer to a spec, not a body");
16683 else
16684 Set_Body_Required (Cunit_Node);
16685 Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
16687 -- If we are in dynamic elaboration mode, then we suppress
16688 -- elaboration warnings for the unit, since it is definitely
16689 -- fine NOT to do dynamic checks at the first level (and such
16690 -- checks will be suppressed because no elaboration boolean
16691 -- is created for Elaborate_Body packages).
16693 -- But in the static model of elaboration, Elaborate_Body is
16694 -- definitely NOT good enough to ensure elaboration safety on
16695 -- its own, since the body may WITH other units that are not
16696 -- safe from an elaboration point of view, so a client must
16697 -- still do an Elaborate_All on such units.
16699 -- Debug flag -gnatdD restores the old behavior of 3.13, where
16700 -- Elaborate_Body always suppressed elab warnings.
16702 if Legacy_Elaboration_Checks
16703 and then (Dynamic_Elaboration_Checks or Debug_Flag_DD)
16704 then
16705 Set_Suppress_Elaboration_Warnings (Cunit_Ent);
16706 end if;
16707 end if;
16708 end Elaborate_Body;
16710 ------------------------
16711 -- Elaboration_Checks --
16712 ------------------------
16714 -- pragma Elaboration_Checks (Static | Dynamic);
16716 when Pragma_Elaboration_Checks => Elaboration_Checks : declare
16717 procedure Check_Duplicate_Elaboration_Checks_Pragma;
16718 -- Emit an error if the current context list already contains
16719 -- a previous Elaboration_Checks pragma. This routine raises
16720 -- Pragma_Exit if a duplicate is found.
16722 procedure Ignore_Elaboration_Checks_Pragma;
16723 -- Warn that the effects of the pragma are ignored. This routine
16724 -- raises Pragma_Exit.
16726 -----------------------------------------------
16727 -- Check_Duplicate_Elaboration_Checks_Pragma --
16728 -----------------------------------------------
16730 procedure Check_Duplicate_Elaboration_Checks_Pragma is
16731 Item : Node_Id;
16733 begin
16734 Item := Prev (N);
16735 while Present (Item) loop
16736 if Nkind (Item) = N_Pragma
16737 and then Pragma_Name (Item) = Name_Elaboration_Checks
16738 then
16739 Duplication_Error
16740 (Prag => N,
16741 Prev => Item);
16742 raise Pragma_Exit;
16743 end if;
16745 Prev (Item);
16746 end loop;
16747 end Check_Duplicate_Elaboration_Checks_Pragma;
16749 --------------------------------------
16750 -- Ignore_Elaboration_Checks_Pragma --
16751 --------------------------------------
16753 procedure Ignore_Elaboration_Checks_Pragma is
16754 begin
16755 Error_Msg_Name_1 := Pname;
16756 Error_Msg_N ("??effects of pragma % are ignored", N);
16757 Error_Msg_N
16758 ("\place pragma on initial declaration of library unit", N);
16760 raise Pragma_Exit;
16761 end Ignore_Elaboration_Checks_Pragma;
16763 -- Local variables
16765 Context : constant Node_Id := Parent (N);
16766 Unt : Node_Id;
16768 -- Start of processing for Elaboration_Checks
16770 begin
16771 GNAT_Pragma;
16772 Check_Arg_Count (1);
16773 Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
16775 -- The pragma appears in a configuration file
16777 if No (Context) then
16778 Check_Valid_Configuration_Pragma;
16779 Check_Duplicate_Elaboration_Checks_Pragma;
16781 -- The pragma acts as a configuration pragma in a compilation unit
16783 -- pragma Elaboration_Checks (...);
16784 -- package Pack is ...;
16786 elsif Nkind (Context) = N_Compilation_Unit
16787 and then List_Containing (N) = Context_Items (Context)
16788 then
16789 Check_Valid_Configuration_Pragma;
16790 Check_Duplicate_Elaboration_Checks_Pragma;
16792 Unt := Unit (Context);
16794 -- The pragma must appear on the initial declaration of a unit.
16795 -- If this is not the case, warn that the effects of the pragma
16796 -- are ignored.
16798 if Nkind (Unt) = N_Package_Body then
16799 Ignore_Elaboration_Checks_Pragma;
16801 -- Check the Acts_As_Spec flag of the compilation units itself
16802 -- to determine whether the subprogram body completes since it
16803 -- has not been analyzed yet. This is safe because compilation
16804 -- units are not overloadable.
16806 elsif Nkind (Unt) = N_Subprogram_Body
16807 and then not Acts_As_Spec (Context)
16808 then
16809 Ignore_Elaboration_Checks_Pragma;
16811 elsif Nkind (Unt) = N_Subunit then
16812 Ignore_Elaboration_Checks_Pragma;
16813 end if;
16815 -- Otherwise the pragma does not appear at the configuration level
16816 -- and is illegal.
16818 else
16819 Pragma_Misplaced;
16820 end if;
16822 -- At this point the pragma is not a duplicate, and appears in the
16823 -- proper context. Set the elaboration model in effect.
16825 Dynamic_Elaboration_Checks :=
16826 Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic;
16827 end Elaboration_Checks;
16829 ---------------
16830 -- Eliminate --
16831 ---------------
16833 -- pragma Eliminate (
16834 -- [Unit_Name =>] IDENTIFIER | SELECTED_COMPONENT,
16835 -- [Entity =>] IDENTIFIER |
16836 -- SELECTED_COMPONENT |
16837 -- STRING_LITERAL]
16838 -- [, Source_Location => SOURCE_TRACE]);
16840 -- SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
16841 -- SOURCE_TRACE ::= STRING_LITERAL
16843 when Pragma_Eliminate => Eliminate : declare
16844 Args : Args_List (1 .. 5);
16845 Names : constant Name_List (1 .. 5) := (
16846 Name_Unit_Name,
16847 Name_Entity,
16848 Name_Parameter_Types,
16849 Name_Result_Type,
16850 Name_Source_Location);
16852 -- Note : Parameter_Types and Result_Type are leftovers from
16853 -- prior implementations of the pragma. They are not generated
16854 -- by the gnatelim tool, and play no role in selecting which
16855 -- of a set of overloaded names is chosen for elimination.
16857 Unit_Name : Node_Id renames Args (1);
16858 Entity : Node_Id renames Args (2);
16859 Parameter_Types : Node_Id renames Args (3);
16860 Result_Type : Node_Id renames Args (4);
16861 Source_Location : Node_Id renames Args (5);
16863 begin
16864 GNAT_Pragma;
16865 Check_Valid_Configuration_Pragma;
16866 Gather_Associations (Names, Args);
16868 if No (Unit_Name) then
16869 Error_Pragma ("missing Unit_Name argument for pragma%");
16870 end if;
16872 if No (Entity)
16873 and then (Present (Parameter_Types)
16874 or else
16875 Present (Result_Type)
16876 or else
16877 Present (Source_Location))
16878 then
16879 Error_Pragma ("missing Entity argument for pragma%");
16880 end if;
16882 if (Present (Parameter_Types)
16883 or else
16884 Present (Result_Type))
16885 and then
16886 Present (Source_Location)
16887 then
16888 Error_Pragma
16889 ("parameter profile and source location cannot be used "
16890 & "together in pragma%");
16891 end if;
16893 Process_Eliminate_Pragma
16895 Unit_Name,
16896 Entity,
16897 Parameter_Types,
16898 Result_Type,
16899 Source_Location);
16900 end Eliminate;
16902 -----------------------------------
16903 -- Enable_Atomic_Synchronization --
16904 -----------------------------------
16906 -- pragma Enable_Atomic_Synchronization [(Entity)];
16908 when Pragma_Enable_Atomic_Synchronization =>
16909 GNAT_Pragma;
16910 Process_Disable_Enable_Atomic_Sync (Name_Unsuppress);
16912 -----------------------
16913 -- Exceptional_Cases --
16914 -----------------------
16916 -- pragma Exceptional_Cases ( EXCEPTIONAL_CONTRACT_LIST );
16918 -- EXCEPTIONAL_CONTRACT_LIST ::=
16919 -- ( EXCEPTIONAL_CONTRACT {, EXCEPTIONAL_CONTRACT })
16921 -- EXCEPTIONAL_CONTRACT ::=
16922 -- EXCEPTION_CHOICE {'|' EXCEPTION_CHOICE} => CONSEQUENCE
16924 -- where
16926 -- CONSEQUENCE ::= boolean_EXPRESSION
16928 -- Characteristics:
16930 -- * Analysis - The annotation undergoes initial checks to verify
16931 -- the legal placement and context. Secondary checks preanalyze the
16932 -- expressions in:
16934 -- Analyze_Exceptional_Cases_In_Decl_Part
16936 -- * Expansion - The annotation is expanded during the expansion of
16937 -- the related subprogram [body] contract as performed in:
16939 -- Expand_Subprogram_Contract
16941 -- * Template - The annotation utilizes the generic template of the
16942 -- related subprogram [body] when it is:
16944 -- aspect on subprogram declaration
16945 -- aspect on stand-alone subprogram body
16946 -- pragma on stand-alone subprogram body
16948 -- The annotation must prepare its own template when it is:
16950 -- pragma on subprogram declaration
16952 -- * Globals - Capture of global references must occur after full
16953 -- analysis.
16955 -- * Instance - The annotation is instantiated automatically when
16956 -- the related generic subprogram [body] is instantiated except for
16957 -- the "pragma on subprogram declaration" case. In that scenario
16958 -- the annotation must instantiate itself.
16960 when Pragma_Exceptional_Cases => Exceptional_Cases : declare
16961 Spec_Id : Entity_Id;
16962 Subp_Decl : Node_Id;
16963 Subp_Spec : Node_Id;
16965 begin
16966 GNAT_Pragma;
16967 Check_No_Identifiers;
16968 Check_Arg_Count (1);
16970 -- Ensure the proper placement of the pragma. Exceptional_Cases
16971 -- must be associated with a subprogram declaration or a body that
16972 -- acts as a spec.
16974 Subp_Decl :=
16975 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
16977 -- Generic subprogram
16979 if Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
16980 null;
16982 -- Body acts as spec
16984 elsif Nkind (Subp_Decl) = N_Subprogram_Body
16985 and then No (Corresponding_Spec (Subp_Decl))
16986 then
16987 null;
16989 -- Body stub acts as spec
16991 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
16992 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
16993 then
16994 null;
16996 -- Subprogram
16998 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
16999 Subp_Spec := Specification (Subp_Decl);
17001 -- Pragma Exceptional_Cases is forbidden on null procedures,
17002 -- as this may lead to potential ambiguities in behavior when
17003 -- interface null procedures are involved. Also, it just
17004 -- wouldn't make sense, because null procedures do not raise
17005 -- exceptions.
17007 if Nkind (Subp_Spec) = N_Procedure_Specification
17008 and then Null_Present (Subp_Spec)
17009 then
17010 Error_Msg_N (Fix_Error
17011 ("pragma % cannot apply to null procedure"), N);
17012 return;
17013 end if;
17015 else
17016 Pragma_Misplaced;
17017 end if;
17019 Spec_Id := Unique_Defining_Entity (Subp_Decl);
17021 -- In order to call Is_Function_With_Side_Effects, analyze pragma
17022 -- Side_Effects if present.
17024 Analyze_If_Present (Pragma_Side_Effects);
17026 -- Pragma Exceptional_Cases is not allowed on functions without
17027 -- side effects.
17029 if Ekind (Spec_Id) in E_Function | E_Generic_Function
17030 and then not Is_Function_With_Side_Effects (Spec_Id)
17031 then
17032 Error_Msg_Sloc := GEC_Exceptional_Cases_On_Function;
17034 if Ekind (Spec_Id) = E_Function then
17035 Error_Msg_N (Fix_Error
17036 ("pragma % cannot apply to function '[[]']"), N);
17037 return;
17039 elsif Ekind (Spec_Id) = E_Generic_Function then
17040 Error_Msg_N (Fix_Error
17041 ("pragma % cannot apply to generic function '[[]']"), N);
17042 return;
17043 end if;
17044 end if;
17046 -- A pragma that applies to a Ghost entity becomes Ghost for the
17047 -- purposes of legality checks and removal of ignored Ghost code.
17049 Mark_Ghost_Pragma (N, Spec_Id);
17050 Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
17052 -- Chain the pragma on the contract for further processing by
17053 -- Analyze_Exceptional_Cases_In_Decl_Part.
17055 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
17057 -- Fully analyze the pragma when it appears inside a subprogram
17058 -- body because it cannot benefit from forward references.
17060 if Nkind (Subp_Decl) in N_Subprogram_Body
17061 | N_Subprogram_Body_Stub
17062 then
17063 -- The legality checks of pragma Exceptional_Cases are
17064 -- affected by the SPARK mode in effect and the volatility
17065 -- of the context. Analyze all pragmas in a specific order.
17067 Analyze_If_Present (Pragma_SPARK_Mode);
17068 Analyze_If_Present (Pragma_Volatile_Function);
17069 Analyze_Exceptional_Cases_In_Decl_Part (N);
17070 end if;
17071 end Exceptional_Cases;
17073 ------------
17074 -- Export --
17075 ------------
17077 -- pragma Export (
17078 -- [ Convention =>] convention_IDENTIFIER,
17079 -- [ Entity =>] LOCAL_NAME
17080 -- [, [External_Name =>] static_string_EXPRESSION ]
17081 -- [, [Link_Name =>] static_string_EXPRESSION ]);
17083 when Pragma_Export => Export : declare
17084 C : Convention_Id;
17085 Def_Id : Entity_Id;
17087 pragma Warnings (Off, C);
17089 begin
17090 Check_Ada_83_Warning;
17091 Check_Arg_Order
17092 ((Name_Convention,
17093 Name_Entity,
17094 Name_External_Name,
17095 Name_Link_Name));
17097 Check_At_Least_N_Arguments (2);
17098 Check_At_Most_N_Arguments (4);
17100 -- In Relaxed_RM_Semantics, support old Ada 83 style:
17101 -- pragma Export (Entity, "external name");
17103 if Relaxed_RM_Semantics
17104 and then Arg_Count = 2
17105 and then Nkind (Expression (Arg2)) = N_String_Literal
17106 then
17107 C := Convention_C;
17108 Def_Id := Get_Pragma_Arg (Arg1);
17109 Analyze (Def_Id);
17111 if not Is_Entity_Name (Def_Id) then
17112 Error_Pragma_Arg ("entity name required", Arg1);
17113 end if;
17115 Def_Id := Entity (Def_Id);
17116 Set_Exported (Def_Id, Arg1);
17118 else
17119 Process_Convention (C, Def_Id);
17121 -- A pragma that applies to a Ghost entity becomes Ghost for
17122 -- the purposes of legality checks and removal of ignored Ghost
17123 -- code.
17125 Mark_Ghost_Pragma (N, Def_Id);
17127 if Ekind (Def_Id) /= E_Constant then
17128 Note_Possible_Modification
17129 (Get_Pragma_Arg (Arg2), Sure => False);
17130 end if;
17132 Process_Interface_Name (Def_Id, Arg3, Arg4, N);
17133 Set_Exported (Def_Id, Arg2);
17134 end if;
17136 -- If the entity is a deferred constant, propagate the information
17137 -- to the full view, because gigi elaborates the full view only.
17139 if Ekind (Def_Id) = E_Constant
17140 and then Present (Full_View (Def_Id))
17141 then
17142 declare
17143 Id2 : constant Entity_Id := Full_View (Def_Id);
17144 begin
17145 Set_Is_Exported (Id2, Is_Exported (Def_Id));
17146 Set_First_Rep_Item (Id2, First_Rep_Item (Def_Id));
17147 Set_Interface_Name
17148 (Id2, Einfo.Entities.Interface_Name (Def_Id));
17149 end;
17150 end if;
17151 end Export;
17153 ---------------------
17154 -- Export_Function --
17155 ---------------------
17157 -- pragma Export_Function (
17158 -- [Internal =>] LOCAL_NAME
17159 -- [, [External =>] EXTERNAL_SYMBOL]
17160 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
17161 -- [, [Result_Type =>] TYPE_DESIGNATOR]
17162 -- [, [Mechanism =>] MECHANISM]
17163 -- [, [Result_Mechanism =>] MECHANISM_NAME]);
17165 -- EXTERNAL_SYMBOL ::=
17166 -- IDENTIFIER
17167 -- | static_string_EXPRESSION
17169 -- PARAMETER_TYPES ::=
17170 -- null
17171 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
17173 -- TYPE_DESIGNATOR ::=
17174 -- subtype_NAME
17175 -- | subtype_Name ' Access
17177 -- MECHANISM ::=
17178 -- MECHANISM_NAME
17179 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
17181 -- MECHANISM_ASSOCIATION ::=
17182 -- [formal_parameter_NAME =>] MECHANISM_NAME
17184 -- MECHANISM_NAME ::=
17185 -- Value
17186 -- | Reference
17188 when Pragma_Export_Function => Export_Function : declare
17189 Args : Args_List (1 .. 6);
17190 Names : constant Name_List (1 .. 6) := (
17191 Name_Internal,
17192 Name_External,
17193 Name_Parameter_Types,
17194 Name_Result_Type,
17195 Name_Mechanism,
17196 Name_Result_Mechanism);
17198 Internal : Node_Id renames Args (1);
17199 External : Node_Id renames Args (2);
17200 Parameter_Types : Node_Id renames Args (3);
17201 Result_Type : Node_Id renames Args (4);
17202 Mechanism : Node_Id renames Args (5);
17203 Result_Mechanism : Node_Id renames Args (6);
17205 begin
17206 GNAT_Pragma;
17207 Gather_Associations (Names, Args);
17208 Process_Extended_Import_Export_Subprogram_Pragma (
17209 Arg_Internal => Internal,
17210 Arg_External => External,
17211 Arg_Parameter_Types => Parameter_Types,
17212 Arg_Result_Type => Result_Type,
17213 Arg_Mechanism => Mechanism,
17214 Arg_Result_Mechanism => Result_Mechanism);
17215 end Export_Function;
17217 -------------------
17218 -- Export_Object --
17219 -------------------
17221 -- pragma Export_Object (
17222 -- [Internal =>] LOCAL_NAME
17223 -- [, [External =>] EXTERNAL_SYMBOL]
17224 -- [, [Size =>] EXTERNAL_SYMBOL]);
17226 -- EXTERNAL_SYMBOL ::=
17227 -- IDENTIFIER
17228 -- | static_string_EXPRESSION
17230 -- PARAMETER_TYPES ::=
17231 -- null
17232 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
17234 -- TYPE_DESIGNATOR ::=
17235 -- subtype_NAME
17236 -- | subtype_Name ' Access
17238 -- MECHANISM ::=
17239 -- MECHANISM_NAME
17240 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
17242 -- MECHANISM_ASSOCIATION ::=
17243 -- [formal_parameter_NAME =>] MECHANISM_NAME
17245 -- MECHANISM_NAME ::=
17246 -- Value
17247 -- | Reference
17249 when Pragma_Export_Object => Export_Object : declare
17250 Args : Args_List (1 .. 3);
17251 Names : constant Name_List (1 .. 3) := (
17252 Name_Internal,
17253 Name_External,
17254 Name_Size);
17256 Internal : Node_Id renames Args (1);
17257 External : Node_Id renames Args (2);
17258 Size : Node_Id renames Args (3);
17260 begin
17261 GNAT_Pragma;
17262 Gather_Associations (Names, Args);
17263 Process_Extended_Import_Export_Object_Pragma (
17264 Arg_Internal => Internal,
17265 Arg_External => External,
17266 Arg_Size => Size);
17267 end Export_Object;
17269 ----------------------
17270 -- Export_Procedure --
17271 ----------------------
17273 -- pragma Export_Procedure (
17274 -- [Internal =>] LOCAL_NAME
17275 -- [, [External =>] EXTERNAL_SYMBOL]
17276 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
17277 -- [, [Mechanism =>] MECHANISM]);
17279 -- EXTERNAL_SYMBOL ::=
17280 -- IDENTIFIER
17281 -- | static_string_EXPRESSION
17283 -- PARAMETER_TYPES ::=
17284 -- null
17285 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
17287 -- TYPE_DESIGNATOR ::=
17288 -- subtype_NAME
17289 -- | subtype_Name ' Access
17291 -- MECHANISM ::=
17292 -- MECHANISM_NAME
17293 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
17295 -- MECHANISM_ASSOCIATION ::=
17296 -- [formal_parameter_NAME =>] MECHANISM_NAME
17298 -- MECHANISM_NAME ::=
17299 -- Value
17300 -- | Reference
17302 when Pragma_Export_Procedure => Export_Procedure : declare
17303 Args : Args_List (1 .. 4);
17304 Names : constant Name_List (1 .. 4) := (
17305 Name_Internal,
17306 Name_External,
17307 Name_Parameter_Types,
17308 Name_Mechanism);
17310 Internal : Node_Id renames Args (1);
17311 External : Node_Id renames Args (2);
17312 Parameter_Types : Node_Id renames Args (3);
17313 Mechanism : Node_Id renames Args (4);
17315 begin
17316 GNAT_Pragma;
17317 Gather_Associations (Names, Args);
17318 Process_Extended_Import_Export_Subprogram_Pragma (
17319 Arg_Internal => Internal,
17320 Arg_External => External,
17321 Arg_Parameter_Types => Parameter_Types,
17322 Arg_Mechanism => Mechanism);
17323 end Export_Procedure;
17325 -----------------------------
17326 -- Export_Valued_Procedure --
17327 -----------------------------
17329 -- pragma Export_Valued_Procedure (
17330 -- [Internal =>] LOCAL_NAME
17331 -- [, [External =>] EXTERNAL_SYMBOL,]
17332 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
17333 -- [, [Mechanism =>] MECHANISM]);
17335 -- EXTERNAL_SYMBOL ::=
17336 -- IDENTIFIER
17337 -- | static_string_EXPRESSION
17339 -- PARAMETER_TYPES ::=
17340 -- null
17341 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
17343 -- TYPE_DESIGNATOR ::=
17344 -- subtype_NAME
17345 -- | subtype_Name ' Access
17347 -- MECHANISM ::=
17348 -- MECHANISM_NAME
17349 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
17351 -- MECHANISM_ASSOCIATION ::=
17352 -- [formal_parameter_NAME =>] MECHANISM_NAME
17354 -- MECHANISM_NAME ::=
17355 -- Value
17356 -- | Reference
17358 when Pragma_Export_Valued_Procedure =>
17359 Export_Valued_Procedure : declare
17360 Args : Args_List (1 .. 4);
17361 Names : constant Name_List (1 .. 4) := (
17362 Name_Internal,
17363 Name_External,
17364 Name_Parameter_Types,
17365 Name_Mechanism);
17367 Internal : Node_Id renames Args (1);
17368 External : Node_Id renames Args (2);
17369 Parameter_Types : Node_Id renames Args (3);
17370 Mechanism : Node_Id renames Args (4);
17372 begin
17373 GNAT_Pragma;
17374 Gather_Associations (Names, Args);
17375 Process_Extended_Import_Export_Subprogram_Pragma (
17376 Arg_Internal => Internal,
17377 Arg_External => External,
17378 Arg_Parameter_Types => Parameter_Types,
17379 Arg_Mechanism => Mechanism);
17380 end Export_Valued_Procedure;
17382 -------------------
17383 -- Extend_System --
17384 -------------------
17386 -- pragma Extend_System ([Name =>] Identifier);
17388 when Pragma_Extend_System =>
17389 GNAT_Pragma;
17390 Check_Valid_Configuration_Pragma;
17391 Check_Arg_Count (1);
17392 Check_Optional_Identifier (Arg1, Name_Name);
17393 Check_Arg_Is_Identifier (Arg1);
17395 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
17397 if Name_Len > 4
17398 and then Name_Buffer (1 .. 4) = "aux_"
17399 then
17400 if Present (System_Extend_Pragma_Arg) then
17401 if Chars (Get_Pragma_Arg (Arg1)) =
17402 Chars (Expression (System_Extend_Pragma_Arg))
17403 then
17404 null;
17405 else
17406 Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
17407 Error_Pragma ("pragma% conflicts with that #");
17408 end if;
17410 else
17411 System_Extend_Pragma_Arg := Arg1;
17413 if not GNAT_Mode then
17414 System_Extend_Unit := Arg1;
17415 end if;
17416 end if;
17417 else
17418 Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
17419 end if;
17421 ------------------------
17422 -- Extensions_Allowed --
17423 ------------------------
17425 -- pragma Extensions_Allowed (ON | OFF | ALL_EXTENSIONS);
17427 when Pragma_Extensions_Allowed =>
17428 GNAT_Pragma;
17429 Check_Arg_Count (1);
17430 Check_No_Identifiers;
17431 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off, Name_All_Extensions);
17433 if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
17434 Ada_Version := Ada_With_Core_Extensions;
17435 elsif Chars (Get_Pragma_Arg (Arg1)) = Name_All_Extensions then
17436 Ada_Version := Ada_With_All_Extensions;
17437 else
17438 Ada_Version := Ada_Version_Explicit;
17439 Ada_Version_Pragma := Empty;
17440 end if;
17442 ------------------------
17443 -- Extensions_Visible --
17444 ------------------------
17446 -- pragma Extensions_Visible [ (static_boolean_EXPRESSION) ];
17448 -- Characteristics:
17450 -- * Analysis - The annotation is fully analyzed immediately upon
17451 -- elaboration as its expression must be static.
17453 -- * Expansion - None.
17455 -- * Template - The annotation utilizes the generic template of the
17456 -- related subprogram [body] when it is:
17458 -- aspect on subprogram declaration
17459 -- aspect on stand-alone subprogram body
17460 -- pragma on stand-alone subprogram body
17462 -- The annotation must prepare its own template when it is:
17464 -- pragma on subprogram declaration
17466 -- * Globals - Capture of global references must occur after full
17467 -- analysis.
17469 -- * Instance - The annotation is instantiated automatically when
17470 -- the related generic subprogram [body] is instantiated except for
17471 -- the "pragma on subprogram declaration" case. In that scenario
17472 -- the annotation must instantiate itself.
17474 when Pragma_Extensions_Visible => Extensions_Visible : declare
17475 Formal : Entity_Id;
17476 Has_OK_Formal : Boolean := False;
17477 Spec_Id : Entity_Id;
17478 Subp_Decl : Node_Id;
17480 begin
17481 GNAT_Pragma;
17482 Check_No_Identifiers;
17483 Check_At_Most_N_Arguments (1);
17485 Subp_Decl :=
17486 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
17488 -- Abstract subprogram declaration
17490 if Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
17491 null;
17493 -- Generic subprogram declaration
17495 elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
17496 null;
17498 -- Body acts as spec
17500 elsif Nkind (Subp_Decl) = N_Subprogram_Body
17501 and then No (Corresponding_Spec (Subp_Decl))
17502 then
17503 null;
17505 -- Body stub acts as spec
17507 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
17508 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
17509 then
17510 null;
17512 -- Subprogram declaration
17514 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
17515 null;
17517 -- Otherwise the pragma is associated with an illegal construct
17519 else
17520 Error_Pragma ("pragma % must apply to a subprogram");
17521 end if;
17523 -- Mark the pragma as Ghost if the related subprogram is also
17524 -- Ghost. This also ensures that any expansion performed further
17525 -- below will produce Ghost nodes.
17527 Spec_Id := Unique_Defining_Entity (Subp_Decl);
17528 Mark_Ghost_Pragma (N, Spec_Id);
17530 -- Chain the pragma on the contract for completeness
17532 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
17534 -- The legality checks of pragma Extension_Visible are affected
17535 -- by the SPARK mode in effect. Analyze all pragmas in specific
17536 -- order.
17538 Analyze_If_Present (Pragma_SPARK_Mode);
17540 -- Examine the formals of the related subprogram
17542 Formal := First_Formal (Spec_Id);
17543 while Present (Formal) loop
17545 -- At least one of the formals is of a specific tagged type,
17546 -- the pragma is legal.
17548 if Is_Specific_Tagged_Type (Etype (Formal)) then
17549 Has_OK_Formal := True;
17550 exit;
17552 -- A generic subprogram with at least one formal of a private
17553 -- type ensures the legality of the pragma because the actual
17554 -- may be specifically tagged. Note that this is verified by
17555 -- the check above at instantiation time.
17557 elsif Is_Private_Type (Etype (Formal))
17558 and then Is_Generic_Type (Etype (Formal))
17559 then
17560 Has_OK_Formal := True;
17561 exit;
17562 end if;
17564 Next_Formal (Formal);
17565 end loop;
17567 if not Has_OK_Formal then
17568 Error_Msg_Name_1 := Pname;
17569 Error_Msg_N (Fix_Error ("incorrect placement of pragma %"), N);
17570 Error_Msg_NE
17571 ("\subprogram & lacks parameter of specific tagged or "
17572 & "generic private type", N, Spec_Id);
17574 return;
17575 end if;
17577 -- Analyze the Boolean expression (if any)
17579 if Present (Arg1) then
17580 Check_Static_Boolean_Expression
17581 (Expression (Get_Argument (N, Spec_Id)));
17582 end if;
17583 end Extensions_Visible;
17585 --------------
17586 -- External --
17587 --------------
17589 -- pragma External (
17590 -- [ Convention =>] convention_IDENTIFIER,
17591 -- [ Entity =>] LOCAL_NAME
17592 -- [, [External_Name =>] static_string_EXPRESSION ]
17593 -- [, [Link_Name =>] static_string_EXPRESSION ]);
17595 when Pragma_External => External : declare
17596 C : Convention_Id;
17597 E : Entity_Id;
17598 pragma Warnings (Off, C);
17600 begin
17601 GNAT_Pragma;
17602 Check_Arg_Order
17603 ((Name_Convention,
17604 Name_Entity,
17605 Name_External_Name,
17606 Name_Link_Name));
17607 Check_At_Least_N_Arguments (2);
17608 Check_At_Most_N_Arguments (4);
17609 Process_Convention (C, E);
17611 -- A pragma that applies to a Ghost entity becomes Ghost for the
17612 -- purposes of legality checks and removal of ignored Ghost code.
17614 Mark_Ghost_Pragma (N, E);
17616 Note_Possible_Modification
17617 (Get_Pragma_Arg (Arg2), Sure => False);
17618 Process_Interface_Name (E, Arg3, Arg4, N);
17619 Set_Exported (E, Arg2);
17620 end External;
17622 --------------------------
17623 -- External_Name_Casing --
17624 --------------------------
17626 -- pragma External_Name_Casing (
17627 -- UPPERCASE | LOWERCASE
17628 -- [, AS_IS | UPPERCASE | LOWERCASE]);
17630 when Pragma_External_Name_Casing =>
17631 GNAT_Pragma;
17632 Check_No_Identifiers;
17634 if Arg_Count = 2 then
17635 Check_Arg_Is_One_Of
17636 (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
17638 case Chars (Get_Pragma_Arg (Arg2)) is
17639 when Name_As_Is =>
17640 Opt.External_Name_Exp_Casing := As_Is;
17642 when Name_Uppercase =>
17643 Opt.External_Name_Exp_Casing := Uppercase;
17645 when Name_Lowercase =>
17646 Opt.External_Name_Exp_Casing := Lowercase;
17648 when others =>
17649 null;
17650 end case;
17652 else
17653 Check_Arg_Count (1);
17654 end if;
17656 Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
17658 case Chars (Get_Pragma_Arg (Arg1)) is
17659 when Name_Uppercase =>
17660 Opt.External_Name_Imp_Casing := Uppercase;
17662 when Name_Lowercase =>
17663 Opt.External_Name_Imp_Casing := Lowercase;
17665 when others =>
17666 null;
17667 end case;
17669 ---------------
17670 -- Fast_Math --
17671 ---------------
17673 -- pragma Fast_Math;
17675 when Pragma_Fast_Math =>
17676 GNAT_Pragma;
17677 Check_No_Identifiers;
17678 Check_Valid_Configuration_Pragma;
17679 Fast_Math := True;
17681 --------------------------
17682 -- Favor_Top_Level --
17683 --------------------------
17685 -- pragma Favor_Top_Level (type_LOCAL_NAME);
17687 when Pragma_Favor_Top_Level => Favor_Top_Level : declare
17688 Typ : Entity_Id;
17690 begin
17691 GNAT_Pragma;
17692 Check_No_Identifiers;
17693 Check_Arg_Count (1);
17694 Check_Arg_Is_Local_Name (Arg1);
17695 Typ := Entity (Get_Pragma_Arg (Arg1));
17697 -- A pragma that applies to a Ghost entity becomes Ghost for the
17698 -- purposes of legality checks and removal of ignored Ghost code.
17700 Mark_Ghost_Pragma (N, Typ);
17702 -- If it's an access-to-subprogram type (in particular, not a
17703 -- subtype), set the flag on that type.
17705 if Is_Access_Subprogram_Type (Typ) then
17706 Set_Can_Use_Internal_Rep (Typ, False);
17708 -- Otherwise it's an error (name denotes the wrong sort of entity)
17710 else
17711 Error_Pragma_Arg
17712 ("access-to-subprogram type expected",
17713 Get_Pragma_Arg (Arg1));
17714 end if;
17715 end Favor_Top_Level;
17717 ---------------------------
17718 -- Finalize_Storage_Only --
17719 ---------------------------
17721 -- pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
17723 when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
17724 Assoc : constant Node_Id := Arg1;
17725 Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
17726 Typ : Entity_Id;
17728 begin
17729 GNAT_Pragma;
17730 Check_No_Identifiers;
17731 Check_Arg_Count (1);
17732 Check_Arg_Is_Local_Name (Arg1);
17734 Find_Type (Type_Id);
17735 Typ := Entity (Type_Id);
17737 if Typ = Any_Type
17738 or else Rep_Item_Too_Early (Typ, N)
17739 then
17740 return;
17741 else
17742 Typ := Underlying_Type (Typ);
17743 end if;
17745 if not Is_Controlled (Typ) then
17746 Error_Pragma ("pragma% must specify controlled type");
17747 end if;
17749 Check_First_Subtype (Arg1);
17751 if Finalize_Storage_Only (Typ) then
17752 Error_Pragma ("duplicate pragma%, only one allowed");
17754 elsif not Rep_Item_Too_Late (Typ, N) then
17755 Set_Finalize_Storage_Only (Base_Type (Typ), True);
17756 end if;
17757 end Finalize_Storage;
17759 ----------------------------------------
17760 -- Pragma_First_Controlling_Parameter --
17761 ----------------------------------------
17763 when Pragma_First_Controlling_Parameter => First_Ctrl_Param : declare
17764 Arg : Node_Id;
17765 E : Entity_Id := Empty;
17766 Expr : Node_Id := Empty;
17768 begin
17769 GNAT_Pragma;
17770 Check_At_Least_N_Arguments (1);
17771 Check_At_Most_N_Arguments (2);
17773 Arg := Get_Pragma_Arg (Arg1);
17774 Check_Arg_Is_Identifier (Arg);
17776 Analyze (Arg);
17777 E := Entity (Arg);
17779 if Present (Arg2) then
17780 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_Boolean);
17781 Expr := Get_Pragma_Arg (Arg2);
17782 Analyze_And_Resolve (Expr, Standard_Boolean);
17783 end if;
17785 if not Core_Extensions_Allowed then
17786 if No (Expr)
17787 or else
17788 (Present (Expr)
17789 and then Is_Entity_Name (Expr)
17790 and then Entity (Expr) = Standard_True)
17791 then
17792 Error_Msg_GNAT_Extension
17793 ("'First_'Controlling_'Parameter", Sloc (N),
17794 Is_Core_Extension => True);
17795 end if;
17797 return;
17799 elsif Present (Expr)
17800 and then Is_Entity_Name (Expr)
17801 and then Entity (Expr) = Standard_False
17802 then
17803 if Is_Derived_Type (E)
17804 and then Has_First_Controlling_Parameter_Aspect (Etype (E))
17805 then
17806 Error_Msg_Name_1 := Name_First_Controlling_Parameter;
17807 Error_Msg_N
17808 ("specification of inherited True value for aspect% can "
17809 & "only confirm parent value", Pragma_Identifier (N));
17810 end if;
17812 return;
17813 end if;
17815 if No (E)
17816 or else not Is_Type (E)
17817 or else not (Is_Tagged_Type (E)
17818 or else Is_Concurrent_Type (E))
17819 then
17820 Error_Pragma
17821 ("pragma% must specify tagged type or concurrent type");
17822 end if;
17824 -- Check use of the pragma on private types
17826 if Has_Private_Declaration (E) then
17827 declare
17828 Prev_Id : constant Entity_Id :=
17829 Incomplete_Or_Partial_View (E);
17830 begin
17831 if Is_Tagged_Type (Prev_Id) then
17832 if Has_First_Controlling_Parameter_Aspect (Prev_Id) then
17833 Error_Pragma
17834 ("pragma already specified in private declaration");
17835 else
17836 Error_Msg_N
17837 ("hidden 'First_'Controlling_'Parameter tagged type"
17838 & " not allowed", N);
17839 end if;
17841 -- No action needed if the partial view is not tagged. For
17842 -- example:
17844 -- package Example is
17845 -- type Private_Type is private;
17846 -- private
17847 -- type Private_Type is new ... with null record
17848 -- with First_Controlling_Parameter; -- Legal
17849 -- end;
17851 else
17852 null;
17853 end if;
17854 end;
17855 end if;
17857 -- The corresponding record type of concurrent types will not be
17858 -- a tagged type when it does not implement some interface type.
17860 if Is_Concurrent_Type (E)
17861 and then Present (Parent (E))
17862 and then No (Interface_List (Parent (E)))
17863 then
17864 if Warn_On_Non_Dispatching_Primitives then
17865 Error_Msg_N
17866 ("?_j?'First_'Controlling_'Parameter has no effect", N);
17867 Error_Msg_NE
17868 ("?_j?because & does not implement interface types",
17869 N, E);
17870 end if;
17872 else
17873 Set_Has_First_Controlling_Parameter_Aspect (E);
17874 end if;
17875 end First_Ctrl_Param;
17877 -----------
17878 -- Ghost --
17879 -----------
17881 -- pragma Ghost [ (static_boolean_EXPRESSION) ];
17883 when Pragma_Ghost => Ghost : declare
17884 Context : Node_Id;
17885 Expr : Node_Id;
17886 Id : Entity_Id;
17887 Orig_Stmt : Node_Id;
17888 Prev_Id : Entity_Id;
17889 Stmt : Node_Id;
17891 begin
17892 GNAT_Pragma;
17893 Check_No_Identifiers;
17894 Check_At_Most_N_Arguments (1);
17896 Id := Empty;
17897 Stmt := Prev (N);
17898 while Present (Stmt) loop
17900 -- Skip prior pragmas, but check for duplicates
17902 if Nkind (Stmt) = N_Pragma then
17903 if Pragma_Name (Stmt) = Pname then
17904 Duplication_Error
17905 (Prag => N,
17906 Prev => Stmt);
17907 raise Pragma_Exit;
17908 end if;
17910 -- Task unit declared without a definition cannot be subject to
17911 -- pragma Ghost (SPARK RM 6.9(21)).
17913 elsif Nkind (Stmt) in
17914 N_Single_Task_Declaration | N_Task_Type_Declaration
17915 then
17916 Error_Pragma ("pragma % cannot apply to a task type");
17918 -- Skip internally generated code
17920 elsif not Comes_From_Source (Stmt) then
17921 Orig_Stmt := Original_Node (Stmt);
17923 -- When pragma Ghost applies to an untagged derivation, the
17924 -- derivation is transformed into a [sub]type declaration.
17926 if Nkind (Stmt) in
17927 N_Full_Type_Declaration | N_Subtype_Declaration
17928 and then Comes_From_Source (Orig_Stmt)
17929 and then Nkind (Orig_Stmt) = N_Full_Type_Declaration
17930 and then Nkind (Type_Definition (Orig_Stmt)) =
17931 N_Derived_Type_Definition
17932 then
17933 Id := Defining_Entity (Stmt);
17934 exit;
17936 -- When pragma Ghost applies to an object declaration which
17937 -- is initialized by means of a function call that returns
17938 -- on the secondary stack, the object declaration becomes a
17939 -- renaming.
17941 elsif Nkind (Stmt) = N_Object_Renaming_Declaration
17942 and then Comes_From_Source (Orig_Stmt)
17943 and then Nkind (Orig_Stmt) = N_Object_Declaration
17944 then
17945 Id := Defining_Entity (Stmt);
17946 exit;
17948 -- When pragma Ghost applies to an expression function, the
17949 -- expression function is transformed into a subprogram.
17951 elsif Nkind (Stmt) = N_Subprogram_Declaration
17952 and then Comes_From_Source (Orig_Stmt)
17953 and then Nkind (Orig_Stmt) = N_Expression_Function
17954 then
17955 Id := Defining_Entity (Stmt);
17956 exit;
17958 -- When pragma Ghost applies to a generic formal type, the
17959 -- type declaration in the instantiation is a generated
17960 -- subtype declaration.
17962 elsif Nkind (Stmt) = N_Subtype_Declaration
17963 and then Present (Generic_Parent_Type (Stmt))
17964 then
17965 Id := Defining_Entity (Stmt);
17966 exit;
17967 end if;
17969 -- The pragma applies to a legal construct, stop the traversal
17971 elsif Nkind (Stmt) in N_Abstract_Subprogram_Declaration
17972 | N_Formal_Object_Declaration
17973 | N_Formal_Subprogram_Declaration
17974 | N_Formal_Type_Declaration
17975 | N_Full_Type_Declaration
17976 | N_Generic_Subprogram_Declaration
17977 | N_Object_Declaration
17978 | N_Private_Extension_Declaration
17979 | N_Private_Type_Declaration
17980 | N_Subprogram_Declaration
17981 | N_Subtype_Declaration
17982 then
17983 Id := Defining_Entity (Stmt);
17984 exit;
17986 -- The pragma does not apply to a legal construct, issue an
17987 -- error and stop the analysis.
17989 else
17990 Error_Pragma
17991 ("pragma % must apply to an object, package, subprogram "
17992 & "or type");
17993 end if;
17995 Stmt := Prev (Stmt);
17996 end loop;
17998 Context := Parent (N);
18000 -- Handle compilation units
18002 if Nkind (Context) = N_Compilation_Unit_Aux then
18003 Context := Unit (Parent (Context));
18004 end if;
18006 -- Protected and task types cannot be subject to pragma Ghost
18007 -- (SPARK RM 6.9(21)).
18009 if Nkind (Context) in N_Protected_Body | N_Protected_Definition
18010 then
18011 Error_Pragma ("pragma % cannot apply to a protected type");
18013 elsif Nkind (Context) in N_Task_Body | N_Task_Definition then
18014 Error_Pragma ("pragma % cannot apply to a task type");
18015 end if;
18017 if No (Id) then
18019 -- When pragma Ghost is associated with a [generic] package, it
18020 -- appears in the visible declarations.
18022 if Nkind (Context) = N_Package_Specification
18023 and then Present (Visible_Declarations (Context))
18024 and then List_Containing (N) = Visible_Declarations (Context)
18025 then
18026 Id := Defining_Entity (Context);
18028 -- Pragma Ghost applies to a stand-alone subprogram body
18030 elsif Nkind (Context) = N_Subprogram_Body
18031 and then No (Corresponding_Spec (Context))
18032 then
18033 Id := Defining_Entity (Context);
18035 -- Pragma Ghost applies to a subprogram declaration that acts
18036 -- as a compilation unit.
18038 elsif Nkind (Context) = N_Subprogram_Declaration then
18039 Id := Defining_Entity (Context);
18041 -- Pragma Ghost applies to a generic subprogram
18043 elsif Nkind (Context) = N_Generic_Subprogram_Declaration then
18044 Id := Defining_Entity (Specification (Context));
18045 end if;
18046 end if;
18048 if No (Id) then
18049 Error_Pragma
18050 ("pragma % must apply to an object, package, subprogram or "
18051 & "type");
18052 end if;
18054 -- Handle completions of types and constants that are subject to
18055 -- pragma Ghost.
18057 if Is_Record_Type (Id) or else Ekind (Id) = E_Constant then
18058 Prev_Id := Incomplete_Or_Partial_View (Id);
18060 if Present (Prev_Id) and then not Is_Ghost_Entity (Prev_Id) then
18061 Error_Msg_Name_1 := Pname;
18063 -- The full declaration of a deferred constant cannot be
18064 -- subject to pragma Ghost unless the deferred declaration
18065 -- is also Ghost (SPARK RM 6.9(9)).
18067 if Ekind (Prev_Id) = E_Constant then
18068 Error_Msg_Name_1 := Pname;
18069 Error_Msg_NE (Fix_Error
18070 ("pragma % must apply to declaration of deferred "
18071 & "constant &"), N, Id);
18072 return;
18074 -- Pragma Ghost may appear on the full view of an incomplete
18075 -- type because the incomplete declaration lacks aspects and
18076 -- cannot be subject to pragma Ghost.
18078 elsif Ekind (Prev_Id) = E_Incomplete_Type then
18079 null;
18081 -- The full declaration of a type cannot be subject to
18082 -- pragma Ghost unless the partial view is also Ghost
18083 -- (SPARK RM 6.9(9)).
18085 else
18086 Error_Msg_NE (Fix_Error
18087 ("pragma % must apply to partial view of type &"),
18088 N, Id);
18089 return;
18090 end if;
18091 end if;
18093 -- A synchronized object cannot be subject to pragma Ghost
18094 -- (SPARK RM 6.9(21)).
18096 elsif Ekind (Id) = E_Variable then
18097 if Is_Protected_Type (Etype (Id)) then
18098 Error_Pragma ("pragma % cannot apply to a protected object");
18100 elsif Is_Task_Type (Etype (Id)) then
18101 Error_Pragma ("pragma % cannot apply to a task object");
18102 end if;
18103 end if;
18105 -- Analyze the Boolean expression (if any)
18107 if Present (Arg1) then
18108 Expr := Get_Pragma_Arg (Arg1);
18110 Analyze_And_Resolve (Expr, Standard_Boolean);
18112 if Is_OK_Static_Expression (Expr) then
18114 -- "Ghostness" cannot be turned off once enabled within a
18115 -- region (SPARK RM 6.9(6)).
18117 if Is_False (Expr_Value (Expr))
18118 and then Ghost_Mode > None
18119 then
18120 Error_Pragma
18121 ("pragma % with value False cannot appear in enabled "
18122 & "ghost region");
18123 end if;
18125 -- Otherwise the expression is not static
18127 else
18128 Error_Pragma_Arg
18129 ("expression of pragma % must be static", Expr);
18130 end if;
18131 end if;
18133 Set_Is_Ghost_Entity (Id);
18134 end Ghost;
18136 ------------
18137 -- Global --
18138 ------------
18140 -- pragma Global (GLOBAL_SPECIFICATION);
18142 -- GLOBAL_SPECIFICATION ::=
18143 -- null
18144 -- | (GLOBAL_LIST)
18145 -- | (MODED_GLOBAL_LIST {, MODED_GLOBAL_LIST})
18147 -- MODED_GLOBAL_LIST ::= MODE_SELECTOR => GLOBAL_LIST
18149 -- MODE_SELECTOR ::= In_Out | Input | Output | Proof_In
18150 -- GLOBAL_LIST ::= GLOBAL_ITEM | (GLOBAL_ITEM {, GLOBAL_ITEM})
18151 -- GLOBAL_ITEM ::= NAME
18153 -- Characteristics:
18155 -- * Analysis - The annotation undergoes initial checks to verify
18156 -- the legal placement and context. Secondary checks fully analyze
18157 -- the dependency clauses in:
18159 -- Analyze_Global_In_Decl_Part
18161 -- * Expansion - None.
18163 -- * Template - The annotation utilizes the generic template of the
18164 -- related subprogram [body] when it is:
18166 -- aspect on subprogram declaration
18167 -- aspect on stand-alone subprogram body
18168 -- pragma on stand-alone subprogram body
18170 -- The annotation must prepare its own template when it is:
18172 -- pragma on subprogram declaration
18174 -- * Globals - Capture of global references must occur after full
18175 -- analysis.
18177 -- * Instance - The annotation is instantiated automatically when
18178 -- the related generic subprogram [body] is instantiated except for
18179 -- the "pragma on subprogram declaration" case. In that scenario
18180 -- the annotation must instantiate itself.
18182 when Pragma_Global => Global : declare
18183 Legal : Boolean;
18184 Spec_Id : Entity_Id;
18185 Subp_Decl : Node_Id;
18187 begin
18188 Analyze_Depends_Global (Spec_Id, Subp_Decl, Legal);
18190 if Legal then
18192 -- Chain the pragma on the contract for further processing by
18193 -- Analyze_Global_In_Decl_Part.
18195 Add_Contract_Item (N, Spec_Id);
18197 -- Fully analyze the pragma when it appears inside an entry
18198 -- or subprogram body because it cannot benefit from forward
18199 -- references.
18201 if Nkind (Subp_Decl) in N_Entry_Body
18202 | N_Subprogram_Body
18203 | N_Subprogram_Body_Stub
18204 then
18205 -- The legality checks of pragmas Depends and Global are
18206 -- affected by the SPARK mode in effect and the volatility
18207 -- of the context. In addition these two pragmas are subject
18208 -- to an inherent order:
18210 -- 1) Global
18211 -- 2) Depends
18213 -- Analyze all these pragmas in the order outlined above
18215 Analyze_If_Present (Pragma_SPARK_Mode);
18216 Analyze_If_Present (Pragma_Volatile_Function);
18217 Analyze_If_Present (Pragma_Side_Effects);
18218 Analyze_Global_In_Decl_Part (N);
18219 Analyze_If_Present (Pragma_Depends);
18220 end if;
18221 end if;
18222 end Global;
18224 -----------
18225 -- Ident --
18226 -----------
18228 -- pragma Ident (static_string_EXPRESSION)
18230 -- Note: pragma Comment shares this processing. Pragma Ident is
18231 -- identical in effect to pragma Commment.
18233 when Pragma_Comment
18234 | Pragma_Ident
18236 Ident : declare
18237 Str : Node_Id;
18239 begin
18240 GNAT_Pragma;
18241 Check_Arg_Count (1);
18242 Check_No_Identifiers;
18243 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
18244 Store_Note (N);
18246 Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
18248 declare
18249 CS : Node_Id;
18250 GP : Node_Id;
18252 begin
18253 GP := Parent (Parent (N));
18255 if Nkind (GP) in
18256 N_Package_Declaration | N_Generic_Package_Declaration
18257 then
18258 GP := Parent (GP);
18259 end if;
18261 -- If we have a compilation unit, then record the ident value,
18262 -- checking for improper duplication.
18264 if Nkind (GP) = N_Compilation_Unit then
18265 CS := Ident_String (Current_Sem_Unit);
18267 if Present (CS) then
18269 -- If we have multiple instances, concatenate them.
18271 Start_String (Strval (CS));
18272 Store_String_Char (' ');
18273 Store_String_Chars (Strval (Str));
18274 Set_Strval (CS, End_String);
18276 else
18277 Set_Ident_String (Current_Sem_Unit, Str);
18278 end if;
18280 -- For subunits, we just ignore the Ident, since in GNAT these
18281 -- are not separate object files, and hence not separate units
18282 -- in the unit table.
18284 elsif Nkind (GP) = N_Subunit then
18285 null;
18286 end if;
18287 end;
18288 end Ident;
18290 -------------------
18291 -- Ignore_Pragma --
18292 -------------------
18294 -- pragma Ignore_Pragma (pragma_IDENTIFIER);
18296 -- Entirely handled in the parser, nothing to do here
18298 when Pragma_Ignore_Pragma =>
18299 null;
18301 ----------------------------
18302 -- Implementation_Defined --
18303 ----------------------------
18305 -- pragma Implementation_Defined (LOCAL_NAME);
18307 -- Marks previously declared entity as implementation defined. For
18308 -- an overloaded entity, applies to the most recent homonym.
18310 -- pragma Implementation_Defined;
18312 -- The form with no arguments appears anywhere within a scope, most
18313 -- typically a package spec, and indicates that all entities that are
18314 -- defined within the package spec are Implementation_Defined.
18316 when Pragma_Implementation_Defined => Implementation_Defined : declare
18317 Ent : Entity_Id;
18319 begin
18320 GNAT_Pragma;
18321 Check_No_Identifiers;
18323 -- Form with no arguments
18325 if Arg_Count = 0 then
18326 Set_Is_Implementation_Defined (Current_Scope);
18328 -- Form with one argument
18330 else
18331 Check_Arg_Count (1);
18332 Check_Arg_Is_Local_Name (Arg1);
18333 Ent := Entity (Get_Pragma_Arg (Arg1));
18334 Set_Is_Implementation_Defined (Ent);
18335 end if;
18336 end Implementation_Defined;
18338 -----------------
18339 -- Implemented --
18340 -----------------
18342 -- pragma Implemented (procedure_LOCAL_NAME, IMPLEMENTATION_KIND);
18344 -- IMPLEMENTATION_KIND ::=
18345 -- By_Entry | By_Protected_Procedure | By_Any | Optional
18347 -- "By_Any" and "Optional" are treated as synonyms in order to
18348 -- support Ada 2012 aspect Synchronization.
18350 when Pragma_Implemented => Implemented : declare
18351 Proc_Id : Entity_Id;
18352 Typ : Entity_Id;
18354 begin
18355 Ada_2012_Pragma;
18356 Check_Arg_Count (2);
18357 Check_No_Identifiers;
18358 Check_Arg_Is_Identifier (Arg1);
18359 Check_Arg_Is_Local_Name (Arg1);
18360 Check_Arg_Is_One_Of (Arg2,
18361 Name_By_Any,
18362 Name_By_Entry,
18363 Name_By_Protected_Procedure,
18364 Name_Optional);
18366 -- Extract the name of the local procedure
18368 Proc_Id := Entity (Get_Pragma_Arg (Arg1));
18370 -- Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
18371 -- primitive procedure of a synchronized tagged type.
18373 if Ekind (Proc_Id) = E_Procedure
18374 and then Is_Primitive (Proc_Id)
18375 and then Present (First_Formal (Proc_Id))
18376 then
18377 Typ := Etype (First_Formal (Proc_Id));
18379 if Is_Tagged_Type (Typ)
18380 and then
18382 -- Check for a protected, a synchronized or a task interface
18384 ((Is_Interface (Typ)
18385 and then Is_Synchronized_Interface (Typ))
18387 -- Check for a protected type or a task type that implements
18388 -- an interface.
18390 or else
18391 (Is_Concurrent_Record_Type (Typ)
18392 and then Present (Interfaces (Typ)))
18394 -- In analysis-only mode, examine original protected type
18396 or else
18397 (Nkind (Parent (Typ)) = N_Protected_Type_Declaration
18398 and then Present (Interface_List (Parent (Typ))))
18400 -- Check for a private record extension with keyword
18401 -- "synchronized".
18403 or else
18404 (Ekind (Typ) in E_Record_Type_With_Private
18405 | E_Record_Subtype_With_Private
18406 and then Synchronized_Present (Parent (Typ))))
18407 then
18408 null;
18409 else
18410 Error_Pragma_Arg
18411 ("controlling formal must be of synchronized tagged type",
18412 Arg1);
18413 end if;
18415 -- Ada 2012 (AI05-0030): Cannot apply the implementation_kind
18416 -- By_Protected_Procedure to the primitive procedure of a task
18417 -- interface.
18419 if Chars (Get_Pragma_Arg (Arg2)) = Name_By_Protected_Procedure
18420 and then Is_Interface (Typ)
18421 and then Is_Task_Interface (Typ)
18422 then
18423 Error_Pragma_Arg
18424 ("implementation kind By_Protected_Procedure cannot be "
18425 & "applied to a task interface primitive", Arg2);
18426 end if;
18428 -- Procedures declared inside a protected type must be accepted
18430 elsif Ekind (Proc_Id) = E_Procedure
18431 and then Is_Protected_Type (Scope (Proc_Id))
18432 then
18433 null;
18435 -- The first argument is not a primitive procedure
18437 else
18438 Error_Pragma_Arg
18439 ("pragma % must be applied to a primitive procedure", Arg1);
18440 end if;
18442 -- Ada 2012 (AI12-0279): Cannot apply the implementation_kind
18443 -- By_Protected_Procedure to a procedure that has aspect Yield
18445 if Chars (Get_Pragma_Arg (Arg2)) = Name_By_Protected_Procedure
18446 and then Has_Yield_Aspect (Proc_Id)
18447 then
18448 Error_Pragma_Arg
18449 ("implementation kind By_Protected_Procedure cannot be "
18450 & "applied to entities with aspect 'Yield", Arg2);
18451 end if;
18453 Record_Rep_Item (Proc_Id, N);
18454 end Implemented;
18456 ----------------------
18457 -- Implicit_Packing --
18458 ----------------------
18460 -- pragma Implicit_Packing;
18462 when Pragma_Implicit_Packing =>
18463 GNAT_Pragma;
18464 Check_Arg_Count (0);
18465 Implicit_Packing := True;
18467 ------------
18468 -- Import --
18469 ------------
18471 -- pragma Import (
18472 -- [Convention =>] convention_IDENTIFIER,
18473 -- [Entity =>] LOCAL_NAME
18474 -- [, [External_Name =>] static_string_EXPRESSION ]
18475 -- [, [Link_Name =>] static_string_EXPRESSION ]);
18477 when Pragma_Import =>
18478 Check_Ada_83_Warning;
18479 Check_Arg_Order
18480 ((Name_Convention,
18481 Name_Entity,
18482 Name_External_Name,
18483 Name_Link_Name));
18485 Check_At_Least_N_Arguments (2);
18486 Check_At_Most_N_Arguments (4);
18487 Process_Import_Or_Interface;
18489 ---------------------
18490 -- Import_Function --
18491 ---------------------
18493 -- pragma Import_Function (
18494 -- [Internal =>] LOCAL_NAME,
18495 -- [, [External =>] EXTERNAL_SYMBOL]
18496 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
18497 -- [, [Result_Type =>] SUBTYPE_MARK]
18498 -- [, [Mechanism =>] MECHANISM]
18499 -- [, [Result_Mechanism =>] MECHANISM_NAME]);
18501 -- EXTERNAL_SYMBOL ::=
18502 -- IDENTIFIER
18503 -- | static_string_EXPRESSION
18505 -- PARAMETER_TYPES ::=
18506 -- null
18507 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
18509 -- TYPE_DESIGNATOR ::=
18510 -- subtype_NAME
18511 -- | subtype_Name ' Access
18513 -- MECHANISM ::=
18514 -- MECHANISM_NAME
18515 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
18517 -- MECHANISM_ASSOCIATION ::=
18518 -- [formal_parameter_NAME =>] MECHANISM_NAME
18520 -- MECHANISM_NAME ::=
18521 -- Value
18522 -- | Reference
18524 when Pragma_Import_Function => Import_Function : declare
18525 Args : Args_List (1 .. 6);
18526 Names : constant Name_List (1 .. 6) := (
18527 Name_Internal,
18528 Name_External,
18529 Name_Parameter_Types,
18530 Name_Result_Type,
18531 Name_Mechanism,
18532 Name_Result_Mechanism);
18534 Internal : Node_Id renames Args (1);
18535 External : Node_Id renames Args (2);
18536 Parameter_Types : Node_Id renames Args (3);
18537 Result_Type : Node_Id renames Args (4);
18538 Mechanism : Node_Id renames Args (5);
18539 Result_Mechanism : Node_Id renames Args (6);
18541 begin
18542 GNAT_Pragma;
18543 Gather_Associations (Names, Args);
18544 Process_Extended_Import_Export_Subprogram_Pragma (
18545 Arg_Internal => Internal,
18546 Arg_External => External,
18547 Arg_Parameter_Types => Parameter_Types,
18548 Arg_Result_Type => Result_Type,
18549 Arg_Mechanism => Mechanism,
18550 Arg_Result_Mechanism => Result_Mechanism);
18551 end Import_Function;
18553 -------------------
18554 -- Import_Object --
18555 -------------------
18557 -- pragma Import_Object (
18558 -- [Internal =>] LOCAL_NAME
18559 -- [, [External =>] EXTERNAL_SYMBOL]
18560 -- [, [Size =>] EXTERNAL_SYMBOL]);
18562 -- EXTERNAL_SYMBOL ::=
18563 -- IDENTIFIER
18564 -- | static_string_EXPRESSION
18566 when Pragma_Import_Object => Import_Object : declare
18567 Args : Args_List (1 .. 3);
18568 Names : constant Name_List (1 .. 3) := (
18569 Name_Internal,
18570 Name_External,
18571 Name_Size);
18573 Internal : Node_Id renames Args (1);
18574 External : Node_Id renames Args (2);
18575 Size : Node_Id renames Args (3);
18577 begin
18578 GNAT_Pragma;
18579 Gather_Associations (Names, Args);
18580 Process_Extended_Import_Export_Object_Pragma (
18581 Arg_Internal => Internal,
18582 Arg_External => External,
18583 Arg_Size => Size);
18584 end Import_Object;
18586 ----------------------
18587 -- Import_Procedure --
18588 ----------------------
18590 -- pragma Import_Procedure (
18591 -- [Internal =>] LOCAL_NAME
18592 -- [, [External =>] EXTERNAL_SYMBOL]
18593 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
18594 -- [, [Mechanism =>] MECHANISM]);
18596 -- EXTERNAL_SYMBOL ::=
18597 -- IDENTIFIER
18598 -- | static_string_EXPRESSION
18600 -- PARAMETER_TYPES ::=
18601 -- null
18602 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
18604 -- TYPE_DESIGNATOR ::=
18605 -- subtype_NAME
18606 -- | subtype_Name ' Access
18608 -- MECHANISM ::=
18609 -- MECHANISM_NAME
18610 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
18612 -- MECHANISM_ASSOCIATION ::=
18613 -- [formal_parameter_NAME =>] MECHANISM_NAME
18615 -- MECHANISM_NAME ::=
18616 -- Value
18617 -- | Reference
18619 when Pragma_Import_Procedure => Import_Procedure : declare
18620 Args : Args_List (1 .. 4);
18621 Names : constant Name_List (1 .. 4) := (
18622 Name_Internal,
18623 Name_External,
18624 Name_Parameter_Types,
18625 Name_Mechanism);
18627 Internal : Node_Id renames Args (1);
18628 External : Node_Id renames Args (2);
18629 Parameter_Types : Node_Id renames Args (3);
18630 Mechanism : Node_Id renames Args (4);
18632 begin
18633 GNAT_Pragma;
18634 Gather_Associations (Names, Args);
18635 Process_Extended_Import_Export_Subprogram_Pragma (
18636 Arg_Internal => Internal,
18637 Arg_External => External,
18638 Arg_Parameter_Types => Parameter_Types,
18639 Arg_Mechanism => Mechanism);
18640 end Import_Procedure;
18642 -----------------------------
18643 -- Import_Valued_Procedure --
18644 -----------------------------
18646 -- pragma Import_Valued_Procedure (
18647 -- [Internal =>] LOCAL_NAME
18648 -- [, [External =>] EXTERNAL_SYMBOL]
18649 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
18650 -- [, [Mechanism =>] MECHANISM]);
18652 -- EXTERNAL_SYMBOL ::=
18653 -- IDENTIFIER
18654 -- | static_string_EXPRESSION
18656 -- PARAMETER_TYPES ::=
18657 -- null
18658 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
18660 -- TYPE_DESIGNATOR ::=
18661 -- subtype_NAME
18662 -- | subtype_Name ' Access
18664 -- MECHANISM ::=
18665 -- MECHANISM_NAME
18666 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
18668 -- MECHANISM_ASSOCIATION ::=
18669 -- [formal_parameter_NAME =>] MECHANISM_NAME
18671 -- MECHANISM_NAME ::=
18672 -- Value
18673 -- | Reference
18675 when Pragma_Import_Valued_Procedure =>
18676 Import_Valued_Procedure : declare
18677 Args : Args_List (1 .. 4);
18678 Names : constant Name_List (1 .. 4) := (
18679 Name_Internal,
18680 Name_External,
18681 Name_Parameter_Types,
18682 Name_Mechanism);
18684 Internal : Node_Id renames Args (1);
18685 External : Node_Id renames Args (2);
18686 Parameter_Types : Node_Id renames Args (3);
18687 Mechanism : Node_Id renames Args (4);
18689 begin
18690 GNAT_Pragma;
18691 Gather_Associations (Names, Args);
18692 Process_Extended_Import_Export_Subprogram_Pragma (
18693 Arg_Internal => Internal,
18694 Arg_External => External,
18695 Arg_Parameter_Types => Parameter_Types,
18696 Arg_Mechanism => Mechanism);
18697 end Import_Valued_Procedure;
18699 -----------------
18700 -- Independent --
18701 -----------------
18703 -- pragma Independent (LOCAL_NAME);
18705 when Pragma_Independent =>
18706 Process_Atomic_Independent_Shared_Volatile;
18708 ----------------------------
18709 -- Independent_Components --
18710 ----------------------------
18712 -- pragma Independent_Components (array_or_record_LOCAL_NAME);
18714 when Pragma_Independent_Components => Independent_Components : declare
18715 C : Node_Id;
18716 D : Node_Id;
18717 E_Id : Node_Id;
18718 E : Entity_Id;
18720 begin
18721 Check_Ada_83_Warning;
18722 Ada_2012_Pragma;
18723 Check_No_Identifiers;
18724 Check_Arg_Count (1);
18725 Check_Arg_Is_Local_Name (Arg1);
18726 E_Id := Get_Pragma_Arg (Arg1);
18728 if Etype (E_Id) = Any_Type then
18729 return;
18730 end if;
18732 E := Entity (E_Id);
18734 -- A record type with a self-referential component of anonymous
18735 -- access type is given an incomplete view in order to handle the
18736 -- self reference:
18738 -- type Rec is record
18739 -- Self : access Rec;
18740 -- end record;
18742 -- becomes
18744 -- type Rec;
18745 -- type Ptr is access Rec;
18746 -- type Rec is record
18747 -- Self : Ptr;
18748 -- end record;
18750 -- Since the incomplete view is now the initial view of the type,
18751 -- the argument of the pragma will reference the incomplete view,
18752 -- but this view is illegal according to the semantics of the
18753 -- pragma.
18755 -- Obtain the full view of an internally-generated incomplete type
18756 -- only. This way an attempt to associate the pragma with a source
18757 -- incomplete type is still caught.
18759 if Ekind (E) = E_Incomplete_Type
18760 and then not Comes_From_Source (E)
18761 and then Present (Full_View (E))
18762 then
18763 E := Full_View (E);
18764 end if;
18766 -- A pragma that applies to a Ghost entity becomes Ghost for the
18767 -- purposes of legality checks and removal of ignored Ghost code.
18769 Mark_Ghost_Pragma (N, E);
18771 -- Check duplicate before we chain ourselves
18773 Check_Duplicate_Pragma (E);
18775 -- Check appropriate entity
18777 if Rep_Item_Too_Early (E, N)
18778 or else
18779 Rep_Item_Too_Late (E, N)
18780 then
18781 return;
18782 end if;
18784 D := Declaration_Node (E);
18786 -- The flag is set on the base type, or on the object
18788 if Nkind (D) = N_Full_Type_Declaration
18789 and then (Is_Array_Type (E) or else Is_Record_Type (E))
18790 then
18791 Set_Has_Independent_Components (Base_Type (E));
18792 Record_Independence_Check (N, Base_Type (E));
18794 -- For record type, set all components independent
18796 if Is_Record_Type (E) then
18797 C := First_Component (E);
18798 while Present (C) loop
18799 Set_Is_Independent (C);
18800 Next_Component (C);
18801 end loop;
18802 end if;
18804 elsif (Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
18805 and then Nkind (D) = N_Object_Declaration
18806 and then Nkind (Object_Definition (D)) =
18807 N_Constrained_Array_Definition
18808 then
18809 Set_Has_Independent_Components (E);
18810 Record_Independence_Check (N, E);
18812 else
18813 Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
18814 end if;
18815 end Independent_Components;
18817 -----------------------
18818 -- Initial_Condition --
18819 -----------------------
18821 -- pragma Initial_Condition (boolean_EXPRESSION);
18823 -- Characteristics:
18825 -- * Analysis - The annotation undergoes initial checks to verify
18826 -- the legal placement and context. Secondary checks preanalyze the
18827 -- expression in:
18829 -- Analyze_Initial_Condition_In_Decl_Part
18831 -- * Expansion - The annotation is expanded during the expansion of
18832 -- the package body whose declaration is subject to the annotation
18833 -- as done in:
18835 -- Expand_Pragma_Initial_Condition
18837 -- * Template - The annotation utilizes the generic template of the
18838 -- related package declaration.
18840 -- * Globals - Capture of global references must occur after full
18841 -- analysis.
18843 -- * Instance - The annotation is instantiated automatically when
18844 -- the related generic package is instantiated.
18846 when Pragma_Initial_Condition => Initial_Condition : declare
18847 Pack_Decl : Node_Id;
18848 Pack_Id : Entity_Id;
18850 begin
18851 GNAT_Pragma;
18852 Check_No_Identifiers;
18853 Check_Arg_Count (1);
18855 Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
18857 if Nkind (Pack_Decl) not in
18858 N_Generic_Package_Declaration | N_Package_Declaration
18859 then
18860 Pragma_Misplaced;
18861 end if;
18863 Pack_Id := Defining_Entity (Pack_Decl);
18865 -- A pragma that applies to a Ghost entity becomes Ghost for the
18866 -- purposes of legality checks and removal of ignored Ghost code.
18868 Mark_Ghost_Pragma (N, Pack_Id);
18870 -- Chain the pragma on the contract for further processing by
18871 -- Analyze_Initial_Condition_In_Decl_Part.
18873 Add_Contract_Item (N, Pack_Id);
18875 -- The legality checks of pragmas Abstract_State, Initializes, and
18876 -- Initial_Condition are affected by the SPARK mode in effect. In
18877 -- addition, these three pragmas are subject to an inherent order:
18879 -- 1) Abstract_State
18880 -- 2) Initializes
18881 -- 3) Initial_Condition
18883 -- Analyze all these pragmas in the order outlined above
18885 Analyze_If_Present (Pragma_SPARK_Mode);
18886 Analyze_If_Present (Pragma_Abstract_State);
18887 Analyze_If_Present (Pragma_Initializes);
18888 end Initial_Condition;
18890 ------------------------
18891 -- Initialize_Scalars --
18892 ------------------------
18894 -- pragma Initialize_Scalars
18895 -- [ ( TYPE_VALUE_PAIR {, TYPE_VALUE_PAIR} ) ];
18897 -- TYPE_VALUE_PAIR ::=
18898 -- SCALAR_TYPE => static_EXPRESSION
18900 -- SCALAR_TYPE :=
18901 -- Short_Float
18902 -- | Float
18903 -- | Long_Float
18904 -- | Long_Long_Float
18905 -- | Signed_8
18906 -- | Signed_16
18907 -- | Signed_32
18908 -- | Signed_64
18909 -- | Signed_128
18910 -- | Unsigned_8
18911 -- | Unsigned_16
18912 -- | Unsigned_32
18913 -- | Unsigned_64
18914 -- | Unsigned_128
18916 when Pragma_Initialize_Scalars => Do_Initialize_Scalars : declare
18917 Seen : array (Scalar_Id) of Node_Id := (others => Empty);
18918 -- This collection holds the individual pairs which specify the
18919 -- invalid values of their respective scalar types.
18921 procedure Analyze_Float_Value
18922 (Scal_Typ : Float_Scalar_Id;
18923 Val_Expr : Node_Id);
18924 -- Analyze a type value pair associated with float type Scal_Typ
18925 -- and expression Val_Expr.
18927 procedure Analyze_Integer_Value
18928 (Scal_Typ : Integer_Scalar_Id;
18929 Val_Expr : Node_Id);
18930 -- Analyze a type value pair associated with integer type Scal_Typ
18931 -- and expression Val_Expr.
18933 procedure Analyze_Type_Value_Pair (Pair : Node_Id);
18934 -- Analyze type value pair Pair
18936 -------------------------
18937 -- Analyze_Float_Value --
18938 -------------------------
18940 procedure Analyze_Float_Value
18941 (Scal_Typ : Float_Scalar_Id;
18942 Val_Expr : Node_Id)
18944 begin
18945 Analyze_And_Resolve (Val_Expr, Any_Real);
18947 if Is_OK_Static_Expression (Val_Expr) then
18948 Set_Invalid_Scalar_Value (Scal_Typ, Expr_Value_R (Val_Expr));
18950 else
18951 Error_Msg_Name_1 := Scal_Typ;
18952 Error_Msg_N ("value for type % must be static", Val_Expr);
18953 end if;
18954 end Analyze_Float_Value;
18956 ---------------------------
18957 -- Analyze_Integer_Value --
18958 ---------------------------
18960 procedure Analyze_Integer_Value
18961 (Scal_Typ : Integer_Scalar_Id;
18962 Val_Expr : Node_Id)
18964 begin
18965 Analyze_And_Resolve (Val_Expr, Any_Integer);
18967 if (Scal_Typ = Name_Signed_128
18968 or else Scal_Typ = Name_Unsigned_128)
18969 and then Ttypes.System_Max_Integer_Size < 128
18970 then
18971 Error_Msg_Name_1 := Scal_Typ;
18972 Error_Msg_N ("value cannot be set for type %", Val_Expr);
18974 elsif Is_OK_Static_Expression (Val_Expr) then
18975 Set_Invalid_Scalar_Value (Scal_Typ, Expr_Value (Val_Expr));
18977 else
18978 Error_Msg_Name_1 := Scal_Typ;
18979 Error_Msg_N ("value for type % must be static", Val_Expr);
18980 end if;
18981 end Analyze_Integer_Value;
18983 -----------------------------
18984 -- Analyze_Type_Value_Pair --
18985 -----------------------------
18987 procedure Analyze_Type_Value_Pair (Pair : Node_Id) is
18988 Scal_Typ : constant Name_Id := Chars (Pair);
18989 Val_Expr : constant Node_Id := Expression (Pair);
18990 Prev_Pair : Node_Id;
18992 begin
18993 if Scal_Typ in Scalar_Id then
18994 Prev_Pair := Seen (Scal_Typ);
18996 -- Prevent multiple attempts to set a value for a scalar
18997 -- type.
18999 if Present (Prev_Pair) then
19000 Error_Msg_Name_1 := Scal_Typ;
19001 Error_Msg_N
19002 ("cannot specify multiple invalid values for type %",
19003 Pair);
19005 Error_Msg_Sloc := Sloc (Prev_Pair);
19006 Error_Msg_N ("previous value set #", Pair);
19008 -- Ignore the effects of the pair, but do not halt the
19009 -- analysis of the pragma altogether.
19011 return;
19013 -- Otherwise capture the first pair for this scalar type
19015 else
19016 Seen (Scal_Typ) := Pair;
19017 end if;
19019 if Scal_Typ in Float_Scalar_Id then
19020 Analyze_Float_Value (Scal_Typ, Val_Expr);
19022 else pragma Assert (Scal_Typ in Integer_Scalar_Id);
19023 Analyze_Integer_Value (Scal_Typ, Val_Expr);
19024 end if;
19026 -- Otherwise the scalar family is illegal
19028 else
19029 Error_Msg_Name_1 := Pname;
19030 Error_Msg_N
19031 ("argument of pragma % must denote valid scalar family",
19032 Pair);
19033 end if;
19034 end Analyze_Type_Value_Pair;
19036 -- Local variables
19038 Pairs : constant List_Id := Pragma_Argument_Associations (N);
19039 Pair : Node_Id;
19041 -- Start of processing for Do_Initialize_Scalars
19043 begin
19044 GNAT_Pragma;
19045 Check_Valid_Configuration_Pragma;
19046 Check_Restriction (No_Initialize_Scalars, N);
19048 -- Ignore the effects of the pragma when No_Initialize_Scalars is
19049 -- in effect.
19051 if Restriction_Active (No_Initialize_Scalars) then
19052 null;
19054 -- Initialize_Scalars creates false positives in CodePeer, and
19055 -- incorrect negative results in GNATprove mode, so ignore this
19056 -- pragma in these modes.
19058 elsif CodePeer_Mode or GNATprove_Mode then
19059 null;
19061 -- Otherwise analyze the pragma
19063 else
19064 if Present (Pairs) then
19066 -- Install Standard in order to provide access to primitive
19067 -- types in case the expressions contain attributes such as
19068 -- Integer'Last.
19070 Push_Scope (Standard_Standard);
19072 Pair := First (Pairs);
19073 while Present (Pair) loop
19074 Analyze_Type_Value_Pair (Pair);
19075 Next (Pair);
19076 end loop;
19078 -- Remove Standard
19080 Pop_Scope;
19081 end if;
19083 Init_Or_Norm_Scalars := True;
19084 Initialize_Scalars := True;
19085 end if;
19086 end Do_Initialize_Scalars;
19088 -----------------
19089 -- Initializes --
19090 -----------------
19092 -- pragma Initializes (INITIALIZATION_LIST);
19094 -- INITIALIZATION_LIST ::=
19095 -- null
19096 -- | (INITIALIZATION_ITEM {, INITIALIZATION_ITEM})
19098 -- INITIALIZATION_ITEM ::= name [=> INPUT_LIST]
19100 -- INPUT_LIST ::=
19101 -- null
19102 -- | INPUT
19103 -- | (INPUT {, INPUT})
19105 -- INPUT ::= name
19107 -- Characteristics:
19109 -- * Analysis - The annotation undergoes initial checks to verify
19110 -- the legal placement and context. Secondary checks preanalyze the
19111 -- expression in:
19113 -- Analyze_Initializes_In_Decl_Part
19115 -- * Expansion - None.
19117 -- * Template - The annotation utilizes the generic template of the
19118 -- related package declaration.
19120 -- * Globals - Capture of global references must occur after full
19121 -- analysis.
19123 -- * Instance - The annotation is instantiated automatically when
19124 -- the related generic package is instantiated.
19126 when Pragma_Initializes => Initializes : declare
19127 Pack_Decl : Node_Id;
19128 Pack_Id : Entity_Id;
19130 begin
19131 GNAT_Pragma;
19132 Check_No_Identifiers;
19133 Check_Arg_Count (1);
19135 Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
19137 if Nkind (Pack_Decl) not in
19138 N_Generic_Package_Declaration | N_Package_Declaration
19139 then
19140 Pragma_Misplaced;
19141 end if;
19143 Pack_Id := Defining_Entity (Pack_Decl);
19145 -- A pragma that applies to a Ghost entity becomes Ghost for the
19146 -- purposes of legality checks and removal of ignored Ghost code.
19148 Mark_Ghost_Pragma (N, Pack_Id);
19149 Ensure_Aggregate_Form (Get_Argument (N, Pack_Id));
19151 -- Chain the pragma on the contract for further processing by
19152 -- Analyze_Initializes_In_Decl_Part.
19154 Add_Contract_Item (N, Pack_Id);
19156 -- The legality checks of pragmas Abstract_State, Initializes, and
19157 -- Initial_Condition are affected by the SPARK mode in effect. In
19158 -- addition, these three pragmas are subject to an inherent order:
19160 -- 1) Abstract_State
19161 -- 2) Initializes
19162 -- 3) Initial_Condition
19164 -- Analyze all these pragmas in the order outlined above
19166 Analyze_If_Present (Pragma_SPARK_Mode);
19167 Analyze_If_Present (Pragma_Abstract_State);
19168 Analyze_If_Present (Pragma_Initial_Condition);
19169 end Initializes;
19171 ------------
19172 -- Inline --
19173 ------------
19175 -- pragma Inline ( NAME {, NAME} );
19177 when Pragma_Inline =>
19179 -- Pragma always active unless in GNATprove mode. It is disabled
19180 -- in GNATprove mode because frontend inlining is applied
19181 -- independently of pragmas Inline and Inline_Always for
19182 -- formal verification, see Can_Be_Inlined_In_GNATprove_Mode
19183 -- in inline.ads.
19185 if not GNATprove_Mode then
19187 -- Inline status is Enabled if option -gnatn is specified.
19188 -- However this status determines only the value of the
19189 -- Is_Inlined flag on the subprogram and does not prevent
19190 -- the pragma itself from being recorded for later use,
19191 -- in particular for a later modification of Is_Inlined
19192 -- independently of the -gnatn option.
19194 -- In other words, if -gnatn is specified for a unit, then
19195 -- all Inline pragmas processed for the compilation of this
19196 -- unit, including those in the spec of other units, are
19197 -- activated, so subprograms will be inlined across units.
19199 -- If -gnatn is not specified, no Inline pragma is activated
19200 -- here, which means that subprograms will not be inlined
19201 -- across units. The Is_Inlined flag will nevertheless be
19202 -- set later when bodies are analyzed, so subprograms will
19203 -- be inlined within the unit.
19205 if Inline_Active then
19206 Process_Inline (Enabled);
19207 else
19208 Process_Inline (Disabled);
19209 end if;
19210 end if;
19212 -------------------
19213 -- Inline_Always --
19214 -------------------
19216 -- pragma Inline_Always ( NAME {, NAME} );
19218 when Pragma_Inline_Always =>
19219 GNAT_Pragma;
19221 -- Pragma always active unless in CodePeer mode or GNATprove
19222 -- mode. It is disabled in CodePeer mode because inlining is
19223 -- not helpful, and enabling it caused walk order issues. It
19224 -- is disabled in GNATprove mode because frontend inlining is
19225 -- applied independently of pragmas Inline and Inline_Always for
19226 -- formal verification, see Can_Be_Inlined_In_GNATprove_Mode in
19227 -- inline.ads.
19229 if not CodePeer_Mode and not GNATprove_Mode then
19230 Process_Inline (Enabled);
19231 end if;
19233 --------------------
19234 -- Inline_Generic --
19235 --------------------
19237 -- pragma Inline_Generic (NAME {, NAME});
19239 when Pragma_Inline_Generic =>
19240 GNAT_Pragma;
19241 Process_Generic_List;
19243 ----------------------
19244 -- Inspection_Point --
19245 ----------------------
19247 -- pragma Inspection_Point [(object_NAME {, object_NAME})];
19249 when Pragma_Inspection_Point => Inspection_Point : declare
19250 Arg : Node_Id;
19251 Exp : Node_Id;
19253 begin
19256 if Arg_Count > 0 then
19257 Arg := Arg1;
19258 loop
19259 Exp := Get_Pragma_Arg (Arg);
19260 Analyze (Exp);
19262 if not Is_Entity_Name (Exp)
19263 or else not Is_Object (Entity (Exp))
19264 then
19265 Error_Pragma_Arg ("object name required", Arg);
19266 end if;
19268 Next (Arg);
19269 exit when No (Arg);
19270 end loop;
19271 end if;
19272 end Inspection_Point;
19274 ---------------
19275 -- Interface --
19276 ---------------
19278 -- pragma Interface (
19279 -- [ Convention =>] convention_IDENTIFIER,
19280 -- [ Entity =>] LOCAL_NAME
19281 -- [, [External_Name =>] static_string_EXPRESSION ]
19282 -- [, [Link_Name =>] static_string_EXPRESSION ]);
19284 when Pragma_Interface =>
19285 GNAT_Pragma;
19286 Check_Arg_Order
19287 ((Name_Convention,
19288 Name_Entity,
19289 Name_External_Name,
19290 Name_Link_Name));
19291 Check_At_Least_N_Arguments (2);
19292 Check_At_Most_N_Arguments (4);
19293 Process_Import_Or_Interface;
19295 -- In Ada 2005, the permission to use Interface (a reserved word)
19296 -- as a pragma name is considered an obsolescent feature, and this
19297 -- pragma was already obsolescent in Ada 95.
19299 if Ada_Version >= Ada_95 then
19300 Check_Restriction
19301 (No_Obsolescent_Features, Pragma_Identifier (N));
19303 if Warn_On_Obsolescent_Feature then
19304 Error_Msg_N
19305 ("pragma Interface is an obsolescent feature?j?", N);
19306 Error_Msg_N
19307 ("|use pragma Import instead?j?", N);
19308 end if;
19309 end if;
19311 --------------------
19312 -- Interface_Name --
19313 --------------------
19315 -- pragma Interface_Name (
19316 -- [ Entity =>] LOCAL_NAME
19317 -- [,[External_Name =>] static_string_EXPRESSION ]
19318 -- [,[Link_Name =>] static_string_EXPRESSION ]);
19320 when Pragma_Interface_Name => Interface_Name : declare
19321 Id : Node_Id;
19322 Def_Id : Entity_Id;
19323 Hom_Id : Entity_Id;
19324 Found : Boolean;
19326 begin
19327 GNAT_Pragma;
19328 Check_Arg_Order
19329 ((Name_Entity, Name_External_Name, Name_Link_Name));
19330 Check_At_Least_N_Arguments (2);
19331 Check_At_Most_N_Arguments (3);
19332 Id := Get_Pragma_Arg (Arg1);
19333 Analyze (Id);
19335 -- This is obsolete from Ada 95 on, but it is an implementation
19336 -- defined pragma, so we do not consider that it violates the
19337 -- restriction (No_Obsolescent_Features).
19339 if Ada_Version >= Ada_95 then
19340 if Warn_On_Obsolescent_Feature then
19341 Error_Msg_N
19342 ("pragma Interface_Name is an obsolescent feature?j?", N);
19343 Error_Msg_N
19344 ("|use pragma Import instead?j?", N);
19345 end if;
19346 end if;
19348 if not Is_Entity_Name (Id) then
19349 Error_Pragma_Arg
19350 ("first argument for pragma% must be entity name", Arg1);
19351 elsif Etype (Id) = Any_Type then
19352 return;
19353 else
19354 Def_Id := Entity (Id);
19355 end if;
19357 -- Special DEC-compatible processing for the object case, forces
19358 -- object to be imported.
19360 if Ekind (Def_Id) = E_Variable then
19361 Kill_Size_Check_Code (Def_Id);
19362 Note_Possible_Modification (Id, Sure => False);
19364 -- Initialization is not allowed for imported variable
19366 if Present (Expression (Parent (Def_Id)))
19367 and then Comes_From_Source (Expression (Parent (Def_Id)))
19368 then
19369 Error_Msg_Sloc := Sloc (Def_Id);
19370 Error_Pragma_Arg
19371 ("no initialization allowed for declaration of& #",
19372 Arg2);
19374 else
19375 -- For compatibility, support VADS usage of providing both
19376 -- pragmas Interface and Interface_Name to obtain the effect
19377 -- of a single Import pragma.
19379 if Is_Imported (Def_Id)
19380 and then Present (First_Rep_Item (Def_Id))
19381 and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
19382 and then Pragma_Name (First_Rep_Item (Def_Id)) =
19383 Name_Interface
19384 then
19385 null;
19386 else
19387 Set_Imported (Def_Id);
19388 end if;
19390 Set_Is_Public (Def_Id);
19391 Process_Interface_Name (Def_Id, Arg2, Arg3, N);
19392 end if;
19394 -- Otherwise must be subprogram
19396 elsif not Is_Subprogram (Def_Id) then
19397 Error_Pragma_Arg
19398 ("argument of pragma% is not subprogram", Arg1);
19400 else
19401 Check_At_Most_N_Arguments (3);
19402 Hom_Id := Def_Id;
19403 Found := False;
19405 -- Loop through homonyms
19407 loop
19408 Def_Id := Get_Base_Subprogram (Hom_Id);
19410 if Is_Imported (Def_Id) then
19411 Process_Interface_Name (Def_Id, Arg2, Arg3, N);
19412 Found := True;
19413 end if;
19415 exit when From_Aspect_Specification (N);
19416 Hom_Id := Homonym (Hom_Id);
19418 exit when No (Hom_Id)
19419 or else Scope (Hom_Id) /= Current_Scope;
19420 end loop;
19422 if not Found then
19423 Error_Pragma_Arg
19424 ("argument of pragma% is not imported subprogram",
19425 Arg1);
19426 end if;
19427 end if;
19428 end Interface_Name;
19430 -----------------------
19431 -- Interrupt_Handler --
19432 -----------------------
19434 -- pragma Interrupt_Handler (handler_NAME);
19436 when Pragma_Interrupt_Handler =>
19437 Check_Ada_83_Warning;
19438 Check_Arg_Count (1);
19439 Check_No_Identifiers;
19441 if No_Run_Time_Mode then
19442 Error_Msg_CRT ("Interrupt_Handler pragma", N);
19443 else
19444 Check_Interrupt_Or_Attach_Handler;
19445 Process_Interrupt_Or_Attach_Handler;
19446 end if;
19448 ------------------------
19449 -- Interrupt_Priority --
19450 ------------------------
19452 -- pragma Interrupt_Priority [(EXPRESSION)];
19454 when Pragma_Interrupt_Priority => Interrupt_Priority : declare
19455 P : constant Node_Id := Parent (N);
19456 Arg : Node_Id;
19457 Ent : Entity_Id;
19459 begin
19460 Check_Ada_83_Warning;
19462 if Arg_Count /= 0 then
19463 Arg := Get_Pragma_Arg (Arg1);
19464 Check_Arg_Count (1);
19465 Check_No_Identifiers;
19467 -- The expression must be analyzed in the special manner
19468 -- described in "Handling of Default and Per-Object
19469 -- Expressions" in sem.ads.
19471 Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
19472 end if;
19474 if Nkind (P) not in N_Task_Definition | N_Protected_Definition then
19475 Pragma_Misplaced;
19477 else
19478 Ent := Defining_Identifier (Parent (P));
19480 -- Check duplicate pragma before we chain the pragma in the Rep
19481 -- Item chain of Ent.
19483 Check_Duplicate_Pragma (Ent);
19484 Record_Rep_Item (Ent, N);
19486 -- Check the No_Task_At_Interrupt_Priority restriction
19488 if Nkind (P) = N_Task_Definition then
19489 Check_Restriction (No_Task_At_Interrupt_Priority, N);
19490 end if;
19491 end if;
19492 end Interrupt_Priority;
19494 ---------------------
19495 -- Interrupt_State --
19496 ---------------------
19498 -- pragma Interrupt_State (
19499 -- [Name =>] INTERRUPT_ID,
19500 -- [State =>] INTERRUPT_STATE);
19502 -- INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
19503 -- INTERRUPT_STATE => System | Runtime | User
19505 -- Note: if the interrupt id is given as an identifier, then it must
19506 -- be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
19507 -- given as a static integer expression which must be in the range of
19508 -- Ada.Interrupts.Interrupt_ID.
19510 when Pragma_Interrupt_State => Interrupt_State : declare
19511 Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
19512 -- This is the entity Ada.Interrupts.Interrupt_ID;
19514 State_Type : Character;
19515 -- Set to 's'/'r'/'u' for System/Runtime/User
19517 IST_Num : Pos;
19518 -- Index to entry in Interrupt_States table
19520 Int_Val : Uint;
19521 -- Value of interrupt
19523 Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
19524 -- The first argument to the pragma
19526 Int_Ent : Entity_Id;
19527 -- Interrupt entity in Ada.Interrupts.Names
19529 begin
19530 GNAT_Pragma;
19531 Check_Arg_Order ((Name_Name, Name_State));
19532 Check_Arg_Count (2);
19534 Check_Optional_Identifier (Arg1, Name_Name);
19535 Check_Optional_Identifier (Arg2, Name_State);
19536 Check_Arg_Is_Identifier (Arg2);
19538 -- First argument is identifier
19540 if Nkind (Arg1X) = N_Identifier then
19542 -- Search list of names in Ada.Interrupts.Names
19544 Int_Ent := First_Entity (RTE (RE_Names));
19545 loop
19546 if No (Int_Ent) then
19547 Error_Pragma_Arg ("invalid interrupt name", Arg1);
19549 elsif Chars (Int_Ent) = Chars (Arg1X) then
19550 Int_Val := Expr_Value (Constant_Value (Int_Ent));
19551 exit;
19552 end if;
19554 Next_Entity (Int_Ent);
19555 end loop;
19557 -- First argument is not an identifier, so it must be a static
19558 -- expression of type Ada.Interrupts.Interrupt_ID.
19560 else
19561 Check_Arg_Is_OK_Static_Expression (Arg1, Any_Integer);
19562 Int_Val := Expr_Value (Arg1X);
19564 if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
19565 or else
19566 Int_Val > Expr_Value (Type_High_Bound (Int_Id))
19567 then
19568 Error_Pragma_Arg
19569 ("value not in range of type "
19570 & """Ada.Interrupts.Interrupt_'I'D""", Arg1);
19571 end if;
19572 end if;
19574 -- Check OK state
19576 case Chars (Get_Pragma_Arg (Arg2)) is
19577 when Name_Runtime => State_Type := 'r';
19578 when Name_System => State_Type := 's';
19579 when Name_User => State_Type := 'u';
19581 when others =>
19582 Error_Pragma_Arg ("invalid interrupt state", Arg2);
19583 end case;
19585 -- Check if entry is already stored
19587 IST_Num := Interrupt_States.First;
19588 loop
19589 -- If entry not found, add it
19591 if IST_Num > Interrupt_States.Last then
19592 Interrupt_States.Append
19593 ((Interrupt_Number => UI_To_Int (Int_Val),
19594 Interrupt_State => State_Type,
19595 Pragma_Loc => Loc));
19596 exit;
19598 -- Case of entry for the same entry
19600 elsif Int_Val = Interrupt_States.Table (IST_Num).
19601 Interrupt_Number
19602 then
19603 -- If state matches, done, no need to make redundant entry
19605 exit when
19606 State_Type = Interrupt_States.Table (IST_Num).
19607 Interrupt_State;
19609 -- Otherwise if state does not match, error
19611 Error_Msg_Sloc :=
19612 Interrupt_States.Table (IST_Num).Pragma_Loc;
19613 Error_Pragma_Arg
19614 ("state conflicts with that given #", Arg2);
19615 end if;
19617 IST_Num := IST_Num + 1;
19618 end loop;
19619 end Interrupt_State;
19621 ---------------
19622 -- Invariant --
19623 ---------------
19625 -- pragma Invariant
19626 -- ([Entity =>] type_LOCAL_NAME,
19627 -- [Check =>] EXPRESSION
19628 -- [,[Message =>] String_Expression]);
19630 when Pragma_Invariant => Invariant : declare
19631 Discard : Boolean;
19632 Typ : Entity_Id;
19633 Typ_Arg : Node_Id;
19635 begin
19636 GNAT_Pragma;
19637 Check_At_Least_N_Arguments (2);
19638 Check_At_Most_N_Arguments (3);
19639 Check_Optional_Identifier (Arg1, Name_Entity);
19640 Check_Optional_Identifier (Arg2, Name_Check);
19642 if Arg_Count = 3 then
19643 Check_Optional_Identifier (Arg3, Name_Message);
19644 Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
19645 end if;
19647 Check_Arg_Is_Local_Name (Arg1);
19649 Typ_Arg := Get_Pragma_Arg (Arg1);
19650 Find_Type (Typ_Arg);
19651 Typ := Entity (Typ_Arg);
19653 -- Nothing to do of the related type is erroneous in some way
19655 if Typ = Any_Type then
19656 return;
19658 -- AI12-0041: Invariants are allowed in interface types
19660 elsif Is_Interface (Typ) then
19661 null;
19663 -- An invariant must apply to a private type, or appear in the
19664 -- private part of a package spec and apply to a completion.
19665 -- a class-wide invariant can only appear on a private declaration
19666 -- or private extension, not a completion.
19668 -- A [class-wide] invariant may be associated a [limited] private
19669 -- type or a private extension.
19671 elsif Ekind (Typ) in E_Limited_Private_Type
19672 | E_Private_Type
19673 | E_Record_Type_With_Private
19674 then
19675 null;
19677 -- A non-class-wide invariant may be associated with the full view
19678 -- of a [limited] private type or a private extension.
19680 elsif Has_Private_Declaration (Typ)
19681 and then not Class_Present (N)
19682 then
19683 null;
19685 -- A class-wide invariant may appear on the partial view only
19687 elsif Class_Present (N) then
19688 Error_Pragma_Arg
19689 ("pragma % only allowed for private type", Arg1);
19691 -- A regular invariant may appear on both views
19693 else
19694 Error_Pragma_Arg
19695 ("pragma % only allowed for private type or corresponding "
19696 & "full view", Arg1);
19697 end if;
19699 -- An invariant associated with an abstract type (this includes
19700 -- interfaces) must be class-wide.
19702 if Is_Abstract_Type (Typ) and then not Class_Present (N) then
19703 Error_Pragma_Arg
19704 ("pragma % not allowed for abstract type", Arg1);
19705 end if;
19707 -- A pragma that applies to a Ghost entity becomes Ghost for the
19708 -- purposes of legality checks and removal of ignored Ghost code.
19710 Mark_Ghost_Pragma (N, Typ);
19712 -- The pragma defines a type-specific invariant, the type is said
19713 -- to have invariants of its "own".
19715 Set_Has_Own_Invariants (Base_Type (Typ));
19717 -- If the invariant is class-wide, then it can be inherited by
19718 -- derived or interface implementing types. The type is said to
19719 -- have "inheritable" invariants.
19721 if Class_Present (N) then
19722 Set_Has_Inheritable_Invariants (Typ);
19723 end if;
19725 -- Chain the pragma on to the rep item chain, for processing when
19726 -- the type is frozen.
19728 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
19730 -- Create the declaration of the invariant procedure that will
19731 -- verify the invariant at run time. Interfaces are treated as the
19732 -- partial view of a private type in order to achieve uniformity
19733 -- with the general case. As a result, an interface receives only
19734 -- a "partial" invariant procedure, which is never called.
19736 Build_Invariant_Procedure_Declaration
19737 (Typ => Typ,
19738 Partial_Invariant => Is_Interface (Typ));
19739 end Invariant;
19741 ----------------
19742 -- Keep_Names --
19743 ----------------
19745 -- pragma Keep_Names ([On => ] LOCAL_NAME);
19747 when Pragma_Keep_Names => Keep_Names : declare
19748 Arg : Node_Id;
19750 begin
19751 GNAT_Pragma;
19752 Check_Arg_Count (1);
19753 Check_Optional_Identifier (Arg1, Name_On);
19754 Check_Arg_Is_Local_Name (Arg1);
19756 Arg := Get_Pragma_Arg (Arg1);
19757 Analyze (Arg);
19759 if Etype (Arg) = Any_Type then
19760 return;
19761 end if;
19763 if not Is_Entity_Name (Arg)
19764 or else Ekind (Entity (Arg)) /= E_Enumeration_Type
19765 then
19766 Error_Pragma_Arg
19767 ("pragma% requires a local enumeration type", Arg1);
19768 end if;
19770 Set_Discard_Names (Entity (Arg), False);
19771 end Keep_Names;
19773 -------------
19774 -- License --
19775 -------------
19777 -- pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
19779 when Pragma_License =>
19780 GNAT_Pragma;
19782 -- Do not analyze pragma any further in CodePeer mode, to avoid
19783 -- extraneous errors in this implementation-dependent pragma,
19784 -- which has a different profile on other compilers.
19786 if CodePeer_Mode then
19787 return;
19788 end if;
19790 Check_Arg_Count (1);
19791 Check_No_Identifiers;
19792 Check_Valid_Configuration_Pragma;
19793 Check_Arg_Is_Identifier (Arg1);
19795 declare
19796 Sind : constant Source_File_Index :=
19797 Source_Index (Current_Sem_Unit);
19799 begin
19800 case Chars (Get_Pragma_Arg (Arg1)) is
19801 when Name_GPL =>
19802 Set_License (Sind, GPL);
19804 when Name_Modified_GPL =>
19805 Set_License (Sind, Modified_GPL);
19807 when Name_Restricted =>
19808 Set_License (Sind, Restricted);
19810 when Name_Unrestricted =>
19811 Set_License (Sind, Unrestricted);
19813 when others =>
19814 Error_Pragma_Arg ("invalid license name", Arg1);
19815 end case;
19816 end;
19818 ---------------
19819 -- Link_With --
19820 ---------------
19822 -- pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
19824 when Pragma_Link_With => Link_With : declare
19825 Arg : Node_Id;
19827 begin
19828 GNAT_Pragma;
19830 if Operating_Mode = Generate_Code
19831 and then In_Extended_Main_Source_Unit (N)
19832 then
19833 Check_At_Least_N_Arguments (1);
19834 Check_No_Identifiers;
19835 Check_Is_In_Decl_Part_Or_Package_Spec;
19836 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
19837 Start_String;
19839 Arg := Arg1;
19840 while Present (Arg) loop
19841 Check_Arg_Is_OK_Static_Expression (Arg, Standard_String);
19843 -- Store argument, converting sequences of spaces to a
19844 -- single null character (this is one of the differences
19845 -- in processing between Link_With and Linker_Options).
19847 Arg_Store : declare
19848 C : constant Char_Code := Get_Char_Code (' ');
19849 S : constant String_Id :=
19850 Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
19851 L : constant Nat := String_Length (S);
19852 F : Nat := 1;
19854 procedure Skip_Spaces;
19855 -- Advance F past any spaces
19857 -----------------
19858 -- Skip_Spaces --
19859 -----------------
19861 procedure Skip_Spaces is
19862 begin
19863 while F <= L and then Get_String_Char (S, F) = C loop
19864 F := F + 1;
19865 end loop;
19866 end Skip_Spaces;
19868 -- Start of processing for Arg_Store
19870 begin
19871 Skip_Spaces; -- skip leading spaces
19873 -- Loop through characters, changing any embedded
19874 -- sequence of spaces to a single null character (this
19875 -- is how Link_With/Linker_Options differ)
19877 while F <= L loop
19878 if Get_String_Char (S, F) = C then
19879 Skip_Spaces;
19880 exit when F > L;
19881 Store_String_Char (ASCII.NUL);
19883 else
19884 Store_String_Char (Get_String_Char (S, F));
19885 F := F + 1;
19886 end if;
19887 end loop;
19888 end Arg_Store;
19890 Arg := Next (Arg);
19892 if Present (Arg) then
19893 Store_String_Char (ASCII.NUL);
19894 end if;
19895 end loop;
19897 Store_Linker_Option_String (End_String);
19898 end if;
19899 end Link_With;
19901 ------------------
19902 -- Linker_Alias --
19903 ------------------
19905 -- pragma Linker_Alias (
19906 -- [Entity =>] LOCAL_NAME
19907 -- [Target =>] static_string_EXPRESSION);
19909 when Pragma_Linker_Alias =>
19910 GNAT_Pragma;
19911 Check_Arg_Order ((Name_Entity, Name_Target));
19912 Check_Arg_Count (2);
19913 Check_Optional_Identifier (Arg1, Name_Entity);
19914 Check_Optional_Identifier (Arg2, Name_Target);
19915 Check_Arg_Is_Library_Level_Local_Name (Arg1);
19916 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
19918 -- The only processing required is to link this item on to the
19919 -- list of rep items for the given entity. This is accomplished
19920 -- by the call to Rep_Item_Too_Late (when no error is detected
19921 -- and False is returned).
19923 if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
19924 return;
19925 else
19926 Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
19927 end if;
19929 ------------------------
19930 -- Linker_Constructor --
19931 ------------------------
19933 -- pragma Linker_Constructor (procedure_LOCAL_NAME);
19935 -- Code is shared with Linker_Destructor
19937 -----------------------
19938 -- Linker_Destructor --
19939 -----------------------
19941 -- pragma Linker_Destructor (procedure_LOCAL_NAME);
19943 when Pragma_Linker_Constructor
19944 | Pragma_Linker_Destructor
19946 Linker_Constructor : declare
19947 Arg1_X : Node_Id;
19948 Proc : Entity_Id;
19950 begin
19951 GNAT_Pragma;
19952 Check_Arg_Count (1);
19953 Check_No_Identifiers;
19954 Check_Arg_Is_Local_Name (Arg1);
19955 Arg1_X := Get_Pragma_Arg (Arg1);
19956 Analyze (Arg1_X);
19957 Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
19959 if not Is_Library_Level_Entity (Proc) then
19960 Error_Pragma_Arg
19961 ("argument for pragma% must be library level entity", Arg1);
19962 end if;
19964 -- The only processing required is to link this item on to the
19965 -- list of rep items for the given entity. This is accomplished
19966 -- by the call to Rep_Item_Too_Late (when no error is detected
19967 -- and False is returned).
19969 if Rep_Item_Too_Late (Proc, N) then
19970 return;
19971 else
19972 Set_Has_Gigi_Rep_Item (Proc);
19973 end if;
19974 end Linker_Constructor;
19976 --------------------
19977 -- Linker_Options --
19978 --------------------
19980 -- pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
19982 when Pragma_Linker_Options => Linker_Options : declare
19983 Arg : Node_Id;
19985 begin
19986 Check_Ada_83_Warning;
19987 Check_No_Identifiers;
19988 Check_Arg_Count (1);
19989 Check_Is_In_Decl_Part_Or_Package_Spec;
19990 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
19991 Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
19993 Arg := Arg2;
19994 while Present (Arg) loop
19995 Check_Arg_Is_OK_Static_Expression (Arg, Standard_String);
19996 Store_String_Char (ASCII.NUL);
19997 Store_String_Chars
19998 (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
19999 Arg := Next (Arg);
20000 end loop;
20002 if Operating_Mode = Generate_Code
20003 and then In_Extended_Main_Source_Unit (N)
20004 then
20005 Store_Linker_Option_String (End_String);
20006 end if;
20007 end Linker_Options;
20009 --------------------
20010 -- Linker_Section --
20011 --------------------
20013 -- pragma Linker_Section (
20014 -- [Entity =>] LOCAL_NAME
20015 -- [Section =>] static_string_EXPRESSION);
20017 when Pragma_Linker_Section => Linker_Section : declare
20018 Arg : Node_Id;
20019 Ent : Entity_Id;
20020 LPE : Node_Id;
20022 Ghost_Error_Posted : Boolean := False;
20023 -- Flag set when an error concerning the illegal mix of Ghost and
20024 -- non-Ghost subprograms is emitted.
20026 Ghost_Id : Entity_Id := Empty;
20027 -- The entity of the first Ghost subprogram encountered while
20028 -- processing the arguments of the pragma.
20030 begin
20031 GNAT_Pragma;
20032 Check_Arg_Order ((Name_Entity, Name_Section));
20033 Check_Arg_Count (2);
20034 Check_Optional_Identifier (Arg1, Name_Entity);
20035 Check_Optional_Identifier (Arg2, Name_Section);
20036 Check_Arg_Is_Library_Level_Local_Name (Arg1);
20037 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
20039 -- Check kind of entity
20041 Arg := Get_Pragma_Arg (Arg1);
20042 Ent := Entity (Arg);
20044 case Ekind (Ent) is
20046 -- Objects (constants and variables) and types. For these cases
20047 -- all we need to do is to set the Linker_Section_pragma field,
20048 -- checking that we do not have a duplicate.
20050 when Type_Kind
20051 | E_Constant
20052 | E_Variable
20054 LPE := Linker_Section_Pragma (Ent);
20056 if Present (LPE) then
20057 Error_Msg_Sloc := Sloc (LPE);
20058 Error_Msg_NE
20059 ("Linker_Section already specified for &#", Arg1, Ent);
20060 end if;
20062 Set_Linker_Section_Pragma (Ent, N);
20064 -- A pragma that applies to a Ghost entity becomes Ghost for
20065 -- the purposes of legality checks and removal of ignored
20066 -- Ghost code.
20068 Mark_Ghost_Pragma (N, Ent);
20070 -- Subprograms
20072 when Subprogram_Kind =>
20074 -- Aspect case, entity already set
20076 if From_Aspect_Specification (N) then
20077 Set_Linker_Section_Pragma
20078 (Entity (Corresponding_Aspect (N)), N);
20080 -- Propagate it to its ultimate aliased entity to
20081 -- facilitate the backend processing this attribute
20082 -- in instantiations of generic subprograms.
20084 if Present (Alias (Entity (Corresponding_Aspect (N))))
20085 then
20086 Set_Linker_Section_Pragma
20087 (Ultimate_Alias
20088 (Entity (Corresponding_Aspect (N))), N);
20089 end if;
20091 -- Pragma case, we must climb the homonym chain, but skip
20092 -- any for which the linker section is already set.
20094 else
20095 loop
20096 if No (Linker_Section_Pragma (Ent)) then
20097 Set_Linker_Section_Pragma (Ent, N);
20099 -- Propagate it to its ultimate aliased entity to
20100 -- facilitate the backend processing this attribute
20101 -- in instantiations of generic subprograms.
20103 if Present (Alias (Ent)) then
20104 Set_Linker_Section_Pragma
20105 (Ultimate_Alias (Ent), N);
20106 end if;
20108 -- A pragma that applies to a Ghost entity becomes
20109 -- Ghost for the purposes of legality checks and
20110 -- removal of ignored Ghost code.
20112 Mark_Ghost_Pragma (N, Ent);
20114 -- Capture the entity of the first Ghost subprogram
20115 -- being processed for error detection purposes.
20117 if Is_Ghost_Entity (Ent) then
20118 if No (Ghost_Id) then
20119 Ghost_Id := Ent;
20120 end if;
20122 -- Otherwise the subprogram is non-Ghost. It is
20123 -- illegal to mix references to Ghost and non-Ghost
20124 -- entities (SPARK RM 6.9).
20126 elsif Present (Ghost_Id)
20127 and then not Ghost_Error_Posted
20128 then
20129 Ghost_Error_Posted := True;
20131 Error_Msg_Name_1 := Pname;
20132 Error_Msg_N
20133 ("pragma % cannot mention ghost and "
20134 & "non-ghost subprograms", N);
20136 Error_Msg_Sloc := Sloc (Ghost_Id);
20137 Error_Msg_NE
20138 ("\& # declared as ghost", N, Ghost_Id);
20140 Error_Msg_Sloc := Sloc (Ent);
20141 Error_Msg_NE
20142 ("\& # declared as non-ghost", N, Ent);
20143 end if;
20144 end if;
20146 Ent := Homonym (Ent);
20147 exit when No (Ent)
20148 or else Scope (Ent) /= Current_Scope;
20149 end loop;
20150 end if;
20152 -- All other cases are illegal
20154 when others =>
20155 Error_Pragma_Arg
20156 ("pragma% applies only to objects, subprograms, and types",
20157 Arg1);
20158 end case;
20159 end Linker_Section;
20161 ----------
20162 -- List --
20163 ----------
20165 -- pragma List (On | Off)
20167 -- There is nothing to do here, since we did all the processing for
20168 -- this pragma in Par.Prag (so that it works properly even in syntax
20169 -- only mode).
20171 when Pragma_List =>
20172 null;
20174 ---------------
20175 -- Lock_Free --
20176 ---------------
20178 -- pragma Lock_Free [(static_boolean_EXPRESSION)];
20180 when Pragma_Lock_Free => Lock_Free : declare
20181 P : constant Node_Id := Parent (N);
20182 Arg : Node_Id;
20183 Ent : Entity_Id;
20184 Val : Boolean;
20186 begin
20187 GNAT_Pragma;
20188 Check_No_Identifiers;
20189 Check_At_Most_N_Arguments (1);
20191 -- Protected definition case
20193 if Nkind (P) = N_Protected_Definition then
20194 Ent := Defining_Identifier (Parent (P));
20196 -- One argument
20198 if Arg_Count = 1 then
20199 Arg := Get_Pragma_Arg (Arg1);
20200 Val := Is_True (Static_Boolean (Arg));
20202 -- No arguments (expression is considered to be True)
20204 else
20205 Val := True;
20206 end if;
20208 -- Check duplicate pragma before we chain the pragma in the Rep
20209 -- Item chain of Ent.
20211 Check_Duplicate_Pragma (Ent);
20212 Record_Rep_Item (Ent, N);
20213 Set_Uses_Lock_Free (Ent, Val);
20215 -- Anything else is incorrect placement
20217 else
20218 Pragma_Misplaced;
20219 end if;
20220 end Lock_Free;
20222 --------------------
20223 -- Locking_Policy --
20224 --------------------
20226 -- pragma Locking_Policy (policy_IDENTIFIER);
20228 when Pragma_Locking_Policy => declare
20229 subtype LP_Range is Name_Id
20230 range First_Locking_Policy_Name .. Last_Locking_Policy_Name;
20231 LP_Val : LP_Range;
20232 LP : Character;
20234 begin
20235 Check_Ada_83_Warning;
20236 Check_Arg_Count (1);
20237 Check_No_Identifiers;
20238 Check_Arg_Is_Locking_Policy (Arg1);
20239 Check_Valid_Configuration_Pragma;
20240 LP_Val := Chars (Get_Pragma_Arg (Arg1));
20242 case LP_Val is
20243 when Name_Ceiling_Locking => LP := 'C';
20244 when Name_Concurrent_Readers_Locking => LP := 'R';
20245 when Name_Inheritance_Locking => LP := 'I';
20246 end case;
20248 if Locking_Policy /= ' '
20249 and then Locking_Policy /= LP
20250 then
20251 Error_Msg_Sloc := Locking_Policy_Sloc;
20252 Error_Pragma ("locking policy incompatible with policy#");
20254 -- Set new policy, but always preserve System_Location since we
20255 -- like the error message with the run time name.
20257 else
20258 Locking_Policy := LP;
20260 if Locking_Policy_Sloc /= System_Location then
20261 Locking_Policy_Sloc := Loc;
20262 end if;
20263 end if;
20264 end;
20266 -------------------
20267 -- Loop_Optimize --
20268 -------------------
20270 -- pragma Loop_Optimize ( OPTIMIZATION_HINT {, OPTIMIZATION_HINT } );
20272 -- OPTIMIZATION_HINT ::=
20273 -- Ivdep | No_Unroll | Unroll | No_Vector | Vector
20275 when Pragma_Loop_Optimize => Loop_Optimize : declare
20276 Hint : Node_Id;
20278 begin
20279 GNAT_Pragma;
20280 Check_At_Least_N_Arguments (1);
20281 Check_No_Identifiers;
20283 Hint := First (Pragma_Argument_Associations (N));
20284 while Present (Hint) loop
20285 Check_Arg_Is_One_Of (Hint, Name_Ivdep,
20286 Name_No_Unroll,
20287 Name_Unroll,
20288 Name_No_Vector,
20289 Name_Vector);
20290 Next (Hint);
20291 end loop;
20293 Check_Loop_Pragma_Placement;
20294 end Loop_Optimize;
20296 ------------------
20297 -- Loop_Variant --
20298 ------------------
20300 -- pragma Loop_Variant
20301 -- ( LOOP_VARIANT_ITEM {, LOOP_VARIANT_ITEM } );
20303 -- LOOP_VARIANT_ITEM ::= CHANGE_DIRECTION => discrete_EXPRESSION
20305 -- CHANGE_DIRECTION ::= Increases | Decreases
20307 when Pragma_Loop_Variant => Loop_Variant : declare
20308 Variant : Node_Id;
20310 begin
20311 GNAT_Pragma;
20312 Check_At_Least_N_Arguments (1);
20313 Check_Loop_Pragma_Placement;
20315 -- Process all increasing / decreasing expressions
20317 Variant := First (Pragma_Argument_Associations (N));
20318 while Present (Variant) loop
20319 if Chars (Variant) = No_Name then
20320 Error_Pragma_Arg_Ident ("expect name `Increases`", Variant);
20322 elsif Chars (Variant) not in
20323 Name_Decreases | Name_Increases | Name_Structural
20324 then
20325 declare
20326 Name : String := Get_Name_String (Chars (Variant));
20328 begin
20329 -- It is a common mistake to write "Increasing" for
20330 -- "Increases" or "Decreasing" for "Decreases". Recognize
20331 -- specially names starting with "incr" or "decr" to
20332 -- suggest the corresponding name.
20334 System.Case_Util.To_Lower (Name);
20336 if Name'Length >= 4
20337 and then Name (1 .. 4) = "incr"
20338 then
20339 Error_Pragma_Arg_Ident
20340 ("expect name `Increases`", Variant);
20342 elsif Name'Length >= 4
20343 and then Name (1 .. 4) = "decr"
20344 then
20345 Error_Pragma_Arg_Ident
20346 ("expect name `Decreases`", Variant);
20348 elsif Name'Length >= 4
20349 and then Name (1 .. 4) = "stru"
20350 then
20351 Error_Pragma_Arg_Ident
20352 ("expect name `Structural`", Variant);
20354 else
20355 Error_Pragma_Arg_Ident
20356 ("expect name `Increases`, `Decreases`,"
20357 & " or `Structural`", Variant);
20358 end if;
20359 end;
20361 elsif Chars (Variant) = Name_Structural
20362 and then List_Length (Pragma_Argument_Associations (N)) > 1
20363 then
20364 Error_Pragma_Arg_Ident
20365 ("Structural variant shall be the only variant", Variant);
20366 end if;
20368 -- Preanalyze_Assert_Expression, but without enforcing any of
20369 -- the two acceptable types.
20371 Preanalyze_Assert_Expression (Expression (Variant));
20373 -- Expression of a discrete type is allowed. Nothing to
20374 -- check for structural variants.
20376 if Chars (Variant) = Name_Structural
20377 or else Is_Discrete_Type (Etype (Expression (Variant)))
20378 then
20379 null;
20381 -- Expression of a Big_Integer type (or its ghost variant) is
20382 -- only allowed in Decreases clause.
20384 elsif
20385 Is_RTE (Base_Type (Etype (Expression (Variant))),
20386 RE_Big_Integer)
20387 or else
20388 Is_RTE (Base_Type (Etype (Expression (Variant))),
20389 RO_GH_Big_Integer)
20390 then
20391 if Chars (Variant) = Name_Increases then
20392 Error_Msg_N
20393 ("Loop_Variant with Big_Integer can only decrease",
20394 Expression (Variant));
20395 end if;
20397 -- Expression of other types is not allowed
20399 else
20400 Error_Msg_N
20401 ("expected a discrete or Big_Integer type",
20402 Expression (Variant));
20403 end if;
20405 Next (Variant);
20406 end loop;
20407 end Loop_Variant;
20409 -----------------------
20410 -- Machine_Attribute --
20411 -----------------------
20413 -- pragma Machine_Attribute (
20414 -- [Entity =>] LOCAL_NAME,
20415 -- [Attribute_Name =>] static_string_EXPRESSION
20416 -- [, [Info =>] static_EXPRESSION {, static_EXPRESSION}] );
20418 when Pragma_Machine_Attribute => Machine_Attribute : declare
20419 Arg : Node_Id;
20420 Def_Id : Entity_Id;
20422 begin
20423 GNAT_Pragma;
20424 Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
20426 if Arg_Count >= 3 then
20427 Check_Optional_Identifier (Arg3, Name_Info);
20428 Arg := Arg3;
20429 while Present (Arg) loop
20430 Check_Arg_Is_OK_Static_Expression (Arg);
20431 Arg := Next (Arg);
20432 end loop;
20433 else
20434 Check_Arg_Count (2);
20435 end if;
20437 Check_Optional_Identifier (Arg1, Name_Entity);
20438 Check_Optional_Identifier (Arg2, Name_Attribute_Name);
20439 Check_Arg_Is_Local_Name (Arg1);
20440 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
20441 Def_Id := Entity (Get_Pragma_Arg (Arg1));
20443 -- Apply the pragma to the designated type, rather than to the
20444 -- access type, unless it's a strub annotation. We wish to enable
20445 -- objects of access type, as well as access types themselves, to
20446 -- be annotated, so that reading the access objects (as oposed to
20447 -- the designated data) automatically enables stack
20448 -- scrubbing. That said, as in the attribute handler that
20449 -- processes the pragma turned into a compiler attribute, a strub
20450 -- annotation that must be associated with a subprogram type (for
20451 -- holding an explicit strub mode), when applied to an
20452 -- access-to-subprogram, gets promoted to the subprogram type. We
20453 -- might be tempted to leave it alone here, since the C attribute
20454 -- handler will adjust it, but then GNAT would convert the
20455 -- annotated subprogram types to naked ones before using them,
20456 -- cancelling out their intended effects.
20458 if Is_Access_Type (Def_Id)
20459 and then (not Strub_Pragma_P (N)
20460 or else
20461 (Present (Arg3)
20462 and then
20463 Ekind (Designated_Type
20464 (Def_Id)) = E_Subprogram_Type))
20465 then
20466 Def_Id := Designated_Type (Def_Id);
20467 end if;
20469 if Rep_Item_Too_Early (Def_Id, N) then
20470 return;
20471 end if;
20473 Def_Id := Underlying_Type (Def_Id);
20475 -- The only processing required is to link this item on to the
20476 -- list of rep items for the given entity. This is accomplished
20477 -- by the call to Rep_Item_Too_Late (when no error is detected
20478 -- and False is returned).
20480 if Rep_Item_Too_Late (Def_Id, N) then
20481 return;
20482 else
20483 Set_Has_Gigi_Rep_Item (Def_Id);
20484 end if;
20485 end Machine_Attribute;
20487 ----------
20488 -- Main --
20489 ----------
20491 -- pragma Main
20492 -- (MAIN_OPTION [, MAIN_OPTION]);
20494 -- MAIN_OPTION ::=
20495 -- [STACK_SIZE =>] static_integer_EXPRESSION
20496 -- | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
20497 -- | [TIME_SLICING_ENABLED =>] static_boolean_EXPRESSION
20499 when Pragma_Main => Main : declare
20500 Args : Args_List (1 .. 3);
20501 Names : constant Name_List (1 .. 3) := (
20502 Name_Stack_Size,
20503 Name_Task_Stack_Size_Default,
20504 Name_Time_Slicing_Enabled);
20506 Nod : Node_Id;
20508 begin
20509 GNAT_Pragma;
20510 Gather_Associations (Names, Args);
20512 for J in 1 .. 2 loop
20513 if Present (Args (J)) then
20514 Check_Arg_Is_OK_Static_Expression (Args (J), Any_Integer);
20515 end if;
20516 end loop;
20518 if Present (Args (3)) then
20519 Check_Arg_Is_OK_Static_Expression (Args (3), Standard_Boolean);
20520 end if;
20522 Nod := Next (N);
20523 while Present (Nod) loop
20524 if Nkind (Nod) = N_Pragma
20525 and then Pragma_Name (Nod) = Name_Main
20526 then
20527 Error_Msg_Name_1 := Pname;
20528 Error_Msg_N ("duplicate pragma% not permitted", Nod);
20529 end if;
20531 Next (Nod);
20532 end loop;
20533 end Main;
20535 ------------------
20536 -- Main_Storage --
20537 ------------------
20539 -- pragma Main_Storage
20540 -- (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
20542 -- MAIN_STORAGE_OPTION ::=
20543 -- [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
20544 -- | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
20546 when Pragma_Main_Storage => Main_Storage : declare
20547 Args : Args_List (1 .. 2);
20548 Names : constant Name_List (1 .. 2) := (
20549 Name_Working_Storage,
20550 Name_Top_Guard);
20552 Nod : Node_Id;
20554 begin
20555 GNAT_Pragma;
20556 Gather_Associations (Names, Args);
20558 for J in 1 .. 2 loop
20559 if Present (Args (J)) then
20560 Check_Arg_Is_OK_Static_Expression (Args (J), Any_Integer);
20561 end if;
20562 end loop;
20564 Check_In_Main_Program;
20566 Nod := Next (N);
20567 while Present (Nod) loop
20568 if Nkind (Nod) = N_Pragma
20569 and then Pragma_Name (Nod) = Name_Main_Storage
20570 then
20571 Error_Msg_Name_1 := Pname;
20572 Error_Msg_N ("duplicate pragma% not permitted", Nod);
20573 end if;
20575 Next (Nod);
20576 end loop;
20577 end Main_Storage;
20579 ----------------------------
20580 -- Max_Entry_Queue_Length --
20581 ----------------------------
20583 -- pragma Max_Entry_Queue_Length (static_integer_EXPRESSION);
20585 when Pragma_Max_Entry_Queue_Length
20586 | Pragma_Max_Queue_Length
20588 Max_Entry_Queue_Length : declare
20589 Arg : Node_Id;
20590 Entry_Decl : Node_Id;
20591 Entry_Id : Entity_Id;
20592 Val : Uint;
20594 begin
20595 if Prag_Id = Pragma_Max_Queue_Length then
20596 GNAT_Pragma;
20597 end if;
20599 Check_Arg_Count (1);
20601 Entry_Decl :=
20602 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
20604 -- Entry declaration
20606 if Nkind (Entry_Decl) = N_Entry_Declaration then
20608 -- Entry illegally within a task
20610 if Nkind (Parent (N)) = N_Task_Definition then
20611 Error_Pragma ("pragma % cannot apply to task entries");
20612 end if;
20614 Entry_Id := Defining_Entity (Entry_Decl);
20616 -- Otherwise the pragma is associated with an illegal construct
20618 else
20619 Error_Pragma
20620 ("pragma % must apply to a protected entry declaration");
20621 end if;
20623 -- Check for conflicting use of synonyms. Note that we exclude
20624 -- the detection of duplicates here because they are detected
20625 -- elsewhere.
20627 if (Has_Rep_Pragma (Entry_Id, Name_Max_Entry_Queue_Length)
20628 and then
20629 Prag_Id /= Pragma_Max_Entry_Queue_Length)
20630 or else
20631 (Has_Rep_Pragma (Entry_Id, Name_Max_Queue_Length)
20632 and then
20633 Prag_Id /= Pragma_Max_Queue_Length)
20634 then
20635 Error_Msg_N ("??maximum entry queue length already set", N);
20636 end if;
20638 -- Mark the pragma as Ghost if the related subprogram is also
20639 -- Ghost. This also ensures that any expansion performed further
20640 -- below will produce Ghost nodes.
20642 Mark_Ghost_Pragma (N, Entry_Id);
20644 -- Analyze the Integer expression
20646 Arg := Get_Pragma_Arg (Arg1);
20647 Check_Arg_Is_OK_Static_Expression (Arg, Any_Integer);
20649 Val := Expr_Value (Arg);
20651 if Val < -1 then
20652 Error_Pragma_Arg
20653 ("argument for pragma% cannot be less than -1", Arg1);
20655 elsif not UI_Is_In_Int_Range (Val) then
20656 Error_Pragma_Arg
20657 ("argument for pragma% out of range of Integer", Arg1);
20659 end if;
20661 Record_Rep_Item (Entry_Id, N);
20662 end Max_Entry_Queue_Length;
20664 -----------------
20665 -- Memory_Size --
20666 -----------------
20668 -- pragma Memory_Size (NUMERIC_LITERAL)
20670 when Pragma_Memory_Size =>
20671 GNAT_Pragma;
20673 -- Memory size is simply ignored
20675 Check_No_Identifiers;
20676 Check_Arg_Count (1);
20677 Check_Arg_Is_Integer_Literal (Arg1);
20679 -------------
20680 -- No_Body --
20681 -------------
20683 -- pragma No_Body;
20685 -- The only correct use of this pragma is on its own in a file, in
20686 -- which case it is specially processed (see Gnat1drv.Check_Bad_Body
20687 -- and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
20688 -- check for a file containing nothing but a No_Body pragma). If we
20689 -- attempt to process it during normal semantics processing, it means
20690 -- it was misplaced.
20692 when Pragma_No_Body =>
20693 GNAT_Pragma;
20694 Pragma_Misplaced;
20696 -----------------------------
20697 -- No_Elaboration_Code_All --
20698 -----------------------------
20700 -- pragma No_Elaboration_Code_All;
20702 when Pragma_No_Elaboration_Code_All =>
20703 GNAT_Pragma;
20704 Check_Valid_Library_Unit_Pragma;
20706 -- If N was rewritten as a null statement there is nothing more
20707 -- to do.
20709 if Nkind (N) = N_Null_Statement then
20710 return;
20711 end if;
20713 -- Must appear for a spec or generic spec
20715 if Nkind (Unit (Cunit (Current_Sem_Unit))) not in
20716 N_Generic_Package_Declaration |
20717 N_Generic_Subprogram_Declaration |
20718 N_Package_Declaration |
20719 N_Subprogram_Declaration
20720 then
20721 Error_Pragma
20722 (Fix_Error
20723 ("pragma% can only occur for package "
20724 & "or subprogram spec"));
20725 end if;
20727 -- Set flag in unit table
20729 Set_No_Elab_Code_All (Current_Sem_Unit);
20731 -- Set restriction No_Elaboration_Code if this is the main unit
20733 if Current_Sem_Unit = Main_Unit then
20734 Set_Restriction (No_Elaboration_Code, N);
20735 end if;
20737 -- If we are in the main unit or in an extended main source unit,
20738 -- then we also add it to the configuration restrictions so that
20739 -- it will apply to all units in the extended main source.
20741 if Current_Sem_Unit = Main_Unit
20742 or else In_Extended_Main_Source_Unit (N)
20743 then
20744 Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
20745 end if;
20747 -- If in main extended unit, activate transitive with test
20749 if In_Extended_Main_Source_Unit (N) then
20750 Opt.No_Elab_Code_All_Pragma := N;
20751 end if;
20753 -----------------------------
20754 -- No_Component_Reordering --
20755 -----------------------------
20757 -- pragma No_Component_Reordering [([Entity =>] type_LOCAL_NAME)];
20759 when Pragma_No_Component_Reordering => No_Comp_Reordering : declare
20760 E : Entity_Id;
20761 E_Id : Node_Id;
20763 begin
20764 GNAT_Pragma;
20765 Check_At_Most_N_Arguments (1);
20767 if Arg_Count = 0 then
20768 Check_Valid_Configuration_Pragma;
20769 Opt.No_Component_Reordering := True;
20771 else
20772 Check_Optional_Identifier (Arg2, Name_Entity);
20773 Check_Arg_Is_Local_Name (Arg1);
20774 E_Id := Get_Pragma_Arg (Arg1);
20776 if Etype (E_Id) = Any_Type then
20777 return;
20778 end if;
20780 E := Entity (E_Id);
20782 if not Is_Record_Type (E) then
20783 Error_Pragma_Arg ("pragma% requires record type", Arg1);
20784 end if;
20786 Set_No_Reordering (Base_Type (E));
20787 end if;
20788 end No_Comp_Reordering;
20790 --------------------------
20791 -- No_Heap_Finalization --
20792 --------------------------
20794 -- pragma No_Heap_Finalization [ (first_subtype_LOCAL_NAME) ];
20796 when Pragma_No_Heap_Finalization => No_Heap_Finalization : declare
20797 Context : constant Node_Id := Parent (N);
20798 Typ_Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
20799 Prev : Node_Id;
20800 Typ : Entity_Id;
20802 begin
20803 GNAT_Pragma;
20804 Check_No_Identifiers;
20806 -- The pragma appears in a configuration file
20808 if No (Context) then
20809 Check_Arg_Count (0);
20810 Check_Valid_Configuration_Pragma;
20812 -- Detect a duplicate pragma
20814 if Present (No_Heap_Finalization_Pragma) then
20815 Duplication_Error
20816 (Prag => N,
20817 Prev => No_Heap_Finalization_Pragma);
20818 raise Pragma_Exit;
20819 end if;
20821 No_Heap_Finalization_Pragma := N;
20823 -- Otherwise the pragma should be associated with a library-level
20824 -- named access-to-object type.
20826 else
20827 Check_Arg_Count (1);
20828 Check_Arg_Is_Local_Name (Arg1);
20830 Find_Type (Typ_Arg);
20831 Typ := Entity (Typ_Arg);
20833 -- The type being subjected to the pragma is erroneous
20835 if Typ = Any_Type then
20836 Error_Pragma ("cannot find type referenced by pragma %");
20838 -- The pragma is applied to an incomplete or generic formal
20839 -- type way too early.
20841 elsif Rep_Item_Too_Early (Typ, N) then
20842 return;
20844 else
20845 Typ := Underlying_Type (Typ);
20846 end if;
20848 -- The pragma must apply to an access-to-object type
20850 if Ekind (Typ) in E_Access_Type | E_General_Access_Type then
20851 null;
20853 -- Give a detailed error message on all other access type kinds
20855 elsif Ekind (Typ) = E_Access_Protected_Subprogram_Type then
20856 Error_Pragma
20857 ("pragma % cannot apply to access protected subprogram "
20858 & "type");
20860 elsif Ekind (Typ) = E_Access_Subprogram_Type then
20861 Error_Pragma
20862 ("pragma % cannot apply to access subprogram type");
20864 elsif Is_Anonymous_Access_Type (Typ) then
20865 Error_Pragma
20866 ("pragma % cannot apply to anonymous access type");
20868 -- Give a general error message in case the pragma applies to a
20869 -- non-access type.
20871 else
20872 Error_Pragma
20873 ("pragma % must apply to library level access type");
20874 end if;
20876 -- At this point the argument denotes an access-to-object type.
20877 -- Ensure that the type is declared at the library level.
20879 if Is_Library_Level_Entity (Typ) then
20880 null;
20882 -- Quietly ignore an access-to-object type originally declared
20883 -- at the library level within a generic, but instantiated at
20884 -- a non-library level. As a result the access-to-object type
20885 -- "loses" its No_Heap_Finalization property.
20887 elsif In_Instance then
20888 raise Pragma_Exit;
20890 else
20891 Error_Pragma
20892 ("pragma % must apply to library level access type");
20893 end if;
20895 -- Detect a duplicate pragma
20897 if Present (No_Heap_Finalization_Pragma) then
20898 Duplication_Error
20899 (Prag => N,
20900 Prev => No_Heap_Finalization_Pragma);
20901 raise Pragma_Exit;
20903 else
20904 Prev := Get_Pragma (Typ, Pragma_No_Heap_Finalization);
20906 if Present (Prev) then
20907 Duplication_Error
20908 (Prag => N,
20909 Prev => Prev);
20910 raise Pragma_Exit;
20911 end if;
20912 end if;
20914 Record_Rep_Item (Typ, N);
20915 end if;
20916 end No_Heap_Finalization;
20918 ---------------
20919 -- No_Inline --
20920 ---------------
20922 -- pragma No_Inline ( NAME {, NAME} );
20924 when Pragma_No_Inline =>
20925 GNAT_Pragma;
20926 Process_Inline (Suppressed);
20928 --------------
20929 -- No_Raise --
20930 --------------
20932 -- pragma No_Raise (procedure_LOCAL_NAME {, procedure_LOCAL_NAME});
20934 when Pragma_No_Raise => Prag_No_Raise : declare
20935 Arg : Node_Id;
20936 Assoc : Node_Id;
20937 Subp : Entity_Id;
20939 begin
20940 GNAT_Pragma;
20941 Check_No_Identifiers;
20942 Check_At_Least_N_Arguments (1);
20944 Assoc := Arg1;
20945 while Present (Assoc) loop
20946 Arg := Get_Pragma_Arg (Assoc);
20947 Analyze (Arg);
20949 if Is_Entity_Name (Arg) then
20950 Subp := Entity (Arg);
20952 -- If previous error, avoid cascaded errors
20954 if Subp = Any_Id then
20955 Check_Error_Detected;
20957 -- The argument must be a [generic] subprogram
20959 elsif not Is_Subprogram_Or_Generic_Subprogram (Subp) then
20960 Error_Pragma_Arg
20961 ("argument for pragma% must be a subprogram", Assoc);
20963 -- The argument must be in current scope
20965 elsif Scope (Subp) = Current_Scope then
20966 Check_Duplicate_Pragma (Subp);
20967 Record_Rep_Item (Subp, N);
20969 Set_No_Raise (Subp);
20971 -- For the pragma case, climb homonym chain. This is
20972 -- what implements allowing the pragma in the renaming
20973 -- case, with the result applying to the ancestors, and
20974 -- allows No_Raise to apply to all previous homonyms.
20976 if not From_Aspect_Specification (N) then
20977 while Present (Homonym (Subp))
20978 and then Scope (Homonym (Subp)) = Current_Scope
20979 loop
20980 Subp := Homonym (Subp);
20981 Set_No_Raise (Subp);
20982 end loop;
20983 end if;
20985 -- If entity in not in current scope it may be the enclosing
20986 -- subprogram body to which the aspect applies.
20988 elsif Subp = Current_Scope
20989 and then From_Aspect_Specification (N)
20990 then
20991 Set_No_Raise (Subp);
20993 else
20994 Error_Pragma_Arg
20995 ("expect local subprogram name for pragma%", Assoc);
20996 end if;
20997 end if;
20999 Next (Assoc);
21000 end loop;
21001 end Prag_No_Raise;
21003 ---------------
21004 -- No_Return --
21005 ---------------
21007 -- pragma No_Return (procedure_LOCAL_NAME {, procedure_LOCAL_NAME});
21009 when Pragma_No_Return => Prag_No_Return : declare
21011 function Check_No_Return
21012 (E : Entity_Id;
21013 N : Node_Id) return Boolean;
21014 -- Check rule 6.5.1(4/3) of the Ada RM. If the rule is violated,
21015 -- emit an error message and return False, otherwise return True.
21016 -- 6.5.1 Nonreturning procedures:
21017 -- 4/3 "Aspect No_Return shall not be specified for a null
21018 -- procedure nor an instance of a generic unit."
21020 ---------------------
21021 -- Check_No_Return --
21022 ---------------------
21024 function Check_No_Return
21025 (E : Entity_Id;
21026 N : Node_Id) return Boolean
21028 begin
21029 if Ekind (E) in E_Function | E_Generic_Function then
21030 Error_Msg_Ada_2022_Feature ("No_Return function", Sloc (N));
21031 return Ada_Version >= Ada_2022;
21033 elsif Ekind (E) = E_Procedure then
21035 -- If E is a generic instance, marking it with No_Return
21036 -- is forbidden, but having it inherit the No_Return of
21037 -- the generic is allowed. We check if E is inheriting its
21038 -- No_Return flag from the generic by checking if No_Return
21039 -- is already set.
21041 if Is_Generic_Instance (E) and then not No_Return (E) then
21042 Error_Msg_NE
21043 ("generic instance & is marked as No_Return", N, E);
21044 Error_Msg_NE
21045 ("\generic procedure & must be marked No_Return",
21047 Generic_Parent (Parent (E)));
21048 return False;
21050 elsif Null_Present (Subprogram_Specification (E)) then
21051 Error_Msg_NE
21052 ("null procedure & cannot be marked No_Return", N, E);
21053 return False;
21054 end if;
21055 end if;
21057 return True;
21058 end Check_No_Return;
21060 Arg : Node_Id;
21061 E : Entity_Id;
21062 Found : Boolean;
21063 Id : Node_Id;
21065 Ghost_Error_Posted : Boolean := False;
21066 -- Flag set when an error concerning the illegal mix of Ghost and
21067 -- non-Ghost subprograms is emitted.
21069 Ghost_Id : Entity_Id := Empty;
21070 -- The entity of the first Ghost procedure encountered while
21071 -- processing the arguments of the pragma.
21073 begin
21074 Ada_2005_Pragma;
21075 Check_At_Least_N_Arguments (1);
21077 -- Loop through arguments of pragma
21079 Arg := Arg1;
21080 while Present (Arg) loop
21081 Check_Arg_Is_Local_Name (Arg);
21082 Id := Get_Pragma_Arg (Arg);
21083 Analyze (Id);
21085 if not Is_Entity_Name (Id) then
21086 Error_Pragma_Arg ("entity name required", Arg);
21087 end if;
21089 if Etype (Id) = Any_Type then
21090 raise Pragma_Exit;
21091 end if;
21093 Found := False;
21094 -- Loop to find matching procedures or functions (Ada 2022)
21096 Outer_Loop :
21097 for Process_Functions in Boolean loop
21099 -- We make two passes over the Homonym list, first looking
21100 -- at procedures and then at functions. This is done
21101 -- in order to get the desired behavior in the pre-Ada2022
21102 -- case. There are two subcases of the pre-Ada2022 case -
21103 -- either we found a non-function candidate in the first
21104 -- pass or we didn't. If we found one, then exit early
21105 -- (i.e., skip the second pass); we want to silently ignore
21106 -- any functions. But if we didn't find one then we do not
21107 -- want to exit early because looking at functions will
21108 -- allow us (if we find one) to generate a more useful
21109 -- error message ("this is an Ada 2022 construct" instead of
21110 -- "name could not be resolved").
21112 exit Outer_Loop when Found and Ada_Version < Ada_2022;
21114 E := Entity (Id);
21116 while Present (E)
21117 and then Scope (E) = Current_Scope
21118 loop
21119 -- Ada 2022 (AI12-0269): A function can be No_Return
21121 if (if Process_Functions
21122 then Ekind (E) in E_Generic_Function | E_Function
21123 else Ekind (E) in E_Generic_Procedure | E_Procedure)
21125 -- if From_Aspect_Specification, then only one
21126 -- candidate should be considered.
21128 and then (not From_Aspect_Specification (N)
21129 or else E = Entity (Id)
21130 or else No (Entity (Id)))
21132 then
21133 -- Check that the pragma is not applied to a body.
21134 -- First check the specless body case, to give a
21135 -- different error message. These checks do not apply
21136 -- if Relaxed_RM_Semantics, to accommodate other Ada
21137 -- compilers. Disable these checks under -gnatd.J.
21139 if not Debug_Flag_Dot_JJ then
21140 if Nkind (Parent (Declaration_Node (E))) =
21141 N_Subprogram_Body
21142 and then not Relaxed_RM_Semantics
21143 then
21144 Error_Pragma
21145 ("pragma% requires separate spec and must "
21146 & "come before body");
21147 end if;
21149 -- Now the "specful" body case
21151 if Rep_Item_Too_Late (E, N) then
21152 raise Pragma_Exit;
21153 end if;
21154 end if;
21156 if Check_No_Return (E, N) then
21157 Set_No_Return (E);
21158 end if;
21160 -- A pragma that applies to a Ghost entity becomes
21161 -- Ghost for the purposes of legality checks and
21162 -- removal of ignored Ghost code.
21164 Mark_Ghost_Pragma (N, E);
21166 -- Capture the entity of the first Ghost procedure
21167 -- being processed for error detection purposes.
21169 if Is_Ghost_Entity (E) then
21170 if No (Ghost_Id) then
21171 Ghost_Id := E;
21172 end if;
21174 -- Otherwise the subprogram is non-Ghost. It is
21175 -- illegal to mix references to Ghost and non-Ghost
21176 -- entities (SPARK RM 6.9).
21178 elsif Present (Ghost_Id)
21179 and then not Ghost_Error_Posted
21180 then
21181 Ghost_Error_Posted := True;
21183 Error_Msg_Name_1 := Pname;
21184 Error_Msg_N
21185 ("pragma % cannot mention ghost and non-ghost "
21186 & "procedures", N);
21188 Error_Msg_Sloc := Sloc (Ghost_Id);
21189 Error_Msg_NE
21190 ("\& # declared as ghost", N, Ghost_Id);
21192 Error_Msg_Sloc := Sloc (E);
21193 Error_Msg_NE ("\& # declared as non-ghost", N, E);
21194 end if;
21196 -- Set flag on any alias as well
21198 if Is_Overloadable (E)
21199 and then Present (Alias (E))
21200 and then Check_No_Return (Alias (E), N)
21201 then
21202 Set_No_Return (Alias (E));
21203 end if;
21205 Found := True;
21206 end if;
21208 E := Homonym (E);
21209 end loop;
21210 end loop Outer_Loop;
21212 -- If entity in not in current scope it may be the enclosing
21213 -- subprogram body to which the aspect applies.
21215 if not Found then
21216 if Entity (Id) = Current_Scope
21217 and then From_Aspect_Specification (N)
21218 and then Check_No_Return (Entity (Id), N)
21219 then
21220 Set_No_Return (Entity (Id));
21222 elsif Ada_Version >= Ada_2022 then
21223 Error_Pragma_Arg
21224 ("no subprogram& found for pragma%", Arg);
21226 else
21227 Error_Pragma_Arg ("no procedure& found for pragma%", Arg);
21228 end if;
21229 end if;
21231 Next (Arg);
21232 end loop;
21233 end Prag_No_Return;
21235 -----------------
21236 -- No_Run_Time --
21237 -----------------
21239 -- pragma No_Run_Time;
21241 -- Note: this pragma is retained for backwards compatibility. See
21242 -- body of Rtsfind for full details on its handling.
21244 when Pragma_No_Run_Time =>
21245 GNAT_Pragma;
21246 Check_Valid_Configuration_Pragma;
21247 Check_Arg_Count (0);
21249 -- Remove backward compatibility if Build_Type is FSF or GPL and
21250 -- generate a warning.
21252 declare
21253 Ignore : constant Boolean := Build_Type in FSF .. GPL;
21254 begin
21255 if Ignore then
21256 Error_Pragma ("pragma% is ignored, has no effect??");
21257 else
21258 No_Run_Time_Mode := True;
21259 Configurable_Run_Time_Mode := True;
21261 -- Set Duration to 32 bits if word size is 32
21263 if Ttypes.System_Word_Size = 32 then
21264 Duration_32_Bits_On_Target := True;
21265 end if;
21267 -- Set appropriate restrictions
21269 Set_Restriction (No_Finalization, N);
21270 Set_Restriction (No_Exception_Handlers, N);
21271 Set_Restriction (Max_Tasks, N, 0);
21272 Set_Restriction (No_Tasking, N);
21273 end if;
21274 end;
21276 ----------------------------------
21277 -- Interrupts_System_By_Default --
21278 ----------------------------------
21280 -- pragma Interrupts_System_By_Default;
21282 when Pragma_Interrupts_System_By_Default =>
21283 GNAT_Pragma;
21284 Check_Arg_Count (0);
21285 Check_Valid_Configuration_Pragma;
21286 Interrupts_System_By_Default := True;
21288 -----------------------
21289 -- No_Tagged_Streams --
21290 -----------------------
21292 -- pragma No_Tagged_Streams [([Entity => ]tagged_type_local_NAME)];
21294 when Pragma_No_Tagged_Streams => No_Tagged_Strms : declare
21295 E : Entity_Id;
21296 E_Id : Node_Id;
21298 begin
21299 GNAT_Pragma;
21300 Check_At_Most_N_Arguments (1);
21302 -- One argument case
21304 if Arg_Count = 1 then
21305 Check_Optional_Identifier (Arg1, Name_Entity);
21306 Check_Arg_Is_Local_Name (Arg1);
21307 E_Id := Get_Pragma_Arg (Arg1);
21309 if Etype (E_Id) = Any_Type then
21310 return;
21311 end if;
21313 E := Entity (E_Id);
21315 Check_Duplicate_Pragma (E);
21317 if not Is_Tagged_Type (E) or else Is_Derived_Type (E) then
21318 Error_Pragma_Arg
21319 ("argument for pragma% must be root tagged type", Arg1);
21320 end if;
21322 if Rep_Item_Too_Early (E, N)
21323 or else
21324 Rep_Item_Too_Late (E, N)
21325 then
21326 return;
21327 else
21328 Set_No_Tagged_Streams_Pragma (E, N);
21329 end if;
21331 -- Zero argument case
21333 else
21334 Check_Is_In_Decl_Part_Or_Package_Spec;
21335 No_Tagged_Streams := N;
21336 end if;
21337 end No_Tagged_Strms;
21339 ------------------------
21340 -- No_Strict_Aliasing --
21341 ------------------------
21343 -- pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
21345 when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
21346 E : Entity_Id;
21347 E_Id : Node_Id;
21349 begin
21350 GNAT_Pragma;
21351 Check_At_Most_N_Arguments (1);
21353 if Arg_Count = 0 then
21354 Check_Valid_Configuration_Pragma;
21355 Opt.No_Strict_Aliasing := True;
21357 else
21358 Check_Optional_Identifier (Arg2, Name_Entity);
21359 Check_Arg_Is_Local_Name (Arg1);
21360 E_Id := Get_Pragma_Arg (Arg1);
21362 if Etype (E_Id) = Any_Type then
21363 return;
21364 end if;
21366 E := Entity (E_Id);
21368 if not Is_Access_Type (E) then
21369 Error_Pragma_Arg ("pragma% requires access type", Arg1);
21370 end if;
21372 Set_No_Strict_Aliasing (Base_Type (E));
21373 end if;
21374 end No_Strict_Aliasing;
21376 -----------------------
21377 -- Normalize_Scalars --
21378 -----------------------
21380 -- pragma Normalize_Scalars;
21382 when Pragma_Normalize_Scalars =>
21383 Check_Ada_83_Warning;
21384 Check_Arg_Count (0);
21385 Check_Valid_Configuration_Pragma;
21387 -- Normalize_Scalars creates false positives in CodePeer, and
21388 -- incorrect negative results in GNATprove mode, so ignore this
21389 -- pragma in these modes.
21391 if not (CodePeer_Mode or GNATprove_Mode) then
21392 Normalize_Scalars := True;
21393 Init_Or_Norm_Scalars := True;
21394 end if;
21396 -----------------
21397 -- Obsolescent --
21398 -----------------
21400 -- pragma Obsolescent;
21402 -- pragma Obsolescent (
21403 -- [Message =>] static_string_EXPRESSION
21404 -- [,[Version =>] Ada_05]);
21406 -- pragma Obsolescent (
21407 -- [Entity =>] NAME
21408 -- [,[Message =>] static_string_EXPRESSION
21409 -- [,[Version =>] Ada_05]]);
21411 when Pragma_Obsolescent => Obsolescent : declare
21412 Decl : Node_Id;
21413 Ename : Node_Id;
21415 procedure Set_Obsolescent (E : Entity_Id);
21416 -- Given an entity Ent, mark it as obsolescent if appropriate
21418 ---------------------
21419 -- Set_Obsolescent --
21420 ---------------------
21422 procedure Set_Obsolescent (E : Entity_Id) is
21423 Active : Boolean;
21424 Ent : Entity_Id;
21425 S : String_Id;
21427 begin
21428 Active := True;
21429 Ent := E;
21431 -- A pragma that applies to a Ghost entity becomes Ghost for
21432 -- the purposes of legality checks and removal of ignored Ghost
21433 -- code.
21435 Mark_Ghost_Pragma (N, E);
21437 -- Entity name was given
21439 if Present (Ename) then
21441 -- If entity name matches, we are fine.
21443 if Chars (Ename) = Chars (Ent) then
21444 Set_Entity (Ename, Ent);
21445 Generate_Reference (Ent, Ename);
21447 -- If entity name does not match, only possibility is an
21448 -- enumeration literal from an enumeration type declaration.
21450 elsif Ekind (Ent) /= E_Enumeration_Type then
21451 Error_Pragma
21452 ("pragma % entity name does not match declaration");
21454 else
21455 Ent := First_Literal (E);
21456 loop
21457 if No (Ent) then
21458 Error_Pragma
21459 ("pragma % entity name does not match any "
21460 & "enumeration literal");
21462 elsif Chars (Ent) = Chars (Ename) then
21463 Set_Entity (Ename, Ent);
21464 Generate_Reference (Ent, Ename);
21465 exit;
21467 else
21468 Next_Literal (Ent);
21469 end if;
21470 end loop;
21471 end if;
21472 end if;
21474 -- Ent points to entity to be marked
21476 if Arg_Count >= 1 then
21478 -- Deal with static string argument
21480 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
21481 S := Strval (Get_Pragma_Arg (Arg1));
21483 for J in 1 .. String_Length (S) loop
21484 if not In_Character_Range (Get_String_Char (S, J)) then
21485 Error_Pragma_Arg
21486 ("pragma% argument does not allow wide characters",
21487 Arg1);
21488 end if;
21489 end loop;
21491 Obsolescent_Warnings.Append
21492 ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
21494 -- Check for Ada_05 parameter
21496 if Arg_Count /= 1 then
21497 Check_Arg_Count (2);
21499 declare
21500 Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
21502 begin
21503 Check_Arg_Is_Identifier (Argx);
21505 if Chars (Argx) /= Name_Ada_05 then
21506 Error_Msg_Name_2 := Name_Ada_05;
21507 Error_Pragma_Arg
21508 ("only allowed argument for pragma% is %", Argx);
21509 end if;
21511 if Ada_Version_Explicit < Ada_2005
21512 or else not Warn_On_Ada_2005_Compatibility
21513 then
21514 Active := False;
21515 end if;
21516 end;
21517 end if;
21518 end if;
21520 -- Set flag if pragma active
21522 if Active then
21523 Set_Is_Obsolescent (Ent);
21524 end if;
21526 return;
21527 end Set_Obsolescent;
21529 -- Start of processing for pragma Obsolescent
21531 begin
21532 GNAT_Pragma;
21534 Check_At_Most_N_Arguments (3);
21536 -- See if first argument specifies an entity name
21538 if Arg_Count >= 1
21539 and then
21540 (Chars (Arg1) = Name_Entity
21541 or else
21542 Nkind (Get_Pragma_Arg (Arg1)) in
21543 N_Character_Literal | N_Identifier | N_Operator_Symbol)
21544 then
21545 Ename := Get_Pragma_Arg (Arg1);
21547 -- Eliminate first argument, so we can share processing
21549 Arg1 := Arg2;
21550 Arg2 := Arg3;
21551 Arg_Count := Arg_Count - 1;
21553 -- No Entity name argument given
21555 else
21556 Ename := Empty;
21557 end if;
21559 if Arg_Count >= 1 then
21560 Check_Optional_Identifier (Arg1, Name_Message);
21562 if Arg_Count = 2 then
21563 Check_Optional_Identifier (Arg2, Name_Version);
21564 end if;
21565 end if;
21567 -- Get immediately preceding declaration
21569 Decl := Prev (N);
21570 while Present (Decl) and then Nkind (Decl) = N_Pragma loop
21571 Prev (Decl);
21572 end loop;
21574 -- Cases where we do not follow anything other than another pragma
21576 if No (Decl) then
21578 -- Case 0: library level compilation unit declaration with
21579 -- the pragma preceding the declaration.
21581 if Nkind (Parent (N)) = N_Compilation_Unit then
21582 Pragma_Misplaced;
21584 -- Case 1: library level compilation unit declaration with
21585 -- the pragma immediately following the declaration.
21587 elsif Nkind (Parent (N)) = N_Compilation_Unit_Aux then
21588 Set_Obsolescent
21589 (Defining_Entity (Unit (Parent (Parent (N)))));
21590 return;
21592 -- Case 2: library unit placement for package
21594 else
21595 declare
21596 Ent : constant Entity_Id := Find_Lib_Unit_Name;
21597 begin
21598 if Is_Package_Or_Generic_Package (Ent) then
21599 Set_Obsolescent (Ent);
21600 return;
21601 end if;
21602 end;
21603 end if;
21605 -- Cases where we must follow a declaration, including an
21606 -- abstract subprogram declaration, which is not in the
21607 -- other node subtypes.
21609 else
21610 if Nkind (Decl) not in N_Declaration
21611 and then Nkind (Decl) not in N_Later_Decl_Item
21612 and then Nkind (Decl) not in N_Generic_Declaration
21613 and then Nkind (Decl) not in N_Renaming_Declaration
21614 and then Nkind (Decl) /= N_Abstract_Subprogram_Declaration
21615 then
21616 Error_Pragma
21617 ("pragma% misplaced, "
21618 & "must immediately follow a declaration");
21620 else
21621 Set_Obsolescent (Defining_Entity (Decl));
21622 return;
21623 end if;
21624 end if;
21625 end Obsolescent;
21627 --------------
21628 -- Optimize --
21629 --------------
21631 -- pragma Optimize (Time | Space | Off);
21633 -- The actual check for optimize is done in Gigi. Note that this
21634 -- pragma does not actually change the optimization setting, it
21635 -- simply checks that it is consistent with the pragma.
21637 when Pragma_Optimize =>
21638 Check_No_Identifiers;
21639 Check_Arg_Count (1);
21640 Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
21642 ------------------------
21643 -- Optimize_Alignment --
21644 ------------------------
21646 -- pragma Optimize_Alignment (Time | Space | Off);
21648 when Pragma_Optimize_Alignment => Optimize_Alignment : begin
21649 GNAT_Pragma;
21650 Check_No_Identifiers;
21651 Check_Arg_Count (1);
21652 Check_Valid_Configuration_Pragma;
21654 declare
21655 Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
21656 begin
21657 case Nam is
21658 when Name_Off => Opt.Optimize_Alignment := 'O';
21659 when Name_Space => Opt.Optimize_Alignment := 'S';
21660 when Name_Time => Opt.Optimize_Alignment := 'T';
21662 when others =>
21663 Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
21664 end case;
21665 end;
21667 -- Set indication that mode is set locally. If we are in fact in a
21668 -- configuration pragma file, this setting is harmless since the
21669 -- switch will get reset anyway at the start of each unit.
21671 Optimize_Alignment_Local := True;
21672 end Optimize_Alignment;
21674 -------------
21675 -- Ordered --
21676 -------------
21678 -- pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
21680 when Pragma_Ordered => Ordered : declare
21681 Assoc : constant Node_Id := Arg1;
21682 Type_Id : Node_Id;
21683 Typ : Entity_Id;
21685 begin
21686 GNAT_Pragma;
21687 Check_No_Identifiers;
21688 Check_Arg_Count (1);
21689 Check_Arg_Is_Local_Name (Arg1);
21691 Type_Id := Get_Pragma_Arg (Assoc);
21692 Find_Type (Type_Id);
21693 Typ := Entity (Type_Id);
21695 if Typ = Any_Type then
21696 return;
21697 else
21698 Typ := Underlying_Type (Typ);
21699 end if;
21701 if not Is_Enumeration_Type (Typ) then
21702 Error_Pragma ("pragma% must specify enumeration type");
21703 end if;
21705 Check_First_Subtype (Arg1);
21706 Set_Has_Pragma_Ordered (Base_Type (Typ));
21707 end Ordered;
21709 -------------------
21710 -- Overflow_Mode --
21711 -------------------
21713 -- pragma Overflow_Mode
21714 -- ([General => ] MODE [, [Assertions => ] MODE]);
21716 -- MODE := STRICT | MINIMIZED | ELIMINATED
21718 -- Note: ELIMINATED is allowed only if Long_Long_Integer'Size is 64
21719 -- since System.Bignums makes this assumption. This is true of nearly
21720 -- all (all?) targets.
21722 when Pragma_Overflow_Mode => Overflow_Mode : declare
21723 function Get_Overflow_Mode
21724 (Name : Name_Id;
21725 Arg : Node_Id) return Overflow_Mode_Type;
21726 -- Function to process one pragma argument, Arg. If an identifier
21727 -- is present, it must be Name. Mode type is returned if a valid
21728 -- argument exists, otherwise an error is signalled.
21730 -----------------------
21731 -- Get_Overflow_Mode --
21732 -----------------------
21734 function Get_Overflow_Mode
21735 (Name : Name_Id;
21736 Arg : Node_Id) return Overflow_Mode_Type
21738 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
21740 begin
21741 Check_Optional_Identifier (Arg, Name);
21742 Check_Arg_Is_Identifier (Argx);
21744 if Chars (Argx) = Name_Strict then
21745 return Strict;
21747 elsif Chars (Argx) = Name_Minimized then
21748 return Minimized;
21750 elsif Chars (Argx) = Name_Eliminated then
21751 if Ttypes.Standard_Long_Long_Integer_Size /= 64 then
21752 Error_Pragma_Arg
21753 ("Eliminated requires Long_Long_Integer'Size = 64",
21754 Argx);
21755 else
21756 return Eliminated;
21757 end if;
21759 else
21760 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
21761 end if;
21762 end Get_Overflow_Mode;
21764 -- Start of processing for Overflow_Mode
21766 begin
21767 GNAT_Pragma;
21768 Check_At_Least_N_Arguments (1);
21769 Check_At_Most_N_Arguments (2);
21771 -- Process first argument
21773 Scope_Suppress.Overflow_Mode_General :=
21774 Get_Overflow_Mode (Name_General, Arg1);
21776 -- Case of only one argument
21778 if Arg_Count = 1 then
21779 Scope_Suppress.Overflow_Mode_Assertions :=
21780 Scope_Suppress.Overflow_Mode_General;
21782 -- Case of two arguments present
21784 else
21785 Scope_Suppress.Overflow_Mode_Assertions :=
21786 Get_Overflow_Mode (Name_Assertions, Arg2);
21787 end if;
21788 end Overflow_Mode;
21790 --------------------------
21791 -- Overriding Renamings --
21792 --------------------------
21794 -- pragma Overriding_Renamings;
21796 when Pragma_Overriding_Renamings =>
21797 GNAT_Pragma;
21798 Check_Arg_Count (0);
21799 Check_Valid_Configuration_Pragma;
21800 Overriding_Renamings := True;
21802 ----------
21803 -- Pack --
21804 ----------
21806 -- pragma Pack (first_subtype_LOCAL_NAME);
21808 when Pragma_Pack => Pack : declare
21809 Assoc : constant Node_Id := Arg1;
21810 Ctyp : Entity_Id;
21811 Ignore : Boolean := False;
21812 Typ : Entity_Id;
21813 Type_Id : Node_Id;
21815 begin
21816 Check_No_Identifiers;
21817 Check_Arg_Count (1);
21818 Check_Arg_Is_Local_Name (Arg1);
21819 Type_Id := Get_Pragma_Arg (Assoc);
21821 if not Is_Entity_Name (Type_Id)
21822 or else not Is_Type (Entity (Type_Id))
21823 then
21824 Error_Pragma_Arg
21825 ("argument for pragma% must be type or subtype", Arg1);
21826 end if;
21828 Find_Type (Type_Id);
21829 Typ := Entity (Type_Id);
21831 if Typ = Any_Type
21832 or else Rep_Item_Too_Early (Typ, N)
21833 then
21834 return;
21835 else
21836 Typ := Underlying_Type (Typ);
21837 end if;
21839 -- A pragma that applies to a Ghost entity becomes Ghost for the
21840 -- purposes of legality checks and removal of ignored Ghost code.
21842 Mark_Ghost_Pragma (N, Typ);
21844 if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
21845 Error_Pragma ("pragma% must specify array or record type");
21846 end if;
21848 Check_First_Subtype (Arg1);
21849 Check_Duplicate_Pragma (Typ);
21851 -- Array type
21853 if Is_Array_Type (Typ) then
21854 Ctyp := Component_Type (Typ);
21856 -- Ignore pack that does nothing
21858 if Known_Static_Esize (Ctyp)
21859 and then Known_Static_RM_Size (Ctyp)
21860 and then Esize (Ctyp) = RM_Size (Ctyp)
21861 and then Addressable (Esize (Ctyp))
21862 then
21863 Ignore := True;
21864 end if;
21866 -- Process OK pragma Pack. Note that if there is a separate
21867 -- component clause present, the Pack will be cancelled. This
21868 -- processing is in Freeze.
21870 if not Rep_Item_Too_Late (Typ, N) then
21872 -- In CodePeer mode, we do not need complex front-end
21873 -- expansions related to pragma Pack, so disable handling
21874 -- of pragma Pack.
21876 if CodePeer_Mode then
21877 null;
21879 -- Normal case where we do the pack action
21881 else
21882 if not Ignore then
21883 Set_Is_Packed (Base_Type (Typ));
21884 Set_Has_Non_Standard_Rep (Base_Type (Typ));
21885 end if;
21887 Set_Has_Pragma_Pack (Base_Type (Typ));
21888 end if;
21889 end if;
21891 -- For record types, the pack is always effective
21893 else pragma Assert (Is_Record_Type (Typ));
21894 if not Rep_Item_Too_Late (Typ, N) then
21895 Set_Is_Packed (Base_Type (Typ));
21896 Set_Has_Pragma_Pack (Base_Type (Typ));
21897 Set_Has_Non_Standard_Rep (Base_Type (Typ));
21898 end if;
21899 end if;
21900 end Pack;
21902 ----------
21903 -- Page --
21904 ----------
21906 -- pragma Page;
21908 -- There is nothing to do here, since we did all the processing for
21909 -- this pragma in Par.Prag (so that it works properly even in syntax
21910 -- only mode).
21912 when Pragma_Page =>
21913 null;
21915 -------------
21916 -- Part_Of --
21917 -------------
21919 -- pragma Part_Of (ABSTRACT_STATE);
21921 -- ABSTRACT_STATE ::= NAME
21923 when Pragma_Part_Of => Part_Of : declare
21924 procedure Propagate_Part_Of
21925 (Pack_Id : Entity_Id;
21926 State_Id : Entity_Id;
21927 Instance : Node_Id);
21928 -- Propagate the Part_Of indicator to all abstract states and
21929 -- objects declared in the visible state space of a package
21930 -- denoted by Pack_Id. State_Id is the encapsulating state.
21931 -- Instance is the package instantiation node.
21933 -----------------------
21934 -- Propagate_Part_Of --
21935 -----------------------
21937 procedure Propagate_Part_Of
21938 (Pack_Id : Entity_Id;
21939 State_Id : Entity_Id;
21940 Instance : Node_Id)
21942 Has_Item : Boolean := False;
21943 -- Flag set when the visible state space contains at least one
21944 -- abstract state or variable.
21946 procedure Propagate_Part_Of (Pack_Id : Entity_Id);
21947 -- Propagate the Part_Of indicator to all abstract states and
21948 -- objects declared in the visible state space of a package
21949 -- denoted by Pack_Id.
21951 -----------------------
21952 -- Propagate_Part_Of --
21953 -----------------------
21955 procedure Propagate_Part_Of (Pack_Id : Entity_Id) is
21956 Constits : Elist_Id;
21957 Item_Id : Entity_Id;
21959 begin
21960 -- Traverse the entity chain of the package and set relevant
21961 -- attributes of abstract states and objects declared in the
21962 -- visible state space of the package.
21964 Item_Id := First_Entity (Pack_Id);
21965 while Present (Item_Id)
21966 and then not In_Private_Part (Item_Id)
21967 loop
21968 -- Do not consider internally generated items
21970 if not Comes_From_Source (Item_Id) then
21971 null;
21973 -- Do not consider generic formals or their corresponding
21974 -- actuals because they are not part of a visible state.
21975 -- Note that both entities are marked as hidden.
21977 elsif Is_Hidden (Item_Id) then
21978 null;
21980 -- The Part_Of indicator turns an abstract state or an
21981 -- object into a constituent of the encapsulating state.
21982 -- Note that constants are considered here even though
21983 -- they may not depend on variable input. This check is
21984 -- left to the SPARK prover.
21986 elsif Ekind (Item_Id) in
21987 E_Abstract_State | E_Constant | E_Variable
21988 then
21989 Has_Item := True;
21990 Constits := Part_Of_Constituents (State_Id);
21992 if No (Constits) then
21993 Constits := New_Elmt_List;
21994 Set_Part_Of_Constituents (State_Id, Constits);
21995 end if;
21997 Append_Elmt (Item_Id, Constits);
21998 Set_Encapsulating_State (Item_Id, State_Id);
22000 -- Recursively handle nested packages and instantiations
22002 elsif Ekind (Item_Id) = E_Package then
22003 Propagate_Part_Of (Item_Id);
22004 end if;
22006 Next_Entity (Item_Id);
22007 end loop;
22008 end Propagate_Part_Of;
22010 -- Start of processing for Propagate_Part_Of
22012 begin
22013 Propagate_Part_Of (Pack_Id);
22015 -- Detect a package instantiation that is subject to a Part_Of
22016 -- indicator, but has no visible state.
22018 if not Has_Item then
22019 SPARK_Msg_NE
22020 ("package instantiation & has Part_Of indicator but "
22021 & "lacks visible state", Instance, Pack_Id);
22022 end if;
22023 end Propagate_Part_Of;
22025 -- Local variables
22027 Constits : Elist_Id;
22028 Encap : Node_Id;
22029 Encap_Id : Entity_Id;
22030 Item_Id : Entity_Id;
22031 Legal : Boolean;
22032 Stmt : Node_Id;
22034 -- Start of processing for Part_Of
22036 begin
22037 GNAT_Pragma;
22038 Check_No_Identifiers;
22039 Check_Arg_Count (1);
22041 Stmt := Find_Related_Context (N, Do_Checks => True);
22043 -- Object declaration
22045 if Nkind (Stmt) = N_Object_Declaration then
22046 null;
22048 -- Package instantiation
22050 elsif Nkind (Stmt) = N_Package_Instantiation then
22051 null;
22053 -- Single concurrent type declaration
22055 elsif Is_Single_Concurrent_Type_Declaration (Stmt) then
22056 null;
22058 -- Otherwise the pragma is associated with an illegal construct
22060 else
22061 Pragma_Misplaced;
22062 end if;
22064 -- Extract the entity of the related object declaration or package
22065 -- instantiation. In the case of the instantiation, use the entity
22066 -- of the instance spec.
22068 if Nkind (Stmt) = N_Package_Instantiation then
22069 Stmt := Instance_Spec (Stmt);
22070 end if;
22072 Item_Id := Defining_Entity (Stmt);
22074 -- A pragma that applies to a Ghost entity becomes Ghost for the
22075 -- purposes of legality checks and removal of ignored Ghost code.
22077 Mark_Ghost_Pragma (N, Item_Id);
22079 -- Chain the pragma on the contract for further processing by
22080 -- Analyze_Part_Of_In_Decl_Part or for completeness.
22082 Add_Contract_Item (N, Item_Id);
22084 -- A variable may act as constituent of a single concurrent type
22085 -- which in turn could be declared after the variable. Due to this
22086 -- discrepancy, the full analysis of indicator Part_Of is delayed
22087 -- until the end of the enclosing declarative region (see routine
22088 -- Analyze_Part_Of_In_Decl_Part).
22090 if Ekind (Item_Id) = E_Variable then
22091 null;
22093 -- Otherwise indicator Part_Of applies to a constant or a package
22094 -- instantiation.
22096 else
22097 Encap := Get_Pragma_Arg (Arg1);
22099 -- Detect any discrepancies between the placement of the
22100 -- constant or package instantiation with respect to state
22101 -- space and the encapsulating state.
22103 Analyze_Part_Of
22104 (Indic => N,
22105 Item_Id => Item_Id,
22106 Encap => Encap,
22107 Encap_Id => Encap_Id,
22108 Legal => Legal);
22110 if Legal then
22111 pragma Assert (Present (Encap_Id));
22113 if Ekind (Item_Id) = E_Constant then
22114 Constits := Part_Of_Constituents (Encap_Id);
22116 if No (Constits) then
22117 Constits := New_Elmt_List;
22118 Set_Part_Of_Constituents (Encap_Id, Constits);
22119 end if;
22121 Append_Elmt (Item_Id, Constits);
22122 Set_Encapsulating_State (Item_Id, Encap_Id);
22124 -- Propagate the Part_Of indicator to the visible state
22125 -- space of the package instantiation.
22127 else
22128 Propagate_Part_Of
22129 (Pack_Id => Item_Id,
22130 State_Id => Encap_Id,
22131 Instance => Stmt);
22132 end if;
22133 end if;
22134 end if;
22135 end Part_Of;
22137 ----------------------------------
22138 -- Partition_Elaboration_Policy --
22139 ----------------------------------
22141 -- pragma Partition_Elaboration_Policy (policy_IDENTIFIER);
22143 when Pragma_Partition_Elaboration_Policy => PEP : declare
22144 subtype PEP_Range is Name_Id
22145 range First_Partition_Elaboration_Policy_Name
22146 .. Last_Partition_Elaboration_Policy_Name;
22147 PEP_Val : PEP_Range;
22148 PEP : Character;
22150 begin
22151 Ada_2005_Pragma;
22152 Check_Arg_Count (1);
22153 Check_No_Identifiers;
22154 Check_Arg_Is_Partition_Elaboration_Policy (Arg1);
22155 Check_Valid_Configuration_Pragma;
22156 PEP_Val := Chars (Get_Pragma_Arg (Arg1));
22158 case PEP_Val is
22159 when Name_Concurrent => PEP := 'C';
22160 when Name_Sequential => PEP := 'S';
22161 end case;
22163 if Partition_Elaboration_Policy /= ' '
22164 and then Partition_Elaboration_Policy /= PEP
22165 then
22166 Error_Msg_Sloc := Partition_Elaboration_Policy_Sloc;
22167 Error_Pragma
22168 ("partition elaboration policy incompatible with policy#");
22170 -- Set new policy, but always preserve System_Location since we
22171 -- like the error message with the run time name.
22173 else
22174 Partition_Elaboration_Policy := PEP;
22176 if Partition_Elaboration_Policy_Sloc /= System_Location then
22177 Partition_Elaboration_Policy_Sloc := Loc;
22178 end if;
22180 if PEP_Val = Name_Sequential
22181 and then not Restriction_Active (No_Task_Hierarchy)
22182 then
22183 -- RM H.6(6) guarantees that No_Task_Hierarchy will be
22184 -- set eventually, so take advantage of that knowledge now.
22185 -- But we have to do this in a tricky way. If we simply
22186 -- set the No_Task_Hierarchy restriction here, then the
22187 -- assumption that the restriction will be set eventually
22188 -- becomes a self-fulfilling prophecy; the binder can
22189 -- then mistakenly conclude that the H.6(6) rule is
22190 -- satisified in cases where the post-compilation check
22191 -- should fail. So we invent a new restriction,
22192 -- No_Task_Hierarchy_Implicit, which is treated specially
22193 -- in the function Restriction_Active.
22195 Set_Restriction (No_Task_Hierarchy_Implicit, N);
22196 pragma Assert (Restriction_Active (No_Task_Hierarchy));
22197 end if;
22198 end if;
22199 end PEP;
22201 -------------
22202 -- Passive --
22203 -------------
22205 -- pragma Passive [(PASSIVE_FORM)];
22207 -- PASSIVE_FORM ::= Semaphore | No
22209 when Pragma_Passive =>
22210 GNAT_Pragma;
22212 if Nkind (Parent (N)) /= N_Task_Definition then
22213 Error_Pragma ("pragma% must be within task definition");
22214 end if;
22216 if Arg_Count /= 0 then
22217 Check_Arg_Count (1);
22218 Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
22219 end if;
22221 --------------------
22222 -- Persistent_BSS --
22223 --------------------
22225 -- pragma Persistent_BSS [(object_LOCAL_NAME)];
22227 when Pragma_Persistent_BSS => Persistent_BSS : declare
22228 Decl : Node_Id;
22229 Ent : Entity_Id;
22230 Prag : Node_Id;
22232 begin
22233 GNAT_Pragma;
22234 Check_At_Most_N_Arguments (1);
22236 -- Case of application to specific object (one argument)
22238 if Arg_Count = 1 then
22239 Check_Arg_Is_Library_Level_Local_Name (Arg1);
22241 if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
22242 or else
22243 Ekind (Entity (Get_Pragma_Arg (Arg1))) not in
22244 E_Variable | E_Constant
22245 then
22246 Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
22247 end if;
22249 Ent := Entity (Get_Pragma_Arg (Arg1));
22251 -- A pragma that applies to a Ghost entity becomes Ghost for
22252 -- the purposes of legality checks and removal of ignored Ghost
22253 -- code.
22255 Mark_Ghost_Pragma (N, Ent);
22257 -- Check for duplication before inserting in list of
22258 -- representation items.
22260 Check_Duplicate_Pragma (Ent);
22262 if Rep_Item_Too_Late (Ent, N) then
22263 return;
22264 end if;
22266 Decl := Parent (Ent);
22268 if Present (Expression (Decl)) then
22269 -- Variables in Persistent_BSS cannot be initialized, so
22270 -- turn off any initialization that might be caused by
22271 -- pragmas Initialize_Scalars or Normalize_Scalars.
22273 if Kill_Range_Check (Expression (Decl)) then
22274 Prag :=
22275 Make_Pragma (Loc,
22276 Name_Suppress_Initialization,
22277 Pragma_Argument_Associations => New_List (
22278 Make_Pragma_Argument_Association (Loc,
22279 Expression => New_Occurrence_Of (Ent, Loc))));
22280 Insert_Before (N, Prag);
22281 Analyze (Prag);
22283 else
22284 Error_Pragma_Arg
22285 ("object for pragma% cannot have initialization", Arg1);
22286 end if;
22287 end if;
22289 if not Is_Potentially_Persistent_Type (Etype (Ent)) then
22290 Error_Pragma_Arg
22291 ("object type for pragma% is not potentially persistent",
22292 Arg1);
22293 end if;
22295 Prag :=
22296 Make_Linker_Section_Pragma
22297 (Ent, Loc, ".persistent.bss");
22298 Insert_After (N, Prag);
22299 Analyze (Prag);
22301 -- Case of use as configuration pragma with no arguments
22303 else
22304 Check_Valid_Configuration_Pragma;
22305 Persistent_BSS_Mode := True;
22306 end if;
22307 end Persistent_BSS;
22309 ----------------------------------
22310 -- Preelaborable_Initialization --
22311 ----------------------------------
22313 -- pragma Preelaborable_Initialization (DIRECT_NAME);
22315 when Pragma_Preelaborable_Initialization => Preelab_Init : declare
22316 Ent : Entity_Id;
22318 begin
22319 Ada_2005_Pragma;
22320 Check_Arg_Count (1);
22321 Check_No_Identifiers;
22322 Check_Arg_Is_Identifier (Arg1);
22323 Check_Arg_Is_Local_Name (Arg1);
22324 Check_First_Subtype (Arg1);
22325 Ent := Entity (Get_Pragma_Arg (Arg1));
22327 -- A pragma that applies to a Ghost entity becomes Ghost for the
22328 -- purposes of legality checks and removal of ignored Ghost code.
22330 Mark_Ghost_Pragma (N, Ent);
22332 -- The pragma may come from an aspect on a private declaration,
22333 -- even if the freeze point at which this is analyzed in the
22334 -- private part after the full view.
22336 if Has_Private_Declaration (Ent)
22337 and then From_Aspect_Specification (N)
22338 then
22339 null;
22341 -- Check appropriate type argument
22343 elsif Is_Private_Type (Ent)
22344 or else Is_Protected_Type (Ent)
22345 or else (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent))
22347 -- AI05-0028: The pragma applies to all composite types. Note
22348 -- that we apply this binding interpretation to earlier versions
22349 -- of Ada, so there is no Ada 2012 guard. Seems a reasonable
22350 -- choice since there are other compilers that do the same.
22352 or else Is_Composite_Type (Ent)
22353 then
22354 null;
22356 else
22357 Error_Pragma_Arg
22358 ("pragma % can only be applied to private, formal derived, "
22359 & "protected, or composite type", Arg1);
22360 end if;
22362 -- Give an error if the pragma is applied to a protected type that
22363 -- does not qualify (due to having entries, or due to components
22364 -- that do not qualify).
22366 if Is_Protected_Type (Ent)
22367 and then not Has_Preelaborable_Initialization (Ent)
22368 then
22369 Error_Msg_N
22370 ("protected type & does not have preelaborable "
22371 & "initialization", Ent);
22373 -- Otherwise mark the type as definitely having preelaborable
22374 -- initialization.
22376 else
22377 Set_Known_To_Have_Preelab_Init (Ent);
22378 end if;
22380 if Has_Pragma_Preelab_Init (Ent)
22381 and then Warn_On_Redundant_Constructs
22382 then
22383 Error_Pragma ("?r?duplicate pragma%!");
22384 else
22385 Set_Has_Pragma_Preelab_Init (Ent);
22386 end if;
22387 end Preelab_Init;
22389 --------------------
22390 -- Rename_Pragma --
22391 --------------------
22393 -- pragma Rename_Pragma (
22394 -- [New_Name =>] IDENTIFIER,
22395 -- [Renamed =>] pragma_IDENTIFIER);
22397 when Pragma_Rename_Pragma => Rename_Pragma : declare
22398 New_Name : constant Node_Id := Get_Pragma_Arg (Arg1);
22399 Old_Name : constant Node_Id := Get_Pragma_Arg (Arg2);
22401 begin
22402 GNAT_Pragma;
22403 Check_Valid_Configuration_Pragma;
22404 Check_Arg_Count (2);
22405 Check_Optional_Identifier (Arg1, Name_New_Name);
22406 Check_Optional_Identifier (Arg2, Name_Renamed);
22408 if Nkind (New_Name) /= N_Identifier then
22409 Error_Pragma_Arg ("identifier expected", Arg1);
22410 end if;
22412 if Nkind (Old_Name) /= N_Identifier then
22413 Error_Pragma_Arg ("identifier expected", Arg2);
22414 end if;
22416 -- The New_Name arg should not be an existing pragma (but we allow
22417 -- it; it's just a warning). The Old_Name arg must be an existing
22418 -- pragma.
22420 if Is_Pragma_Name (Chars (New_Name)) then
22421 Error_Pragma_Arg ("??pragma is already defined", Arg1);
22422 end if;
22424 if not Is_Pragma_Name (Chars (Old_Name)) then
22425 Error_Pragma_Arg ("existing pragma name expected", Arg1);
22426 end if;
22428 Map_Pragma_Name (From => Chars (New_Name), To => Chars (Old_Name));
22429 end Rename_Pragma;
22431 -----------------------------------
22432 -- Post/Post_Class/Postcondition --
22433 -----------------------------------
22435 -- pragma Post (Boolean_EXPRESSION);
22436 -- pragma Post_Class (Boolean_EXPRESSION);
22437 -- pragma Postcondition ([Check =>] Boolean_EXPRESSION
22438 -- [,[Message =>] String_EXPRESSION]);
22440 -- Characteristics:
22442 -- * Analysis - The annotation undergoes initial checks to verify
22443 -- the legal placement and context. Secondary checks preanalyze the
22444 -- expression in:
22446 -- Analyze_Pre_Post_Condition_In_Decl_Part
22448 -- * Expansion - The annotation is expanded during the expansion of
22449 -- the related subprogram [body] contract as performed in:
22451 -- Expand_Subprogram_Contract
22453 -- * Template - The annotation utilizes the generic template of the
22454 -- related subprogram [body] when it is:
22456 -- aspect on subprogram declaration
22457 -- aspect on stand-alone subprogram body
22458 -- pragma on stand-alone subprogram body
22460 -- The annotation must prepare its own template when it is:
22462 -- pragma on subprogram declaration
22464 -- * Globals - Capture of global references must occur after full
22465 -- analysis.
22467 -- * Instance - The annotation is instantiated automatically when
22468 -- the related generic subprogram [body] is instantiated except for
22469 -- the "pragma on subprogram declaration" case. In that scenario
22470 -- the annotation must instantiate itself.
22472 when Pragma_Post
22473 | Pragma_Post_Class
22474 | Pragma_Postcondition
22476 Analyze_Pre_Post_Condition;
22478 --------------------------------
22479 -- Pre/Pre_Class/Precondition --
22480 --------------------------------
22482 -- pragma Pre (Boolean_EXPRESSION);
22483 -- pragma Pre_Class (Boolean_EXPRESSION);
22484 -- pragma Precondition ([Check =>] Boolean_EXPRESSION
22485 -- [,[Message =>] String_EXPRESSION]);
22487 -- Characteristics:
22489 -- * Analysis - The annotation undergoes initial checks to verify
22490 -- the legal placement and context. Secondary checks preanalyze the
22491 -- expression in:
22493 -- Analyze_Pre_Post_Condition_In_Decl_Part
22495 -- * Expansion - The annotation is expanded during the expansion of
22496 -- the related subprogram [body] contract as performed in:
22498 -- Expand_Subprogram_Contract
22500 -- * Template - The annotation utilizes the generic template of the
22501 -- related subprogram [body] when it is:
22503 -- aspect on subprogram declaration
22504 -- aspect on stand-alone subprogram body
22505 -- pragma on stand-alone subprogram body
22507 -- The annotation must prepare its own template when it is:
22509 -- pragma on subprogram declaration
22511 -- * Globals - Capture of global references must occur after full
22512 -- analysis.
22514 -- * Instance - The annotation is instantiated automatically when
22515 -- the related generic subprogram [body] is instantiated except for
22516 -- the "pragma on subprogram declaration" case. In that scenario
22517 -- the annotation must instantiate itself.
22519 when Pragma_Pre
22520 | Pragma_Pre_Class
22521 | Pragma_Precondition
22523 Analyze_Pre_Post_Condition;
22525 ---------------
22526 -- Predicate --
22527 ---------------
22529 -- pragma Predicate
22530 -- ([Entity =>] type_LOCAL_NAME,
22531 -- [Check =>] boolean_EXPRESSION);
22533 when Pragma_Predicate => Predicate : declare
22534 Discard : Boolean;
22535 Typ : Entity_Id;
22536 Type_Id : Node_Id;
22538 begin
22539 GNAT_Pragma;
22540 Check_Arg_Count (2);
22541 Check_Optional_Identifier (Arg1, Name_Entity);
22542 Check_Optional_Identifier (Arg2, Name_Check);
22544 Check_Arg_Is_Local_Name (Arg1);
22546 Type_Id := Get_Pragma_Arg (Arg1);
22547 Find_Type (Type_Id);
22548 Typ := Entity (Type_Id);
22550 if Typ = Any_Type then
22551 return;
22552 end if;
22554 -- A Ghost_Predicate aspect is always Ghost with a mode inherited
22555 -- from the context. A Predicate pragma that applies to a Ghost
22556 -- entity becomes Ghost for the purposes of legality checks and
22557 -- removal of ignored Ghost code.
22559 if From_Aspect_Specification (N)
22560 and then Get_Aspect_Id
22561 (Chars (Identifier (Corresponding_Aspect (N))))
22562 = Aspect_Ghost_Predicate
22563 then
22564 Mark_Ghost_Pragma
22565 (N, Name_To_Ghost_Mode (Policy_In_Effect (Name_Ghost)));
22566 else
22567 Mark_Ghost_Pragma (N, Typ);
22568 end if;
22570 -- The remaining processing is simply to link the pragma on to
22571 -- the rep item chain, for processing when the type is frozen.
22572 -- This is accomplished by a call to Rep_Item_Too_Late. We also
22573 -- mark the type as having predicates.
22575 -- If the current policy for predicate checking is Ignore mark the
22576 -- subtype accordingly. In the case of predicates we consider them
22577 -- enabled unless Ignore is specified (either directly or with a
22578 -- general Assertion_Policy pragma) to preserve existing warnings.
22580 Set_Has_Predicates (Typ);
22582 -- Indicate that the pragma must be processed at the point the
22583 -- type is frozen, as is done for the corresponding aspect.
22585 Set_Has_Delayed_Aspects (Typ);
22586 Set_Has_Delayed_Freeze (Typ);
22588 -- Mark this aspect as ignored if the policy in effect is Ignore.
22590 -- It is not done for the internally built pragma created as part
22591 -- of processing aspect dynamic predicate because, in such case,
22592 -- this was done when the aspect was processed (see subprogram
22593 -- Analyze_One_Aspect).
22595 if From_Aspect_Specification (N)
22596 and then Pname = Name_Dynamic_Predicate
22597 then
22598 null;
22599 else
22600 Set_Predicates_Ignored (Typ,
22601 Policy_In_Effect (Name_Dynamic_Predicate) = Name_Ignore);
22602 end if;
22604 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
22605 end Predicate;
22607 -----------------------
22608 -- Predicate_Failure --
22609 -----------------------
22611 -- pragma Predicate_Failure
22612 -- ([Entity =>] type_LOCAL_NAME,
22613 -- [Message =>] string_EXPRESSION);
22615 when Pragma_Predicate_Failure => Predicate_Failure : declare
22616 Discard : Boolean;
22617 Typ : Entity_Id;
22618 Type_Id : Node_Id;
22620 begin
22621 GNAT_Pragma;
22622 Check_Arg_Count (2);
22623 Check_Optional_Identifier (Arg1, Name_Entity);
22624 Check_Optional_Identifier (Arg2, Name_Message);
22626 Check_Arg_Is_Local_Name (Arg1);
22628 Type_Id := Get_Pragma_Arg (Arg1);
22629 Find_Type (Type_Id);
22630 Typ := Entity (Type_Id);
22632 if Typ = Any_Type then
22633 return;
22634 end if;
22636 -- A pragma that applies to a Ghost entity becomes Ghost for the
22637 -- purposes of legality checks and removal of ignored Ghost code.
22639 Mark_Ghost_Pragma (N, Typ);
22641 -- The remaining processing is simply to link the pragma on to
22642 -- the rep item chain, for processing when the type is frozen.
22643 -- This is accomplished by a call to Rep_Item_Too_Late.
22645 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
22646 end Predicate_Failure;
22648 ------------------
22649 -- Preelaborate --
22650 ------------------
22652 -- pragma Preelaborate [(library_unit_NAME)];
22654 -- Set the flag Is_Preelaborated of program unit name entity
22656 when Pragma_Preelaborate => Preelaborate : declare
22657 Pa : constant Node_Id := Parent (N);
22658 Pk : constant Node_Kind := Nkind (Pa);
22659 Ent : Entity_Id;
22661 begin
22662 Check_Ada_83_Warning;
22663 Check_Valid_Library_Unit_Pragma;
22665 -- If N was rewritten as a null statement there is nothing more
22666 -- to do.
22668 if Nkind (N) = N_Null_Statement then
22669 return;
22670 end if;
22672 Ent := Find_Lib_Unit_Name;
22674 -- A pragma that applies to a Ghost entity becomes Ghost for the
22675 -- purposes of legality checks and removal of ignored Ghost code.
22677 Mark_Ghost_Pragma (N, Ent);
22678 Check_Duplicate_Pragma (Ent);
22680 -- This filters out pragmas inside generic parents that show up
22681 -- inside instantiations. Pragmas that come from aspects in the
22682 -- unit are not ignored.
22684 if Present (Ent) then
22685 if Pk = N_Package_Specification
22686 and then Present (Generic_Parent (Pa))
22687 and then not From_Aspect_Specification (N)
22688 then
22689 null;
22691 else
22692 if not Debug_Flag_U then
22693 Set_Is_Preelaborated (Ent);
22695 if Legacy_Elaboration_Checks then
22696 Set_Suppress_Elaboration_Warnings (Ent);
22697 end if;
22698 end if;
22699 end if;
22700 end if;
22701 end Preelaborate;
22703 -------------------------------
22704 -- Prefix_Exception_Messages --
22705 -------------------------------
22707 -- pragma Prefix_Exception_Messages;
22709 when Pragma_Prefix_Exception_Messages =>
22710 GNAT_Pragma;
22711 Check_Valid_Configuration_Pragma;
22712 Check_Arg_Count (0);
22713 Prefix_Exception_Messages := True;
22715 --------------
22716 -- Priority --
22717 --------------
22719 -- pragma Priority (EXPRESSION);
22721 when Pragma_Priority => Priority : declare
22722 P : constant Node_Id := Parent (N);
22723 Arg : Node_Id;
22724 Ent : Entity_Id;
22726 begin
22727 Check_No_Identifiers;
22728 Check_Arg_Count (1);
22730 -- Subprogram case
22732 if Nkind (P) = N_Subprogram_Body then
22733 Check_In_Main_Program;
22735 Ent := Defining_Unit_Name (Specification (P));
22737 if Nkind (Ent) = N_Defining_Program_Unit_Name then
22738 Ent := Defining_Identifier (Ent);
22739 end if;
22741 Arg := Get_Pragma_Arg (Arg1);
22742 Analyze_And_Resolve (Arg, Standard_Integer);
22744 -- Must be static
22746 if not Is_OK_Static_Expression (Arg) then
22747 Flag_Non_Static_Expr
22748 ("main subprogram priority is not static!", Arg);
22749 raise Pragma_Exit;
22751 -- If constraint error, then we already signalled an error
22753 elsif Raises_Constraint_Error (Arg) then
22754 null;
22756 -- Otherwise check in range except if Relaxed_RM_Semantics
22757 -- where we ignore the value if out of range.
22759 else
22760 if not Relaxed_RM_Semantics
22761 and then not Is_In_Range (Arg, RTE (RE_Priority))
22762 then
22763 Error_Pragma_Arg
22764 ("main subprogram priority is out of range", Arg1);
22765 else
22766 Set_Main_Priority
22767 (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
22768 end if;
22769 end if;
22771 -- Load an arbitrary entity from System.Tasking.Stages or
22772 -- System.Tasking.Restricted.Stages (depending on the
22773 -- supported profile) to make sure that one of these packages
22774 -- is implicitly with'ed, since we need to have the tasking
22775 -- run time active for the pragma Priority to have any effect.
22776 -- Previously we with'ed the package System.Tasking, but this
22777 -- package does not trigger the required initialization of the
22778 -- run-time library.
22780 if Restricted_Profile then
22781 Discard_Node (RTE (RE_Activate_Restricted_Tasks));
22782 else
22783 Discard_Node (RTE (RE_Activate_Tasks));
22784 end if;
22786 -- Task or Protected, must be of type Integer
22788 elsif Nkind (P) in N_Protected_Definition | N_Task_Definition then
22789 Arg := Get_Pragma_Arg (Arg1);
22790 Ent := Defining_Identifier (Parent (P));
22792 -- The expression must be analyzed in the special manner
22793 -- described in "Handling of Default and Per-Object
22794 -- Expressions" in sem.ads.
22796 Preanalyze_Spec_Expression (Arg, RTE (RE_Any_Priority));
22798 if not Is_OK_Static_Expression (Arg) then
22799 Check_Restriction (Static_Priorities, Arg);
22800 end if;
22802 -- Anything else is incorrect
22804 else
22805 Pragma_Misplaced;
22806 end if;
22808 -- Check duplicate pragma before we chain the pragma in the Rep
22809 -- Item chain of Ent.
22811 Check_Duplicate_Pragma (Ent);
22812 Record_Rep_Item (Ent, N);
22813 end Priority;
22815 -----------------------------------
22816 -- Priority_Specific_Dispatching --
22817 -----------------------------------
22819 -- pragma Priority_Specific_Dispatching (
22820 -- policy_IDENTIFIER,
22821 -- first_priority_EXPRESSION,
22822 -- last_priority_EXPRESSION);
22824 when Pragma_Priority_Specific_Dispatching =>
22825 Priority_Specific_Dispatching : declare
22826 Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
22827 -- This is the entity System.Any_Priority;
22829 DP : Character;
22830 Lower_Bound : Node_Id;
22831 Upper_Bound : Node_Id;
22832 Lower_Val : Uint;
22833 Upper_Val : Uint;
22835 begin
22836 Ada_2005_Pragma;
22837 Check_Arg_Count (3);
22838 Check_No_Identifiers;
22839 Check_Arg_Is_Task_Dispatching_Policy (Arg1);
22840 Check_Valid_Configuration_Pragma;
22841 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
22842 DP := Fold_Upper (Name_Buffer (1));
22844 Lower_Bound := Get_Pragma_Arg (Arg2);
22845 Check_Arg_Is_OK_Static_Expression (Lower_Bound, Standard_Integer);
22846 Lower_Val := Expr_Value (Lower_Bound);
22848 Upper_Bound := Get_Pragma_Arg (Arg3);
22849 Check_Arg_Is_OK_Static_Expression (Upper_Bound, Standard_Integer);
22850 Upper_Val := Expr_Value (Upper_Bound);
22852 -- It is not allowed to use Task_Dispatching_Policy and
22853 -- Priority_Specific_Dispatching in the same partition.
22855 if Task_Dispatching_Policy /= ' ' then
22856 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
22857 Error_Pragma
22858 ("pragma% incompatible with Task_Dispatching_Policy#");
22860 -- Check lower bound in range
22862 elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
22863 or else
22864 Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
22865 then
22866 Error_Pragma_Arg
22867 ("first_priority is out of range", Arg2);
22869 -- Check upper bound in range
22871 elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
22872 or else
22873 Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
22874 then
22875 Error_Pragma_Arg
22876 ("last_priority is out of range", Arg3);
22878 -- Check that the priority range is valid
22880 elsif Lower_Val > Upper_Val then
22881 Error_Pragma
22882 ("last_priority_expression must be greater than or equal to "
22883 & "first_priority_expression");
22885 -- Store the new policy, but always preserve System_Location since
22886 -- we like the error message with the run-time name.
22888 else
22889 -- Check overlapping in the priority ranges specified in other
22890 -- Priority_Specific_Dispatching pragmas within the same
22891 -- partition. We can only check those we know about.
22893 for J in
22894 Specific_Dispatching.First .. Specific_Dispatching.Last
22895 loop
22896 if Specific_Dispatching.Table (J).First_Priority in
22897 UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
22898 or else Specific_Dispatching.Table (J).Last_Priority in
22899 UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
22900 then
22901 Error_Msg_Sloc :=
22902 Specific_Dispatching.Table (J).Pragma_Loc;
22903 Error_Pragma
22904 ("priority range overlaps with "
22905 & "Priority_Specific_Dispatching#");
22906 end if;
22907 end loop;
22909 -- The use of Priority_Specific_Dispatching is incompatible
22910 -- with Task_Dispatching_Policy.
22912 if Task_Dispatching_Policy /= ' ' then
22913 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
22914 Error_Pragma
22915 ("Priority_Specific_Dispatching incompatible "
22916 & "with Task_Dispatching_Policy#");
22917 end if;
22919 -- The use of Priority_Specific_Dispatching forces ceiling
22920 -- locking policy.
22922 if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
22923 Error_Msg_Sloc := Locking_Policy_Sloc;
22924 Error_Pragma
22925 ("Priority_Specific_Dispatching incompatible "
22926 & "with Locking_Policy#");
22928 -- Set the Ceiling_Locking policy, but preserve System_Location
22929 -- since we like the error message with the run time name.
22931 else
22932 Locking_Policy := 'C';
22934 if Locking_Policy_Sloc /= System_Location then
22935 Locking_Policy_Sloc := Loc;
22936 end if;
22937 end if;
22939 -- Add entry in the table
22941 Specific_Dispatching.Append
22942 ((Dispatching_Policy => DP,
22943 First_Priority => UI_To_Int (Lower_Val),
22944 Last_Priority => UI_To_Int (Upper_Val),
22945 Pragma_Loc => Loc));
22946 end if;
22947 end Priority_Specific_Dispatching;
22949 -------------
22950 -- Profile --
22951 -------------
22953 -- pragma Profile (profile_IDENTIFIER);
22955 -- profile_IDENTIFIER => Restricted | Ravenscar | Rational
22957 when Pragma_Profile =>
22958 Ada_2005_Pragma;
22959 Check_Arg_Count (1);
22960 Check_Valid_Configuration_Pragma;
22961 Check_No_Identifiers;
22963 declare
22964 Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
22966 begin
22967 if Nkind (Argx) /= N_Identifier then
22968 Error_Msg_N
22969 ("argument of pragma Profile must be an identifier", N);
22971 elsif Chars (Argx) = Name_Ravenscar then
22972 Set_Ravenscar_Profile (Ravenscar, N);
22974 elsif Chars (Argx) = Name_Jorvik then
22975 Set_Ravenscar_Profile (Jorvik, N);
22977 elsif Chars (Argx) = Name_Gnat_Extended_Ravenscar then
22978 Set_Ravenscar_Profile (GNAT_Extended_Ravenscar, N);
22980 elsif Chars (Argx) = Name_Gnat_Ravenscar_EDF then
22981 Set_Ravenscar_Profile (GNAT_Ravenscar_EDF, N);
22983 elsif Chars (Argx) = Name_Restricted then
22984 Set_Profile_Restrictions
22985 (Restricted,
22986 N, Warn => Treat_Restrictions_As_Warnings);
22988 elsif Chars (Argx) = Name_Rational then
22989 Set_Rational_Profile;
22991 elsif Chars (Argx) = Name_No_Implementation_Extensions then
22992 Set_Profile_Restrictions
22993 (No_Implementation_Extensions,
22994 N, Warn => Treat_Restrictions_As_Warnings);
22996 else
22997 Error_Pragma_Arg ("& is not a valid profile", Argx);
22998 end if;
22999 end;
23001 ----------------------
23002 -- Profile_Warnings --
23003 ----------------------
23005 -- pragma Profile_Warnings (profile_IDENTIFIER);
23007 -- profile_IDENTIFIER => Restricted | Ravenscar
23009 when Pragma_Profile_Warnings =>
23010 GNAT_Pragma;
23011 Check_Arg_Count (1);
23012 Check_Valid_Configuration_Pragma;
23013 Check_No_Identifiers;
23015 declare
23016 Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
23018 begin
23019 if Chars (Argx) = Name_Ravenscar then
23020 Set_Profile_Restrictions (Ravenscar, N, Warn => True);
23022 elsif Chars (Argx) = Name_Restricted then
23023 Set_Profile_Restrictions (Restricted, N, Warn => True);
23025 elsif Chars (Argx) = Name_No_Implementation_Extensions then
23026 Set_Profile_Restrictions
23027 (No_Implementation_Extensions, N, Warn => True);
23029 else
23030 Error_Pragma_Arg ("& is not a valid profile", Argx);
23031 end if;
23032 end;
23034 --------------------------
23035 -- Propagate_Exceptions --
23036 --------------------------
23038 -- pragma Propagate_Exceptions;
23040 -- Note: this pragma is obsolete and has no effect
23042 when Pragma_Propagate_Exceptions =>
23043 GNAT_Pragma;
23044 Check_Arg_Count (0);
23046 if Warn_On_Obsolescent_Feature then
23047 Error_Msg_N
23048 ("'G'N'A'T pragma Propagate'_Exceptions is now obsolete " &
23049 "and has no effect?j?", N);
23050 end if;
23052 -----------------------------
23053 -- Provide_Shift_Operators --
23054 -----------------------------
23056 -- pragma Provide_Shift_Operators (integer_subtype_LOCAL_NAME);
23058 when Pragma_Provide_Shift_Operators =>
23059 Provide_Shift_Operators : declare
23060 Ent : Entity_Id;
23062 procedure Declare_Shift_Operator (Nam : Name_Id);
23063 -- Insert declaration and pragma Instrinsic for named shift op
23065 ----------------------------
23066 -- Declare_Shift_Operator --
23067 ----------------------------
23069 procedure Declare_Shift_Operator (Nam : Name_Id) is
23070 Func : Node_Id;
23071 Import : Node_Id;
23073 begin
23074 Func :=
23075 Make_Subprogram_Declaration (Loc,
23076 Make_Function_Specification (Loc,
23077 Defining_Unit_Name =>
23078 Make_Defining_Identifier (Loc, Chars => Nam),
23080 Result_Definition =>
23081 Make_Identifier (Loc, Chars => Chars (Ent)),
23083 Parameter_Specifications => New_List (
23084 Make_Parameter_Specification (Loc,
23085 Defining_Identifier =>
23086 Make_Defining_Identifier (Loc, Name_Value),
23087 Parameter_Type =>
23088 Make_Identifier (Loc, Chars => Chars (Ent))),
23090 Make_Parameter_Specification (Loc,
23091 Defining_Identifier =>
23092 Make_Defining_Identifier (Loc, Name_Amount),
23093 Parameter_Type =>
23094 New_Occurrence_Of (Standard_Natural, Loc)))));
23096 Import :=
23097 Make_Pragma (Loc,
23098 Chars => Name_Import,
23099 Pragma_Argument_Associations => New_List (
23100 Make_Pragma_Argument_Association (Loc,
23101 Expression => Make_Identifier (Loc, Name_Intrinsic)),
23102 Make_Pragma_Argument_Association (Loc,
23103 Expression => Make_Identifier (Loc, Nam))));
23105 Insert_After (N, Import);
23106 Insert_After (N, Func);
23107 end Declare_Shift_Operator;
23109 -- Start of processing for Provide_Shift_Operators
23111 begin
23112 GNAT_Pragma;
23113 Check_Arg_Count (1);
23114 Check_Arg_Is_Local_Name (Arg1);
23116 Arg1 := Get_Pragma_Arg (Arg1);
23118 -- We must have an entity name
23120 if not Is_Entity_Name (Arg1) then
23121 Error_Pragma_Arg
23122 ("pragma % must apply to integer first subtype", Arg1);
23123 end if;
23125 -- If no Entity, means there was a prior error so ignore
23127 if Present (Entity (Arg1)) then
23128 Ent := Entity (Arg1);
23130 -- Apply error checks
23132 if not Is_First_Subtype (Ent) then
23133 Error_Pragma_Arg
23134 ("cannot apply pragma %",
23135 "\& is not a first subtype",
23136 Arg1);
23138 elsif not Is_Integer_Type (Ent) then
23139 Error_Pragma_Arg
23140 ("cannot apply pragma %",
23141 "\& is not an integer type",
23142 Arg1);
23144 elsif Has_Shift_Operator (Ent) then
23145 Error_Pragma_Arg
23146 ("cannot apply pragma %",
23147 "\& already has declared shift operators",
23148 Arg1);
23150 elsif Is_Frozen (Ent) then
23151 Error_Pragma_Arg
23152 ("pragma % appears too late",
23153 "\& is already frozen",
23154 Arg1);
23155 end if;
23157 -- Now declare the operators. We do this during analysis rather
23158 -- than expansion, since we want the operators available if we
23159 -- are operating in -gnatc mode.
23161 Declare_Shift_Operator (Name_Rotate_Left);
23162 Declare_Shift_Operator (Name_Rotate_Right);
23163 Declare_Shift_Operator (Name_Shift_Left);
23164 Declare_Shift_Operator (Name_Shift_Right);
23165 Declare_Shift_Operator (Name_Shift_Right_Arithmetic);
23166 end if;
23167 end Provide_Shift_Operators;
23169 ------------------
23170 -- Psect_Object --
23171 ------------------
23173 -- pragma Psect_Object (
23174 -- [Internal =>] LOCAL_NAME,
23175 -- [, [External =>] EXTERNAL_SYMBOL]
23176 -- [, [Size =>] EXTERNAL_SYMBOL]);
23178 when Pragma_Common_Object
23179 | Pragma_Psect_Object
23181 Psect_Object : declare
23182 Args : Args_List (1 .. 3);
23183 Names : constant Name_List (1 .. 3) := (
23184 Name_Internal,
23185 Name_External,
23186 Name_Size);
23188 Internal : Node_Id renames Args (1);
23189 External : Node_Id renames Args (2);
23190 Size : Node_Id renames Args (3);
23192 Def_Id : Entity_Id;
23194 procedure Check_Arg (Arg : Node_Id);
23195 -- Checks that argument is either a string literal or an
23196 -- identifier, and posts error message if not.
23198 ---------------
23199 -- Check_Arg --
23200 ---------------
23202 procedure Check_Arg (Arg : Node_Id) is
23203 begin
23204 if Nkind (Original_Node (Arg)) not in
23205 N_String_Literal | N_Identifier
23206 then
23207 Error_Pragma_Arg
23208 ("inappropriate argument for pragma %", Arg);
23209 end if;
23210 end Check_Arg;
23212 -- Start of processing for Common_Object/Psect_Object
23214 begin
23215 GNAT_Pragma;
23216 Gather_Associations (Names, Args);
23217 Process_Extended_Import_Export_Internal_Arg (Internal);
23219 Def_Id := Entity (Internal);
23221 if Ekind (Def_Id) not in E_Constant | E_Variable then
23222 Error_Pragma_Arg
23223 ("pragma% must designate an object", Internal);
23224 end if;
23226 Check_Arg (Internal);
23228 if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
23229 Error_Pragma_Arg
23230 ("cannot use pragma% for imported/exported object",
23231 Internal);
23232 end if;
23234 if Is_Concurrent_Type (Etype (Internal)) then
23235 Error_Pragma_Arg
23236 ("cannot specify pragma % for task/protected object",
23237 Internal);
23238 end if;
23240 if Has_Rep_Pragma (Def_Id, Name_Common_Object)
23241 or else
23242 Has_Rep_Pragma (Def_Id, Name_Psect_Object)
23243 then
23244 Error_Msg_N ("??duplicate Common/Psect_Object pragma", N);
23245 end if;
23247 if Ekind (Def_Id) = E_Constant then
23248 Error_Pragma_Arg
23249 ("cannot specify pragma % for a constant", Internal);
23250 end if;
23252 if Is_Record_Type (Etype (Internal)) then
23253 declare
23254 Ent : Entity_Id;
23255 Decl : Entity_Id;
23257 begin
23258 Ent := First_Entity (Etype (Internal));
23259 while Present (Ent) loop
23260 Decl := Declaration_Node (Ent);
23262 if Ekind (Ent) = E_Component
23263 and then Nkind (Decl) = N_Component_Declaration
23264 and then Present (Expression (Decl))
23265 and then Warn_On_Export_Import
23266 then
23267 Error_Msg_N
23268 ("?x?object for pragma % has defaults", Internal);
23269 exit;
23271 else
23272 Next_Entity (Ent);
23273 end if;
23274 end loop;
23275 end;
23276 end if;
23278 if Present (Size) then
23279 Check_Arg (Size);
23280 end if;
23282 if Present (External) then
23283 Check_Arg_Is_External_Name (External);
23284 end if;
23286 -- If all error tests pass, link pragma on to the rep item chain
23288 Record_Rep_Item (Def_Id, N);
23289 end Psect_Object;
23291 ----------
23292 -- Pure --
23293 ----------
23295 -- pragma Pure [(library_unit_NAME)];
23297 when Pragma_Pure => Pure : declare
23298 Ent : Entity_Id;
23300 begin
23301 Check_Ada_83_Warning;
23303 -- If the pragma comes from a subprogram instantiation, nothing to
23304 -- check, this can happen at any level of nesting.
23306 if Is_Wrapper_Package (Current_Scope) then
23307 return;
23308 end if;
23310 Check_Valid_Library_Unit_Pragma;
23312 -- If N was rewritten as a null statement there is nothing more
23313 -- to do.
23315 if Nkind (N) = N_Null_Statement then
23316 return;
23317 end if;
23319 Ent := Find_Lib_Unit_Name;
23321 -- A pragma that applies to a Ghost entity becomes Ghost for the
23322 -- purposes of legality checks and removal of ignored Ghost code.
23324 Mark_Ghost_Pragma (N, Ent);
23326 if not Debug_Flag_U then
23327 Set_Is_Pure (Ent);
23328 Set_Has_Pragma_Pure (Ent);
23330 if Legacy_Elaboration_Checks then
23331 Set_Suppress_Elaboration_Warnings (Ent);
23332 end if;
23333 end if;
23334 end Pure;
23336 -------------------
23337 -- Pure_Function --
23338 -------------------
23340 -- pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
23342 when Pragma_Pure_Function => Pure_Function : declare
23343 Def_Id : Entity_Id;
23344 E : Entity_Id;
23345 E_Id : Node_Id;
23346 Effective : Boolean := False;
23347 Orig_Def : Entity_Id;
23348 Same_Decl : Boolean := False;
23350 begin
23351 GNAT_Pragma;
23352 Check_Arg_Count (1);
23353 Check_Optional_Identifier (Arg1, Name_Entity);
23354 Check_Arg_Is_Local_Name (Arg1);
23355 E_Id := Get_Pragma_Arg (Arg1);
23357 if Etype (E_Id) = Any_Type then
23358 return;
23359 end if;
23361 -- Loop through homonyms (overloadings) of referenced entity
23363 E := Entity (E_Id);
23365 Analyze_If_Present (Pragma_Side_Effects);
23367 -- A function with side effects shall not have a Pure_Function
23368 -- aspect or pragma (SPARK RM 6.1.11(5)).
23370 if Is_Function_With_Side_Effects (E) then
23371 Error_Pragma
23372 ("pragma % incompatible with ""Side_Effects""");
23373 end if;
23375 -- A pragma that applies to a Ghost entity becomes Ghost for the
23376 -- purposes of legality checks and removal of ignored Ghost code.
23378 Mark_Ghost_Pragma (N, E);
23380 if Present (E) then
23381 loop
23382 Def_Id := Get_Base_Subprogram (E);
23384 if Ekind (Def_Id) not in
23385 E_Function | E_Generic_Function | E_Operator
23386 then
23387 Error_Pragma_Arg
23388 ("pragma% requires a function name", Arg1);
23389 end if;
23391 -- When we have a generic function we must jump up a level
23392 -- to the declaration of the wrapper package itself.
23394 Orig_Def := Def_Id;
23396 if Is_Generic_Instance (Def_Id) then
23397 while Nkind (Orig_Def) /= N_Package_Declaration loop
23398 Orig_Def := Parent (Orig_Def);
23399 end loop;
23400 end if;
23402 if In_Same_Declarative_Part (Parent (N), Orig_Def) then
23403 Same_Decl := True;
23404 Set_Is_Pure (Def_Id);
23406 if not Has_Pragma_Pure_Function (Def_Id) then
23407 Set_Has_Pragma_Pure_Function (Def_Id);
23408 Effective := True;
23409 end if;
23410 end if;
23412 exit when From_Aspect_Specification (N);
23413 E := Homonym (E);
23414 exit when No (E) or else Scope (E) /= Current_Scope;
23415 end loop;
23417 if not Effective
23418 and then Warn_On_Redundant_Constructs
23419 then
23420 Error_Msg_NE
23421 ("pragma Pure_Function on& is redundant?r?",
23422 N, Entity (E_Id));
23424 elsif not Same_Decl then
23425 Error_Pragma_Arg
23426 ("pragma% argument must be in same declarative part",
23427 Arg1);
23428 end if;
23429 end if;
23430 end Pure_Function;
23432 --------------------
23433 -- Queuing_Policy --
23434 --------------------
23436 -- pragma Queuing_Policy (policy_IDENTIFIER);
23438 when Pragma_Queuing_Policy => declare
23439 QP : Character;
23441 begin
23442 Check_Ada_83_Warning;
23443 Check_Arg_Count (1);
23444 Check_No_Identifiers;
23445 Check_Arg_Is_Queuing_Policy (Arg1);
23446 Check_Valid_Configuration_Pragma;
23447 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
23448 QP := Fold_Upper (Name_Buffer (1));
23450 if Queuing_Policy /= ' '
23451 and then Queuing_Policy /= QP
23452 then
23453 Error_Msg_Sloc := Queuing_Policy_Sloc;
23454 Error_Pragma ("queuing policy incompatible with policy#");
23456 -- Set new policy, but always preserve System_Location since we
23457 -- like the error message with the run time name.
23459 else
23460 Queuing_Policy := QP;
23462 if Queuing_Policy_Sloc /= System_Location then
23463 Queuing_Policy_Sloc := Loc;
23464 end if;
23465 end if;
23466 end;
23468 --------------
23469 -- Rational --
23470 --------------
23472 -- pragma Rational, for compatibility with foreign compiler
23474 when Pragma_Rational =>
23475 Set_Rational_Profile;
23477 ---------------------
23478 -- Refined_Depends --
23479 ---------------------
23481 -- pragma Refined_Depends (DEPENDENCY_RELATION);
23483 -- DEPENDENCY_RELATION ::=
23484 -- null
23485 -- | (DEPENDENCY_CLAUSE {, DEPENDENCY_CLAUSE})
23487 -- DEPENDENCY_CLAUSE ::=
23488 -- OUTPUT_LIST =>[+] INPUT_LIST
23489 -- | NULL_DEPENDENCY_CLAUSE
23491 -- NULL_DEPENDENCY_CLAUSE ::= null => INPUT_LIST
23493 -- OUTPUT_LIST ::= OUTPUT | (OUTPUT {, OUTPUT})
23495 -- INPUT_LIST ::= null | INPUT | (INPUT {, INPUT})
23497 -- OUTPUT ::= NAME | FUNCTION_RESULT
23498 -- INPUT ::= NAME
23500 -- where FUNCTION_RESULT is a function Result attribute_reference
23502 -- Characteristics:
23504 -- * Analysis - The annotation undergoes initial checks to verify
23505 -- the legal placement and context. Secondary checks fully analyze
23506 -- the dependency clauses/global list in:
23508 -- Analyze_Refined_Depends_In_Decl_Part
23510 -- * Expansion - None.
23512 -- * Template - The annotation utilizes the generic template of the
23513 -- related subprogram body.
23515 -- * Globals - Capture of global references must occur after full
23516 -- analysis.
23518 -- * Instance - The annotation is instantiated automatically when
23519 -- the related generic subprogram body is instantiated.
23521 when Pragma_Refined_Depends => Refined_Depends : declare
23522 Body_Id : Entity_Id;
23523 Legal : Boolean;
23524 Spec_Id : Entity_Id;
23526 begin
23527 Analyze_Refined_Depends_Global_Post (Spec_Id, Body_Id, Legal);
23529 if Legal then
23531 -- Chain the pragma on the contract for further processing by
23532 -- Analyze_Refined_Depends_In_Decl_Part.
23534 Add_Contract_Item (N, Body_Id);
23536 -- The legality checks of pragmas Refined_Depends and
23537 -- Refined_Global are affected by the SPARK mode in effect and
23538 -- the volatility of the context. In addition these two pragmas
23539 -- are subject to an inherent order:
23541 -- 1) Refined_Global
23542 -- 2) Refined_Depends
23544 -- Analyze all these pragmas in the order outlined above
23546 Analyze_If_Present (Pragma_SPARK_Mode);
23547 Analyze_If_Present (Pragma_Volatile_Function);
23548 Analyze_If_Present (Pragma_Side_Effects);
23549 Analyze_If_Present (Pragma_Refined_Global);
23550 Analyze_Refined_Depends_In_Decl_Part (N);
23551 end if;
23552 end Refined_Depends;
23554 --------------------
23555 -- Refined_Global --
23556 --------------------
23558 -- pragma Refined_Global (GLOBAL_SPECIFICATION);
23560 -- GLOBAL_SPECIFICATION ::=
23561 -- null
23562 -- | (GLOBAL_LIST)
23563 -- | (MODED_GLOBAL_LIST {, MODED_GLOBAL_LIST})
23565 -- MODED_GLOBAL_LIST ::= MODE_SELECTOR => GLOBAL_LIST
23567 -- MODE_SELECTOR ::= In_Out | Input | Output | Proof_In
23568 -- GLOBAL_LIST ::= GLOBAL_ITEM | (GLOBAL_ITEM {, GLOBAL_ITEM})
23569 -- GLOBAL_ITEM ::= NAME
23571 -- Characteristics:
23573 -- * Analysis - The annotation undergoes initial checks to verify
23574 -- the legal placement and context. Secondary checks fully analyze
23575 -- the dependency clauses/global list in:
23577 -- Analyze_Refined_Global_In_Decl_Part
23579 -- * Expansion - None.
23581 -- * Template - The annotation utilizes the generic template of the
23582 -- related subprogram body.
23584 -- * Globals - Capture of global references must occur after full
23585 -- analysis.
23587 -- * Instance - The annotation is instantiated automatically when
23588 -- the related generic subprogram body is instantiated.
23590 when Pragma_Refined_Global => Refined_Global : declare
23591 Body_Id : Entity_Id;
23592 Legal : Boolean;
23593 Spec_Id : Entity_Id;
23595 begin
23596 Analyze_Refined_Depends_Global_Post (Spec_Id, Body_Id, Legal);
23598 if Legal then
23600 -- Chain the pragma on the contract for further processing by
23601 -- Analyze_Refined_Global_In_Decl_Part.
23603 Add_Contract_Item (N, Body_Id);
23605 -- The legality checks of pragmas Refined_Depends and
23606 -- Refined_Global are affected by the SPARK mode in effect and
23607 -- the volatility of the context. In addition these two pragmas
23608 -- are subject to an inherent order:
23610 -- 1) Refined_Global
23611 -- 2) Refined_Depends
23613 -- Analyze all these pragmas in the order outlined above
23615 Analyze_If_Present (Pragma_SPARK_Mode);
23616 Analyze_If_Present (Pragma_Volatile_Function);
23617 Analyze_If_Present (Pragma_Side_Effects);
23618 Analyze_Refined_Global_In_Decl_Part (N);
23619 Analyze_If_Present (Pragma_Refined_Depends);
23620 end if;
23621 end Refined_Global;
23623 ------------------
23624 -- Refined_Post --
23625 ------------------
23627 -- pragma Refined_Post (boolean_EXPRESSION);
23629 -- Characteristics:
23631 -- * Analysis - The annotation is fully analyzed immediately upon
23632 -- elaboration as it cannot forward reference entities.
23634 -- * Expansion - The annotation is expanded during the expansion of
23635 -- the related subprogram body contract as performed in:
23637 -- Expand_Subprogram_Contract
23639 -- * Template - The annotation utilizes the generic template of the
23640 -- related subprogram body.
23642 -- * Globals - Capture of global references must occur after full
23643 -- analysis.
23645 -- * Instance - The annotation is instantiated automatically when
23646 -- the related generic subprogram body is instantiated.
23648 when Pragma_Refined_Post => Refined_Post : declare
23649 Body_Id : Entity_Id;
23650 Legal : Boolean;
23651 Spec_Id : Entity_Id;
23653 begin
23654 Analyze_Refined_Depends_Global_Post (Spec_Id, Body_Id, Legal);
23656 -- Fully analyze the pragma when it appears inside a subprogram
23657 -- body because it cannot benefit from forward references.
23659 if Legal then
23661 -- Chain the pragma on the contract for completeness
23663 Add_Contract_Item (N, Body_Id);
23665 -- The legality checks of pragma Refined_Post are affected by
23666 -- the SPARK mode in effect and the volatility of the context.
23667 -- Analyze all pragmas in a specific order.
23669 Analyze_If_Present (Pragma_SPARK_Mode);
23670 Analyze_If_Present (Pragma_Volatile_Function);
23671 Analyze_Pre_Post_Condition_In_Decl_Part (N);
23673 -- Currently it is not possible to inline pre/postconditions on
23674 -- a subprogram subject to pragma Inline_Always.
23676 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
23677 end if;
23678 end Refined_Post;
23680 -------------------
23681 -- Refined_State --
23682 -------------------
23684 -- pragma Refined_State (REFINEMENT_LIST);
23686 -- REFINEMENT_LIST ::=
23687 -- (REFINEMENT_CLAUSE {, REFINEMENT_CLAUSE})
23689 -- REFINEMENT_CLAUSE ::= state_NAME => CONSTITUENT_LIST
23691 -- CONSTITUENT_LIST ::=
23692 -- null
23693 -- | CONSTITUENT
23694 -- | (CONSTITUENT {, CONSTITUENT})
23696 -- CONSTITUENT ::= object_NAME | state_NAME
23698 -- Characteristics:
23700 -- * Analysis - The annotation undergoes initial checks to verify
23701 -- the legal placement and context. Secondary checks preanalyze the
23702 -- refinement clauses in:
23704 -- Analyze_Refined_State_In_Decl_Part
23706 -- * Expansion - None.
23708 -- * Template - The annotation utilizes the template of the related
23709 -- package body.
23711 -- * Globals - Capture of global references must occur after full
23712 -- analysis.
23714 -- * Instance - The annotation is instantiated automatically when
23715 -- the related generic package body is instantiated.
23717 when Pragma_Refined_State => Refined_State : declare
23718 Pack_Decl : Node_Id;
23719 Spec_Id : Entity_Id;
23721 begin
23722 GNAT_Pragma;
23723 Check_No_Identifiers;
23724 Check_Arg_Count (1);
23726 Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
23728 if Nkind (Pack_Decl) /= N_Package_Body then
23729 Pragma_Misplaced;
23730 end if;
23732 Spec_Id := Corresponding_Spec (Pack_Decl);
23734 -- A pragma that applies to a Ghost entity becomes Ghost for the
23735 -- purposes of legality checks and removal of ignored Ghost code.
23737 Mark_Ghost_Pragma (N, Spec_Id);
23739 -- Chain the pragma on the contract for further processing by
23740 -- Analyze_Refined_State_In_Decl_Part.
23742 Add_Contract_Item (N, Defining_Entity (Pack_Decl));
23744 -- The legality checks of pragma Refined_State are affected by the
23745 -- SPARK mode in effect. Analyze all pragmas in a specific order.
23747 Analyze_If_Present (Pragma_SPARK_Mode);
23749 -- State refinement is allowed only when the corresponding package
23750 -- declaration has non-null pragma Abstract_State (SPARK RM
23751 -- 7.2.2(3)).
23753 if No (Abstract_States (Spec_Id))
23754 or else Has_Null_Abstract_State (Spec_Id)
23755 then
23756 SPARK_Msg_NE
23757 ("useless refinement, package & does not define abstract "
23758 & "states", N, Spec_Id);
23759 return;
23760 end if;
23761 end Refined_State;
23763 -----------------------
23764 -- Relative_Deadline --
23765 -----------------------
23767 -- pragma Relative_Deadline (time_span_EXPRESSION);
23769 when Pragma_Relative_Deadline => Relative_Deadline : declare
23770 P : constant Node_Id := Parent (N);
23771 Arg : Node_Id;
23773 begin
23774 Ada_2005_Pragma;
23775 Check_No_Identifiers;
23776 Check_Arg_Count (1);
23778 Arg := Get_Pragma_Arg (Arg1);
23780 -- The expression must be analyzed in the special manner described
23781 -- in "Handling of Default and Per-Object Expressions" in sem.ads.
23783 Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
23785 -- Subprogram case
23787 if Nkind (P) = N_Subprogram_Body then
23788 Check_In_Main_Program;
23790 -- Only Task and subprogram cases allowed
23792 elsif Nkind (P) /= N_Task_Definition then
23793 Pragma_Misplaced;
23794 end if;
23796 -- Check duplicate pragma before we set the corresponding flag
23798 if Has_Relative_Deadline_Pragma (P) then
23799 Error_Pragma ("duplicate pragma% not allowed");
23800 end if;
23802 -- Set Has_Relative_Deadline_Pragma only for tasks. Note that
23803 -- Relative_Deadline pragma node cannot be inserted in the Rep
23804 -- Item chain of Ent since it is rewritten by the expander as a
23805 -- procedure call statement that will break the chain.
23807 Set_Has_Relative_Deadline_Pragma (P);
23808 end Relative_Deadline;
23810 ------------------------
23811 -- Remote_Access_Type --
23812 ------------------------
23814 -- pragma Remote_Access_Type ([Entity =>] formal_type_LOCAL_NAME);
23816 when Pragma_Remote_Access_Type => Remote_Access_Type : declare
23817 E : Entity_Id;
23819 begin
23820 GNAT_Pragma;
23821 Check_Arg_Count (1);
23822 Check_Optional_Identifier (Arg1, Name_Entity);
23823 Check_Arg_Is_Local_Name (Arg1);
23825 E := Entity (Get_Pragma_Arg (Arg1));
23827 -- A pragma that applies to a Ghost entity becomes Ghost for the
23828 -- purposes of legality checks and removal of ignored Ghost code.
23830 Mark_Ghost_Pragma (N, E);
23832 if Nkind (Parent (E)) = N_Formal_Type_Declaration
23833 and then Ekind (E) = E_General_Access_Type
23834 and then Is_Class_Wide_Type (Directly_Designated_Type (E))
23835 and then Scope (Root_Type (Directly_Designated_Type (E)))
23836 = Scope (E)
23837 and then Is_Valid_Remote_Object_Type
23838 (Root_Type (Directly_Designated_Type (E)))
23839 then
23840 Set_Is_Remote_Types (E);
23842 else
23843 Error_Pragma_Arg
23844 ("pragma% applies only to formal access-to-class-wide types",
23845 Arg1);
23846 end if;
23847 end Remote_Access_Type;
23849 ---------------------------
23850 -- Remote_Call_Interface --
23851 ---------------------------
23853 -- pragma Remote_Call_Interface [(library_unit_NAME)];
23855 when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
23856 Cunit_Node : Node_Id;
23857 Cunit_Ent : Entity_Id;
23858 K : Node_Kind;
23860 begin
23861 Check_Ada_83_Warning;
23862 Check_Valid_Library_Unit_Pragma;
23864 -- If N was rewritten as a null statement there is nothing more
23865 -- to do.
23867 if Nkind (N) = N_Null_Statement then
23868 return;
23869 end if;
23871 Cunit_Node := Cunit (Current_Sem_Unit);
23872 K := Nkind (Unit (Cunit_Node));
23873 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
23875 -- A pragma that applies to a Ghost entity becomes Ghost for the
23876 -- purposes of legality checks and removal of ignored Ghost code.
23878 Mark_Ghost_Pragma (N, Cunit_Ent);
23880 if K = N_Package_Declaration
23881 or else K = N_Generic_Package_Declaration
23882 or else K = N_Subprogram_Declaration
23883 or else K = N_Generic_Subprogram_Declaration
23884 or else (K = N_Subprogram_Body
23885 and then Acts_As_Spec (Unit (Cunit_Node)))
23886 then
23887 null;
23888 else
23889 Error_Pragma (
23890 "pragma% must apply to package or subprogram declaration");
23891 end if;
23893 Set_Is_Remote_Call_Interface (Cunit_Ent);
23894 end Remote_Call_Interface;
23896 ------------------
23897 -- Remote_Types --
23898 ------------------
23900 -- pragma Remote_Types [(library_unit_NAME)];
23902 when Pragma_Remote_Types => Remote_Types : declare
23903 Cunit_Node : Node_Id;
23904 Cunit_Ent : Entity_Id;
23906 begin
23907 Check_Ada_83_Warning;
23908 Check_Valid_Library_Unit_Pragma;
23910 -- If N was rewritten as a null statement there is nothing more
23911 -- to do.
23913 if Nkind (N) = N_Null_Statement then
23914 return;
23915 end if;
23917 Cunit_Node := Cunit (Current_Sem_Unit);
23918 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
23920 -- A pragma that applies to a Ghost entity becomes Ghost for the
23921 -- purposes of legality checks and removal of ignored Ghost code.
23923 Mark_Ghost_Pragma (N, Cunit_Ent);
23925 if Nkind (Unit (Cunit_Node)) not in
23926 N_Package_Declaration | N_Generic_Package_Declaration
23927 then
23928 Error_Pragma
23929 ("pragma% can only apply to a package declaration");
23930 end if;
23932 Set_Is_Remote_Types (Cunit_Ent);
23933 end Remote_Types;
23935 ---------------
23936 -- Ravenscar --
23937 ---------------
23939 -- pragma Ravenscar;
23941 when Pragma_Ravenscar =>
23942 GNAT_Pragma;
23943 Check_Arg_Count (0);
23944 Check_Valid_Configuration_Pragma;
23945 Set_Ravenscar_Profile (Ravenscar, N);
23947 if Warn_On_Obsolescent_Feature then
23948 Error_Msg_N
23949 ("pragma Ravenscar is an obsolescent feature?j?", N);
23950 Error_Msg_N
23951 ("|use pragma Profile (Ravenscar) instead?j?", N);
23952 end if;
23954 -------------------------
23955 -- Restricted_Run_Time --
23956 -------------------------
23958 -- pragma Restricted_Run_Time;
23960 when Pragma_Restricted_Run_Time =>
23961 GNAT_Pragma;
23962 Check_Arg_Count (0);
23963 Check_Valid_Configuration_Pragma;
23964 Set_Profile_Restrictions
23965 (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
23967 if Warn_On_Obsolescent_Feature then
23968 Error_Msg_N
23969 ("pragma Restricted_Run_Time is an obsolescent feature?j?",
23971 Error_Msg_N
23972 ("|use pragma Profile (Restricted) instead?j?", N);
23973 end if;
23975 ------------------
23976 -- Restrictions --
23977 ------------------
23979 -- pragma Restrictions (RESTRICTION {, RESTRICTION});
23981 -- RESTRICTION ::=
23982 -- restriction_IDENTIFIER
23983 -- | restriction_parameter_IDENTIFIER => EXPRESSION
23985 when Pragma_Restrictions =>
23986 Process_Restrictions_Or_Restriction_Warnings
23987 (Warn => Treat_Restrictions_As_Warnings);
23989 --------------------------
23990 -- Restriction_Warnings --
23991 --------------------------
23993 -- pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
23995 -- RESTRICTION ::=
23996 -- restriction_IDENTIFIER
23997 -- | restriction_parameter_IDENTIFIER => EXPRESSION
23999 when Pragma_Restriction_Warnings =>
24000 GNAT_Pragma;
24001 Process_Restrictions_Or_Restriction_Warnings (Warn => True);
24003 ----------------
24004 -- Reviewable --
24005 ----------------
24007 -- pragma Reviewable;
24009 when Pragma_Reviewable =>
24010 Check_Ada_83_Warning;
24011 Check_Arg_Count (0);
24013 -- Call dummy debugging function rv. This is done to assist front
24014 -- end debugging. By placing a Reviewable pragma in the source
24015 -- program, a breakpoint on rv catches this place in the source,
24016 -- allowing convenient stepping to the point of interest.
24020 --------------------------
24021 -- Secondary_Stack_Size --
24022 --------------------------
24024 -- pragma Secondary_Stack_Size (EXPRESSION);
24026 when Pragma_Secondary_Stack_Size => Secondary_Stack_Size : declare
24027 P : constant Node_Id := Parent (N);
24028 Arg : Node_Id;
24029 Ent : Entity_Id;
24031 begin
24032 GNAT_Pragma;
24033 Check_No_Identifiers;
24034 Check_Arg_Count (1);
24036 if Nkind (P) = N_Task_Definition then
24037 Arg := Get_Pragma_Arg (Arg1);
24038 Ent := Defining_Identifier (Parent (P));
24040 -- The expression must be analyzed in the special manner
24041 -- described in "Handling of Default Expressions" in sem.ads.
24043 Preanalyze_Spec_Expression (Arg, Any_Integer);
24045 -- The pragma cannot appear if the No_Secondary_Stack
24046 -- restriction is in effect.
24048 Check_Restriction (No_Secondary_Stack, Arg);
24050 -- Anything else is incorrect
24052 else
24053 Pragma_Misplaced;
24054 end if;
24056 -- Check duplicate pragma before we chain the pragma in the Rep
24057 -- Item chain of Ent.
24059 Check_Duplicate_Pragma (Ent);
24060 Record_Rep_Item (Ent, N);
24061 end Secondary_Stack_Size;
24063 --------------------------
24064 -- Short_Circuit_And_Or --
24065 --------------------------
24067 -- pragma Short_Circuit_And_Or;
24069 when Pragma_Short_Circuit_And_Or =>
24070 GNAT_Pragma;
24071 Check_Arg_Count (0);
24072 Check_Valid_Configuration_Pragma;
24073 Short_Circuit_And_Or := True;
24075 -------------------
24076 -- Share_Generic --
24077 -------------------
24079 -- pragma Share_Generic (GNAME {, GNAME});
24081 -- GNAME ::= generic_unit_NAME | generic_instance_NAME
24083 when Pragma_Share_Generic =>
24084 GNAT_Pragma;
24085 Process_Generic_List;
24087 ------------
24088 -- Shared --
24089 ------------
24091 -- pragma Shared (LOCAL_NAME);
24093 when Pragma_Shared =>
24094 GNAT_Pragma;
24095 Process_Atomic_Independent_Shared_Volatile;
24097 --------------------
24098 -- Shared_Passive --
24099 --------------------
24101 -- pragma Shared_Passive [(library_unit_NAME)];
24103 -- Set the flag Is_Shared_Passive of program unit name entity
24105 when Pragma_Shared_Passive => Shared_Passive : declare
24106 Cunit_Node : Node_Id;
24107 Cunit_Ent : Entity_Id;
24109 begin
24110 Check_Ada_83_Warning;
24111 Check_Valid_Library_Unit_Pragma;
24113 -- If N was rewritten as a null statement there is nothing more
24114 -- to do.
24116 if Nkind (N) = N_Null_Statement then
24117 return;
24118 end if;
24120 Cunit_Node := Cunit (Current_Sem_Unit);
24121 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
24123 -- A pragma that applies to a Ghost entity becomes Ghost for the
24124 -- purposes of legality checks and removal of ignored Ghost code.
24126 Mark_Ghost_Pragma (N, Cunit_Ent);
24128 if Nkind (Unit (Cunit_Node)) not in
24129 N_Package_Declaration | N_Generic_Package_Declaration
24130 then
24131 Error_Pragma
24132 ("pragma% can only apply to a package declaration");
24133 end if;
24135 Set_Is_Shared_Passive (Cunit_Ent);
24136 end Shared_Passive;
24138 -----------------------
24139 -- Short_Descriptors --
24140 -----------------------
24142 -- pragma Short_Descriptors;
24144 -- Recognize and validate, but otherwise ignore
24146 when Pragma_Short_Descriptors =>
24147 GNAT_Pragma;
24148 Check_Arg_Count (0);
24149 Check_Valid_Configuration_Pragma;
24151 ------------------
24152 -- Side_Effects --
24153 ------------------
24155 -- pragma Side_Effects [ (boolean_EXPRESSION) ];
24157 -- Characteristics:
24159 -- * Analysis - The annotation is fully analyzed immediately upon
24160 -- elaboration as its expression must be static.
24162 -- * Expansion - None.
24164 -- * Template - The annotation utilizes the generic template of the
24165 -- related subprogram [body] when it is:
24167 -- aspect on subprogram declaration
24168 -- aspect on stand-alone subprogram body
24169 -- pragma on stand-alone subprogram body
24171 -- The annotation must prepare its own template when it is:
24173 -- pragma on subprogram declaration
24175 -- * Globals - Capture of global references must occur after full
24176 -- analysis.
24178 -- * Instance - The annotation is instantiated automatically when
24179 -- the related generic subprogram [body] is instantiated except for
24180 -- the "pragma on subprogram declaration" case. In that scenario
24181 -- the annotation must instantiate itself.
24183 when Pragma_Side_Effects => Side_Effects : declare
24184 Subp_Decl : Node_Id;
24185 Spec_Id : Entity_Id;
24186 Over_Id : Entity_Id;
24188 begin
24189 GNAT_Pragma;
24190 Check_No_Identifiers;
24191 Check_At_Most_N_Arguments (1);
24193 Subp_Decl :=
24194 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
24196 -- Abstract subprogram declaration
24198 if Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
24199 null;
24201 -- Generic subprogram declaration
24203 elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
24204 null;
24206 -- Body acts as spec
24208 elsif Nkind (Subp_Decl) = N_Subprogram_Body
24209 and then No (Corresponding_Spec (Subp_Decl))
24210 then
24211 null;
24213 -- Body stub acts as spec
24215 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
24216 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
24217 then
24218 null;
24220 -- Subprogram declaration
24222 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
24223 null;
24225 -- Otherwise the pragma is associated with an illegal construct
24227 else
24228 Error_Pragma ("pragma % must apply to a subprogram");
24229 end if;
24231 if Nkind (Specification (Subp_Decl)) /= N_Function_Specification
24232 then
24233 Error_Pragma ("pragma % must apply to a function");
24234 end if;
24236 Spec_Id := Unique_Defining_Entity (Subp_Decl);
24238 -- Chain the pragma on the contract for completeness
24240 Add_Contract_Item (N, Spec_Id);
24242 -- A function with side effects cannot override a function without
24243 -- side effects (SPARK RM 7.1.2(16)). Overriding checks are
24244 -- usually performed in New_Overloaded_Entity, however at
24245 -- that point the pragma has not been processed yet.
24247 Over_Id := Overridden_Operation (Spec_Id);
24249 if Present (Over_Id)
24250 and then not Is_Function_With_Side_Effects (Over_Id)
24251 then
24252 Error_Msg_N
24253 ("incompatible declaration of side effects for function",
24254 Spec_Id);
24256 Error_Msg_Sloc := Sloc (Over_Id);
24257 Error_Msg_N
24258 ("\& declared # with Side_Effects value False",
24259 Spec_Id);
24261 Error_Msg_Sloc := Sloc (Spec_Id);
24262 Error_Msg_N
24263 ("\overridden # with Side_Effects value True",
24264 Spec_Id);
24265 end if;
24267 -- Analyze the Boolean expression (if any)
24269 if Present (Arg1) then
24270 Check_Static_Boolean_Expression (Get_Pragma_Arg (Arg1));
24271 end if;
24272 end Side_Effects;
24274 ------------------------------
24275 -- Simple_Storage_Pool_Type --
24276 ------------------------------
24278 -- pragma Simple_Storage_Pool_Type (type_LOCAL_NAME);
24280 when Pragma_Simple_Storage_Pool_Type =>
24281 Simple_Storage_Pool_Type : declare
24282 Typ : Entity_Id;
24283 Type_Id : Node_Id;
24285 begin
24286 GNAT_Pragma;
24287 Check_Arg_Count (1);
24288 Check_Arg_Is_Library_Level_Local_Name (Arg1);
24290 Type_Id := Get_Pragma_Arg (Arg1);
24291 Find_Type (Type_Id);
24292 Typ := Entity (Type_Id);
24294 if Typ = Any_Type then
24295 return;
24296 end if;
24298 -- A pragma that applies to a Ghost entity becomes Ghost for the
24299 -- purposes of legality checks and removal of ignored Ghost code.
24301 Mark_Ghost_Pragma (N, Typ);
24303 -- We require the pragma to apply to a type declared in a package
24304 -- declaration, but not (immediately) within a package body.
24306 if Ekind (Current_Scope) /= E_Package
24307 or else In_Package_Body (Current_Scope)
24308 then
24309 Error_Pragma
24310 ("pragma% can only apply to type declared immediately "
24311 & "within a package declaration");
24312 end if;
24314 -- A simple storage pool type must be an immutably limited record
24315 -- or private type. If the pragma is given for a private type,
24316 -- the full type is similarly restricted (which is checked later
24317 -- in Freeze_Entity).
24319 if Is_Record_Type (Typ)
24320 and then not Is_Inherently_Limited_Type (Typ)
24321 then
24322 Error_Pragma
24323 ("pragma% can only apply to explicitly limited record type");
24325 elsif Is_Private_Type (Typ) and then not Is_Limited_Type (Typ) then
24326 Error_Pragma
24327 ("pragma% can only apply to a private type that is limited");
24329 elsif not Is_Record_Type (Typ)
24330 and then not Is_Private_Type (Typ)
24331 then
24332 Error_Pragma
24333 ("pragma% can only apply to limited record or private type");
24334 end if;
24336 Record_Rep_Item (Typ, N);
24337 end Simple_Storage_Pool_Type;
24339 ----------------------
24340 -- Source_File_Name --
24341 ----------------------
24343 -- There are five forms for this pragma:
24345 -- pragma Source_File_Name (
24346 -- [UNIT_NAME =>] unit_NAME,
24347 -- BODY_FILE_NAME => STRING_LITERAL
24348 -- [, [INDEX =>] INTEGER_LITERAL]);
24350 -- pragma Source_File_Name (
24351 -- [UNIT_NAME =>] unit_NAME,
24352 -- SPEC_FILE_NAME => STRING_LITERAL
24353 -- [, [INDEX =>] INTEGER_LITERAL]);
24355 -- pragma Source_File_Name (
24356 -- BODY_FILE_NAME => STRING_LITERAL
24357 -- [, DOT_REPLACEMENT => STRING_LITERAL]
24358 -- [, CASING => CASING_SPEC]);
24360 -- pragma Source_File_Name (
24361 -- SPEC_FILE_NAME => STRING_LITERAL
24362 -- [, DOT_REPLACEMENT => STRING_LITERAL]
24363 -- [, CASING => CASING_SPEC]);
24365 -- pragma Source_File_Name (
24366 -- SUBUNIT_FILE_NAME => STRING_LITERAL
24367 -- [, DOT_REPLACEMENT => STRING_LITERAL]
24368 -- [, CASING => CASING_SPEC]);
24370 -- CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
24372 -- Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
24373 -- Source_File_Name (SFN), however their usage is exclusive: SFN can
24374 -- only be used when no project file is used, while SFNP can only be
24375 -- used when a project file is used.
24377 -- No processing here. Processing was completed during parsing, since
24378 -- we need to have file names set as early as possible. Units are
24379 -- loaded well before semantic processing starts.
24381 -- The only processing we defer to this point is the check for
24382 -- correct placement.
24384 when Pragma_Source_File_Name =>
24385 GNAT_Pragma;
24386 Check_Valid_Configuration_Pragma;
24388 ------------------------------
24389 -- Source_File_Name_Project --
24390 ------------------------------
24392 -- See Source_File_Name for syntax
24394 -- No processing here. Processing was completed during parsing, since
24395 -- we need to have file names set as early as possible. Units are
24396 -- loaded well before semantic processing starts.
24398 -- The only processing we defer to this point is the check for
24399 -- correct placement.
24401 when Pragma_Source_File_Name_Project =>
24402 GNAT_Pragma;
24403 Check_Valid_Configuration_Pragma;
24405 -- Check that a pragma Source_File_Name_Project is used only in a
24406 -- configuration pragmas file.
24408 -- Pragmas Source_File_Name_Project should only be generated by
24409 -- the Project Manager in configuration pragmas files.
24411 -- This is really an ugly test. It seems to depend on some
24412 -- accidental and undocumented property. At the very least it
24413 -- needs to be documented, but it would be better to have a
24414 -- clean way of testing if we are in a configuration file???
24416 if Present (Parent (N)) then
24417 Error_Pragma
24418 ("pragma% can only appear in a configuration pragmas file");
24419 end if;
24421 ----------------------
24422 -- Source_Reference --
24423 ----------------------
24425 -- pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
24427 -- Nothing to do, all processing completed in Par.Prag, since we need
24428 -- the information for possible parser messages that are output.
24430 when Pragma_Source_Reference =>
24431 GNAT_Pragma;
24433 ----------------
24434 -- SPARK_Mode --
24435 ----------------
24437 -- pragma SPARK_Mode [(Auto | On | Off)];
24439 when Pragma_SPARK_Mode => Do_SPARK_Mode : declare
24440 Mode_Id : SPARK_Mode_Type;
24442 procedure Check_Pragma_Conformance
24443 (Context_Pragma : Node_Id;
24444 Entity : Entity_Id;
24445 Entity_Pragma : Node_Id);
24446 -- Subsidiary to routines Process_xxx. Verify the SPARK_Mode
24447 -- conformance of pragma N depending the following scenarios:
24449 -- If pragma Context_Pragma is not Empty, verify that pragma N is
24450 -- compatible with the pragma Context_Pragma that was inherited
24451 -- from the context:
24452 -- * If the mode of Context_Pragma is ON, then the new mode can
24453 -- be anything.
24454 -- * If the mode of Context_Pragma is OFF, then the only allowed
24455 -- new mode is also OFF. Emit error if this is not the case.
24457 -- If Entity is not Empty, verify that pragma N is compatible with
24458 -- pragma Entity_Pragma that belongs to Entity.
24459 -- * If Entity_Pragma is Empty, always issue an error as this
24460 -- corresponds to the case where a previous section of Entity
24461 -- has no SPARK_Mode set.
24462 -- * If the mode of Entity_Pragma is ON, then the new mode can
24463 -- be anything.
24464 -- * If the mode of Entity_Pragma is OFF, then the only allowed
24465 -- new mode is also OFF. Emit error if this is not the case.
24467 procedure Check_Library_Level_Entity (E : Entity_Id);
24468 -- Subsidiary to routines Process_xxx. Verify that the related
24469 -- entity E subject to pragma SPARK_Mode is library-level.
24471 procedure Process_Body (Decl : Node_Id);
24472 -- Verify the legality of pragma SPARK_Mode when it appears as the
24473 -- top of the body declarations of entry, package, protected unit,
24474 -- subprogram or task unit body denoted by Decl.
24476 procedure Process_Overloadable (Decl : Node_Id);
24477 -- Verify the legality of pragma SPARK_Mode when it applies to an
24478 -- entry or [generic] subprogram declaration denoted by Decl.
24480 procedure Process_Private_Part (Decl : Node_Id);
24481 -- Verify the legality of pragma SPARK_Mode when it appears at the
24482 -- top of the private declarations of a package spec, protected or
24483 -- task unit declaration denoted by Decl.
24485 procedure Process_Statement_Part (Decl : Node_Id);
24486 -- Verify the legality of pragma SPARK_Mode when it appears at the
24487 -- top of the statement sequence of a package body denoted by node
24488 -- Decl.
24490 procedure Process_Visible_Part (Decl : Node_Id);
24491 -- Verify the legality of pragma SPARK_Mode when it appears at the
24492 -- top of the visible declarations of a package spec, protected or
24493 -- task unit declaration denoted by Decl. The routine is also used
24494 -- on protected or task units declared without a definition.
24496 procedure Set_SPARK_Context;
24497 -- Subsidiary to routines Process_xxx. Set the global variables
24498 -- which represent the mode of the context from pragma N. Ensure
24499 -- that Dynamic_Elaboration_Checks are off if the new mode is On.
24501 ------------------------------
24502 -- Check_Pragma_Conformance --
24503 ------------------------------
24505 procedure Check_Pragma_Conformance
24506 (Context_Pragma : Node_Id;
24507 Entity : Entity_Id;
24508 Entity_Pragma : Node_Id)
24510 Err_Id : Entity_Id;
24511 Err_N : Node_Id;
24513 begin
24514 -- The current pragma may appear without an argument. If this
24515 -- is the case, associate all error messages with the pragma
24516 -- itself.
24518 if Present (Arg1) then
24519 Err_N := Arg1;
24520 else
24521 Err_N := N;
24522 end if;
24524 -- The mode of the current pragma is compared against that of
24525 -- an enclosing context.
24527 if Present (Context_Pragma) then
24528 pragma Assert (Nkind (Context_Pragma) = N_Pragma);
24530 -- Issue an error if the new mode is less restrictive than
24531 -- that of the context.
24533 if Get_SPARK_Mode_From_Annotation (Context_Pragma) = Off
24534 and then Get_SPARK_Mode_From_Annotation (N) = On
24535 then
24536 Error_Msg_N
24537 ("cannot change SPARK_Mode from Off to On", Err_N);
24538 Error_Msg_Sloc := Sloc (SPARK_Mode_Pragma);
24539 Error_Msg_N ("\SPARK_Mode was set to Off#", Err_N);
24540 raise Pragma_Exit;
24541 end if;
24542 end if;
24544 -- The mode of the current pragma is compared against that of
24545 -- an initial package, protected type, subprogram or task type
24546 -- declaration.
24548 if Present (Entity) then
24550 -- A simple protected or task type is transformed into an
24551 -- anonymous type whose name cannot be used to issue error
24552 -- messages. Recover the original entity of the type.
24554 if Ekind (Entity) in E_Protected_Type | E_Task_Type then
24555 Err_Id :=
24556 Defining_Entity
24557 (Original_Node (Unit_Declaration_Node (Entity)));
24558 else
24559 Err_Id := Entity;
24560 end if;
24562 -- Both the initial declaration and the completion carry
24563 -- SPARK_Mode pragmas.
24565 if Present (Entity_Pragma) then
24566 pragma Assert (Nkind (Entity_Pragma) = N_Pragma);
24568 -- Issue an error if the new mode is less restrictive
24569 -- than that of the initial declaration.
24571 if Get_SPARK_Mode_From_Annotation (Entity_Pragma) = Off
24572 and then Get_SPARK_Mode_From_Annotation (N) = On
24573 then
24574 Error_Msg_N ("incorrect use of SPARK_Mode", Err_N);
24575 Error_Msg_Sloc := Sloc (Entity_Pragma);
24576 Error_Msg_NE
24577 ("\value Off was set for SPARK_Mode on&#",
24578 Err_N, Err_Id);
24579 raise Pragma_Exit;
24580 end if;
24582 -- Otherwise the initial declaration lacks a SPARK_Mode
24583 -- pragma in which case the current pragma is illegal as
24584 -- it cannot "complete".
24586 elsif Get_SPARK_Mode_From_Annotation (N) = Off
24587 and then (Is_Generic_Unit (Entity) or else In_Instance)
24588 then
24589 null;
24591 else
24592 Error_Msg_N ("incorrect use of SPARK_Mode", Err_N);
24593 Error_Msg_Sloc := Sloc (Err_Id);
24594 Error_Msg_NE
24595 ("\no value was set for SPARK_Mode on&#",
24596 Err_N, Err_Id);
24597 raise Pragma_Exit;
24598 end if;
24599 end if;
24600 end Check_Pragma_Conformance;
24602 --------------------------------
24603 -- Check_Library_Level_Entity --
24604 --------------------------------
24606 procedure Check_Library_Level_Entity (E : Entity_Id) is
24607 procedure Add_Entity_To_Name_Buffer;
24608 -- Add the E_Kind of entity E to the name buffer
24610 -------------------------------
24611 -- Add_Entity_To_Name_Buffer --
24612 -------------------------------
24614 procedure Add_Entity_To_Name_Buffer is
24615 begin
24616 if Ekind (E) in E_Entry | E_Entry_Family then
24617 Add_Str_To_Name_Buffer ("entry");
24619 elsif Ekind (E) in E_Generic_Package
24620 | E_Package
24621 | E_Package_Body
24622 then
24623 Add_Str_To_Name_Buffer ("package");
24625 elsif Ekind (E) in E_Protected_Body | E_Protected_Type then
24626 Add_Str_To_Name_Buffer ("protected type");
24628 elsif Ekind (E) in E_Function
24629 | E_Generic_Function
24630 | E_Generic_Procedure
24631 | E_Procedure
24632 | E_Subprogram_Body
24633 then
24634 Add_Str_To_Name_Buffer ("subprogram");
24636 else
24637 pragma Assert (Ekind (E) in E_Task_Body | E_Task_Type);
24638 Add_Str_To_Name_Buffer ("task type");
24639 end if;
24640 end Add_Entity_To_Name_Buffer;
24642 -- Local variables
24644 Msg_1 : constant String :=
24645 "incorrect placement of pragma% with value ""On"" '[[]']";
24646 Msg_2 : Name_Id;
24648 -- Start of processing for Check_Library_Level_Entity
24650 begin
24651 -- A SPARK_Mode of On shall only apply to library-level
24652 -- entities, except for those in generic instances, which are
24653 -- ignored (even if the entity gets SPARK_Mode pragma attached
24654 -- in the AST, its effect is not taken into account unless the
24655 -- context already provides SPARK_Mode of On in GNATprove).
24657 if Get_SPARK_Mode_From_Annotation (N) = On
24658 and then not Is_Library_Level_Entity (E)
24659 and then Instantiation_Location (Sloc (N)) = No_Location
24660 then
24661 Error_Msg_Name_1 := Pname;
24662 Error_Msg_Code := GEC_SPARK_Mode_On_Not_Library_Level;
24663 Error_Msg_N (Fix_Error (Msg_1), N);
24665 Name_Len := 0;
24666 Add_Str_To_Name_Buffer ("\& is not a library-level ");
24667 Add_Entity_To_Name_Buffer;
24669 Msg_2 := Name_Find;
24670 Error_Msg_NE (Get_Name_String (Msg_2), N, E);
24672 raise Pragma_Exit;
24673 end if;
24674 end Check_Library_Level_Entity;
24676 ------------------
24677 -- Process_Body --
24678 ------------------
24680 procedure Process_Body (Decl : Node_Id) is
24681 Body_Id : constant Entity_Id := Defining_Entity (Decl);
24682 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Decl);
24684 begin
24685 -- Ignore pragma when applied to the special body created
24686 -- for inlining, recognized by its internal name _Parent; or
24687 -- when applied to the special body created for contracts,
24688 -- recognized by its internal name _Wrapped_Statements.
24690 if Chars (Body_Id) in Name_uParent
24691 | Name_uWrapped_Statements
24692 then
24693 return;
24694 end if;
24696 Check_Library_Level_Entity (Body_Id);
24698 -- For entry bodies, verify the legality against:
24699 -- * The mode of the context
24700 -- * The mode of the spec (if any)
24702 if Nkind (Decl) in N_Entry_Body | N_Subprogram_Body then
24704 -- A stand-alone subprogram body
24706 if Body_Id = Spec_Id then
24707 Check_Pragma_Conformance
24708 (Context_Pragma => SPARK_Pragma (Body_Id),
24709 Entity => Empty,
24710 Entity_Pragma => Empty);
24712 -- An entry or subprogram body that completes a previous
24713 -- declaration.
24715 else
24716 Check_Pragma_Conformance
24717 (Context_Pragma => SPARK_Pragma (Body_Id),
24718 Entity => Spec_Id,
24719 Entity_Pragma => SPARK_Pragma (Spec_Id));
24720 end if;
24722 Set_SPARK_Context;
24723 Set_SPARK_Pragma (Body_Id, N);
24724 Set_SPARK_Pragma_Inherited (Body_Id, False);
24726 -- For package bodies, verify the legality against:
24727 -- * The mode of the context
24728 -- * The mode of the private part
24730 -- This case is separated from protected and task bodies
24731 -- because the statement part of the package body inherits
24732 -- the mode of the body declarations.
24734 elsif Nkind (Decl) = N_Package_Body then
24735 Check_Pragma_Conformance
24736 (Context_Pragma => SPARK_Pragma (Body_Id),
24737 Entity => Spec_Id,
24738 Entity_Pragma => SPARK_Aux_Pragma (Spec_Id));
24740 Set_SPARK_Context;
24741 Set_SPARK_Pragma (Body_Id, N);
24742 Set_SPARK_Pragma_Inherited (Body_Id, False);
24743 Set_SPARK_Aux_Pragma (Body_Id, N);
24744 Set_SPARK_Aux_Pragma_Inherited (Body_Id, True);
24746 -- For protected and task bodies, verify the legality against:
24747 -- * The mode of the context
24748 -- * The mode of the private part
24750 else
24751 pragma Assert
24752 (Nkind (Decl) in N_Protected_Body | N_Task_Body);
24754 Check_Pragma_Conformance
24755 (Context_Pragma => SPARK_Pragma (Body_Id),
24756 Entity => Spec_Id,
24757 Entity_Pragma => SPARK_Aux_Pragma (Spec_Id));
24759 Set_SPARK_Context;
24760 Set_SPARK_Pragma (Body_Id, N);
24761 Set_SPARK_Pragma_Inherited (Body_Id, False);
24762 end if;
24763 end Process_Body;
24765 --------------------------
24766 -- Process_Overloadable --
24767 --------------------------
24769 procedure Process_Overloadable (Decl : Node_Id) is
24770 Spec_Id : constant Entity_Id := Defining_Entity (Decl);
24771 Spec_Typ : constant Entity_Id := Etype (Spec_Id);
24773 begin
24774 Check_Library_Level_Entity (Spec_Id);
24776 -- Verify the legality against:
24777 -- * The mode of the context
24779 Check_Pragma_Conformance
24780 (Context_Pragma => SPARK_Pragma (Spec_Id),
24781 Entity => Empty,
24782 Entity_Pragma => Empty);
24784 Set_SPARK_Pragma (Spec_Id, N);
24785 Set_SPARK_Pragma_Inherited (Spec_Id, False);
24787 -- When the pragma applies to the anonymous object created for
24788 -- a single task type, decorate the type as well. This scenario
24789 -- arises when the single task type lacks a task definition,
24790 -- therefore there is no issue with respect to a potential
24791 -- pragma SPARK_Mode in the private part.
24793 -- task type Anon_Task_Typ;
24794 -- Obj : Anon_Task_Typ;
24795 -- pragma SPARK_Mode ...;
24797 if Is_Single_Task_Object (Spec_Id) then
24798 Set_SPARK_Pragma (Spec_Typ, N);
24799 Set_SPARK_Pragma_Inherited (Spec_Typ, False);
24800 Set_SPARK_Aux_Pragma (Spec_Typ, N);
24801 Set_SPARK_Aux_Pragma_Inherited (Spec_Typ, True);
24802 end if;
24803 end Process_Overloadable;
24805 --------------------------
24806 -- Process_Private_Part --
24807 --------------------------
24809 procedure Process_Private_Part (Decl : Node_Id) is
24810 Spec_Id : constant Entity_Id := Defining_Entity (Decl);
24812 begin
24813 Check_Library_Level_Entity (Spec_Id);
24815 -- Verify the legality against:
24816 -- * The mode of the visible declarations
24818 Check_Pragma_Conformance
24819 (Context_Pragma => Empty,
24820 Entity => Spec_Id,
24821 Entity_Pragma => SPARK_Pragma (Spec_Id));
24823 Set_SPARK_Context;
24824 Set_SPARK_Aux_Pragma (Spec_Id, N);
24825 Set_SPARK_Aux_Pragma_Inherited (Spec_Id, False);
24826 end Process_Private_Part;
24828 ----------------------------
24829 -- Process_Statement_Part --
24830 ----------------------------
24832 procedure Process_Statement_Part (Decl : Node_Id) is
24833 Body_Id : constant Entity_Id := Defining_Entity (Decl);
24835 begin
24836 Check_Library_Level_Entity (Body_Id);
24838 -- Verify the legality against:
24839 -- * The mode of the body declarations
24841 Check_Pragma_Conformance
24842 (Context_Pragma => Empty,
24843 Entity => Body_Id,
24844 Entity_Pragma => SPARK_Pragma (Body_Id));
24846 Set_SPARK_Context;
24847 Set_SPARK_Aux_Pragma (Body_Id, N);
24848 Set_SPARK_Aux_Pragma_Inherited (Body_Id, False);
24849 end Process_Statement_Part;
24851 --------------------------
24852 -- Process_Visible_Part --
24853 --------------------------
24855 procedure Process_Visible_Part (Decl : Node_Id) is
24856 Spec_Id : constant Entity_Id := Defining_Entity (Decl);
24857 Obj_Id : Entity_Id;
24859 begin
24860 Check_Library_Level_Entity (Spec_Id);
24862 -- Verify the legality against:
24863 -- * The mode of the context
24865 Check_Pragma_Conformance
24866 (Context_Pragma => SPARK_Pragma (Spec_Id),
24867 Entity => Empty,
24868 Entity_Pragma => Empty);
24870 -- A task unit declared without a definition does not set the
24871 -- SPARK_Mode of the context because the task does not have any
24872 -- entries that could inherit the mode.
24874 if Nkind (Decl) not in
24875 N_Single_Task_Declaration | N_Task_Type_Declaration
24876 then
24877 Set_SPARK_Context;
24878 end if;
24880 Set_SPARK_Pragma (Spec_Id, N);
24881 Set_SPARK_Pragma_Inherited (Spec_Id, False);
24882 Set_SPARK_Aux_Pragma (Spec_Id, N);
24883 Set_SPARK_Aux_Pragma_Inherited (Spec_Id, True);
24885 -- When the pragma applies to a single protected or task type,
24886 -- decorate the corresponding anonymous object as well.
24888 -- protected Anon_Prot_Typ is
24889 -- pragma SPARK_Mode ...;
24890 -- ...
24891 -- end Anon_Prot_Typ;
24893 -- Obj : Anon_Prot_Typ;
24895 if Is_Single_Concurrent_Type (Spec_Id) then
24896 Obj_Id := Anonymous_Object (Spec_Id);
24898 Set_SPARK_Pragma (Obj_Id, N);
24899 Set_SPARK_Pragma_Inherited (Obj_Id, False);
24900 end if;
24901 end Process_Visible_Part;
24903 -----------------------
24904 -- Set_SPARK_Context --
24905 -----------------------
24907 procedure Set_SPARK_Context is
24908 begin
24909 SPARK_Mode := Mode_Id;
24910 SPARK_Mode_Pragma := N;
24911 end Set_SPARK_Context;
24913 -- Local variables
24915 Context : Node_Id;
24916 Mode : Name_Id;
24917 Stmt : Node_Id;
24919 -- Start of processing for Do_SPARK_Mode
24921 begin
24922 GNAT_Pragma;
24923 Check_No_Identifiers;
24924 Check_At_Most_N_Arguments (1);
24926 -- Check the legality of the mode (no argument = ON)
24928 if Arg_Count = 1 then
24929 Check_Arg_Is_One_Of (Arg1, Name_Auto, Name_On, Name_Off);
24930 Mode := Chars (Get_Pragma_Arg (Arg1));
24931 else
24932 Mode := Name_On;
24933 end if;
24935 Mode_Id := Get_SPARK_Mode_Type (Mode);
24936 Context := Parent (N);
24938 -- When a SPARK_Mode pragma appears inside an instantiation whose
24939 -- enclosing context has SPARK_Mode set to "off", the pragma has
24940 -- no semantic effect.
24942 if Ignore_SPARK_Mode_Pragmas_In_Instance
24943 and then Mode_Id /= Off
24944 then
24945 Rewrite (N, Make_Null_Statement (Loc));
24946 Analyze (N);
24947 return;
24948 end if;
24950 -- The pragma appears in a configuration file
24952 if No (Context) then
24953 Check_Valid_Configuration_Pragma;
24954 Set_SPARK_Context;
24956 -- The pragma acts as a configuration pragma in a compilation unit
24958 -- pragma SPARK_Mode ...;
24959 -- package Pack is ...;
24961 elsif Nkind (Context) = N_Compilation_Unit
24962 and then List_Containing (N) = Context_Items (Context)
24963 then
24964 Check_Valid_Configuration_Pragma;
24965 Set_SPARK_Context;
24967 -- Otherwise the placement of the pragma within the tree dictates
24968 -- its associated construct. Inspect the declarative list where
24969 -- the pragma resides to find a potential construct.
24971 else
24972 -- An explicit mode of Auto is only allowed as a configuration
24973 -- pragma. Escape "pragma" to avoid replacement with "aspect".
24975 if Mode_Id = None then
24976 Error_Pragma_Arg
24977 ("only configuration 'p'r'a'g'm'a% can have value &",
24978 Arg1);
24979 end if;
24981 Stmt := Prev (N);
24982 while Present (Stmt) loop
24984 -- Skip prior pragmas, but check for duplicates. Note that
24985 -- this also takes care of pragmas generated for aspects.
24987 if Nkind (Stmt) = N_Pragma then
24988 if Pragma_Name (Stmt) = Pname then
24989 Duplication_Error
24990 (Prag => N,
24991 Prev => Stmt);
24992 raise Pragma_Exit;
24993 end if;
24995 -- The pragma applies to an expression function that has
24996 -- already been rewritten into a subprogram declaration.
24998 -- function Expr_Func return ... is (...);
24999 -- pragma SPARK_Mode ...;
25001 elsif Nkind (Stmt) = N_Subprogram_Declaration
25002 and then Nkind (Original_Node (Stmt)) =
25003 N_Expression_Function
25004 then
25005 Process_Overloadable (Stmt);
25006 return;
25008 -- The pragma applies to the anonymous object created for a
25009 -- single concurrent type.
25011 -- protected type Anon_Prot_Typ ...;
25012 -- Obj : Anon_Prot_Typ;
25013 -- pragma SPARK_Mode ...;
25015 elsif Nkind (Stmt) = N_Object_Declaration
25016 and then Is_Single_Concurrent_Object
25017 (Defining_Entity (Stmt))
25018 then
25019 Process_Overloadable (Stmt);
25020 return;
25022 -- Skip internally generated code
25024 elsif not Comes_From_Source (Stmt) then
25025 null;
25027 -- The pragma applies to an entry or [generic] subprogram
25028 -- declaration.
25030 -- entry Ent ...;
25031 -- pragma SPARK_Mode ...;
25033 -- [generic]
25034 -- procedure Proc ...;
25035 -- pragma SPARK_Mode ...;
25037 elsif Nkind (Stmt) in N_Generic_Subprogram_Declaration
25038 | N_Subprogram_Declaration
25039 or else (Nkind (Stmt) = N_Entry_Declaration
25040 and then Is_Protected_Type
25041 (Scope (Defining_Entity (Stmt))))
25042 then
25043 Process_Overloadable (Stmt);
25044 return;
25046 -- Otherwise the pragma does not apply to a legal construct
25047 -- or it does not appear at the top of a declarative or a
25048 -- statement list. Issue an error and stop the analysis.
25050 else
25051 Pragma_Misplaced;
25052 end if;
25054 Prev (Stmt);
25055 end loop;
25057 -- The pragma applies to a package or a subprogram that acts as
25058 -- a compilation unit.
25060 -- procedure Proc ...;
25061 -- pragma SPARK_Mode ...;
25063 if Nkind (Context) = N_Compilation_Unit_Aux then
25064 Context := Unit (Parent (Context));
25065 end if;
25067 -- The pragma appears at the top of entry, package, protected
25068 -- unit, subprogram or task unit body declarations.
25070 -- entry Ent when ... is
25071 -- pragma SPARK_Mode ...;
25073 -- package body Pack is
25074 -- pragma SPARK_Mode ...;
25076 -- procedure Proc ... is
25077 -- pragma SPARK_Mode;
25079 -- protected body Prot is
25080 -- pragma SPARK_Mode ...;
25082 if Nkind (Context) in N_Entry_Body
25083 | N_Package_Body
25084 | N_Protected_Body
25085 | N_Subprogram_Body
25086 | N_Task_Body
25087 then
25088 Process_Body (Context);
25090 -- The pragma appears at the top of the visible or private
25091 -- declaration of a package spec, protected or task unit.
25093 -- package Pack is
25094 -- pragma SPARK_Mode ...;
25095 -- private
25096 -- pragma SPARK_Mode ...;
25098 -- protected [type] Prot is
25099 -- pragma SPARK_Mode ...;
25100 -- private
25101 -- pragma SPARK_Mode ...;
25103 elsif Nkind (Context) in N_Package_Specification
25104 | N_Protected_Definition
25105 | N_Task_Definition
25106 then
25107 if List_Containing (N) = Visible_Declarations (Context) then
25108 Process_Visible_Part (Parent (Context));
25109 else
25110 Process_Private_Part (Parent (Context));
25111 end if;
25113 -- The pragma appears at the top of package body statements
25115 -- package body Pack is
25116 -- begin
25117 -- pragma SPARK_Mode;
25119 elsif Nkind (Context) = N_Handled_Sequence_Of_Statements
25120 and then Nkind (Parent (Context)) = N_Package_Body
25121 then
25122 Process_Statement_Part (Parent (Context));
25124 -- The pragma appeared as an aspect of a [generic] subprogram
25125 -- declaration that acts as a compilation unit.
25127 -- [generic]
25128 -- procedure Proc ...;
25129 -- pragma SPARK_Mode ...;
25131 elsif Nkind (Context) in N_Generic_Subprogram_Declaration
25132 | N_Subprogram_Declaration
25133 then
25134 Process_Overloadable (Context);
25136 -- The pragma does not apply to a legal construct, issue error
25138 else
25139 Pragma_Misplaced;
25140 end if;
25141 end if;
25142 end Do_SPARK_Mode;
25144 --------------------------------
25145 -- Static_Elaboration_Desired --
25146 --------------------------------
25148 -- pragma Static_Elaboration_Desired (DIRECT_NAME);
25150 when Pragma_Static_Elaboration_Desired =>
25151 GNAT_Pragma;
25152 Check_At_Most_N_Arguments (1);
25154 if Is_Compilation_Unit (Current_Scope)
25155 and then Ekind (Current_Scope) = E_Package
25156 then
25157 Set_Static_Elaboration_Desired (Current_Scope, True);
25158 else
25159 Error_Pragma ("pragma% must apply to a library-level package");
25160 end if;
25162 ------------------
25163 -- Storage_Size --
25164 ------------------
25166 -- pragma Storage_Size (EXPRESSION);
25168 when Pragma_Storage_Size => Storage_Size : declare
25169 P : constant Node_Id := Parent (N);
25170 Arg : Node_Id;
25172 begin
25173 Check_No_Identifiers;
25174 Check_Arg_Count (1);
25176 -- The expression must be analyzed in the special manner described
25177 -- in "Handling of Default Expressions" in sem.ads.
25179 Arg := Get_Pragma_Arg (Arg1);
25180 Preanalyze_Spec_Expression (Arg, Any_Integer);
25182 if not Is_OK_Static_Expression (Arg) then
25183 Check_Restriction (Static_Storage_Size, Arg);
25184 end if;
25186 if Nkind (P) /= N_Task_Definition then
25187 Pragma_Misplaced;
25189 else
25190 if Has_Storage_Size_Pragma (P) then
25191 Error_Pragma ("duplicate pragma% not allowed");
25192 else
25193 Set_Has_Storage_Size_Pragma (P, True);
25194 end if;
25196 Record_Rep_Item (Defining_Identifier (Parent (P)), N);
25197 end if;
25198 end Storage_Size;
25200 ------------------
25201 -- Storage_Unit --
25202 ------------------
25204 -- pragma Storage_Unit (NUMERIC_LITERAL);
25206 -- Only permitted argument is System'Storage_Unit value
25208 when Pragma_Storage_Unit =>
25209 Check_No_Identifiers;
25210 Check_Arg_Count (1);
25211 Check_Arg_Is_Integer_Literal (Arg1);
25213 if Intval (Get_Pragma_Arg (Arg1)) /=
25214 UI_From_Int (Ttypes.System_Storage_Unit)
25215 then
25216 Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
25217 Error_Pragma_Arg
25218 ("the only allowed argument for pragma% is ^", Arg1);
25219 end if;
25221 --------------------
25222 -- Stream_Convert --
25223 --------------------
25225 -- pragma Stream_Convert (
25226 -- [Entity =>] type_LOCAL_NAME,
25227 -- [Read =>] function_NAME,
25228 -- [Write =>] function NAME);
25230 when Pragma_Stream_Convert => Stream_Convert : declare
25231 procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
25232 -- Check that the given argument is the name of a local function
25233 -- of one argument that is not overloaded earlier in the current
25234 -- local scope. A check is also made that the argument is a
25235 -- function with one parameter.
25237 --------------------------------------
25238 -- Check_OK_Stream_Convert_Function --
25239 --------------------------------------
25241 procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
25242 Ent : Entity_Id;
25244 begin
25245 Check_Arg_Is_Local_Name (Arg);
25246 Ent := Entity (Get_Pragma_Arg (Arg));
25248 if Has_Homonym (Ent) then
25249 Error_Pragma_Arg
25250 ("argument for pragma% may not be overloaded", Arg);
25251 end if;
25253 if Ekind (Ent) /= E_Function
25254 or else No (First_Formal (Ent))
25255 or else Present (Next_Formal (First_Formal (Ent)))
25256 then
25257 Error_Pragma_Arg
25258 ("argument for pragma% must be function of one argument",
25259 Arg);
25260 elsif Is_Abstract_Subprogram (Ent) then
25261 Error_Pragma_Arg
25262 ("argument for pragma% cannot be abstract", Arg);
25263 end if;
25264 end Check_OK_Stream_Convert_Function;
25266 -- Start of processing for Stream_Convert
25268 begin
25269 GNAT_Pragma;
25270 Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
25271 Check_Arg_Count (3);
25272 Check_Optional_Identifier (Arg1, Name_Entity);
25273 Check_Optional_Identifier (Arg2, Name_Read);
25274 Check_Optional_Identifier (Arg3, Name_Write);
25275 Check_Arg_Is_Local_Name (Arg1);
25276 Check_OK_Stream_Convert_Function (Arg2);
25277 Check_OK_Stream_Convert_Function (Arg3);
25279 declare
25280 Typ : constant Entity_Id :=
25281 Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
25282 Read : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
25283 Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
25285 begin
25286 Check_First_Subtype (Arg1);
25288 -- Check for too early or too late. Note that we don't enforce
25289 -- the rule about primitive operations in this case, since, as
25290 -- is the case for explicit stream attributes themselves, these
25291 -- restrictions are not appropriate. Note that the chaining of
25292 -- the pragma by Rep_Item_Too_Late is actually the critical
25293 -- processing done for this pragma.
25295 if Rep_Item_Too_Early (Typ, N)
25296 or else
25297 Rep_Item_Too_Late (Typ, N, FOnly => True)
25298 then
25299 return;
25300 end if;
25302 -- Return if previous error
25304 if Etype (Typ) = Any_Type
25305 or else
25306 Etype (Read) = Any_Type
25307 or else
25308 Etype (Write) = Any_Type
25309 then
25310 return;
25311 end if;
25313 -- Error checks
25315 if Underlying_Type (Etype (Read)) /= Typ then
25316 Error_Pragma_Arg
25317 ("incorrect return type for function&", Arg2);
25318 end if;
25320 if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
25321 Error_Pragma_Arg
25322 ("incorrect parameter type for function&", Arg3);
25323 end if;
25325 if Underlying_Type (Etype (First_Formal (Read))) /=
25326 Underlying_Type (Etype (Write))
25327 then
25328 Error_Pragma_Arg
25329 ("result type of & does not match Read parameter type",
25330 Arg3);
25331 end if;
25332 end;
25333 end Stream_Convert;
25335 ------------------
25336 -- Style_Checks --
25337 ------------------
25339 -- pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
25341 -- This is processed by the parser since some of the style checks
25342 -- take place during source scanning and parsing. This means that
25343 -- we don't need to issue error messages here.
25345 when Pragma_Style_Checks => Style_Checks : declare
25346 A : constant Node_Id := Get_Pragma_Arg (Arg1);
25347 S : String_Id;
25348 C : Char_Code;
25350 begin
25351 GNAT_Pragma;
25352 Check_No_Identifiers;
25354 -- Two argument form
25356 if Arg_Count = 2 then
25357 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
25359 declare
25360 E_Id : Node_Id;
25361 E : Entity_Id;
25363 begin
25364 E_Id := Get_Pragma_Arg (Arg2);
25365 Analyze (E_Id);
25367 if not Is_Entity_Name (E_Id) then
25368 Error_Pragma_Arg
25369 ("second argument of pragma% must be entity name",
25370 Arg2);
25371 end if;
25373 E := Entity (E_Id);
25375 if not Ignore_Style_Checks_Pragmas then
25376 if E = Any_Id then
25377 return;
25378 else
25379 loop
25380 Set_Suppress_Style_Checks
25381 (E, Chars (Get_Pragma_Arg (Arg1)) = Name_Off);
25382 exit when No (Homonym (E));
25383 E := Homonym (E);
25384 end loop;
25385 end if;
25386 end if;
25387 end;
25389 -- One argument form
25391 else
25392 Check_Arg_Count (1);
25394 if Ignore_Style_Checks_Pragmas then
25395 return;
25396 end if;
25398 if Nkind (A) = N_String_Literal then
25399 S := Strval (A);
25401 declare
25402 Slen : constant Natural := Natural (String_Length (S));
25403 Options : String (1 .. Slen);
25404 J : Positive;
25406 begin
25407 J := 1;
25408 loop
25409 C := Get_String_Char (S, Pos (J));
25410 exit when not In_Character_Range (C);
25411 Options (J) := Get_Character (C);
25413 -- If at end of string, set options. As per discussion
25414 -- above, no need to check for errors, since we issued
25415 -- them in the parser.
25417 if J = Slen then
25418 Set_Style_Check_Options (Options);
25420 exit;
25421 end if;
25423 J := J + 1;
25424 end loop;
25425 end;
25427 elsif Nkind (A) = N_Identifier then
25428 if Chars (A) = Name_All_Checks then
25429 if GNAT_Mode then
25430 Set_GNAT_Style_Check_Options;
25431 else
25432 Set_Default_Style_Check_Options;
25433 end if;
25435 elsif Chars (A) = Name_On then
25436 Style_Check := True;
25438 elsif Chars (A) = Name_Off then
25439 Style_Check := False;
25440 end if;
25441 end if;
25442 end if;
25443 end Style_Checks;
25445 ------------------------
25446 -- Subprogram_Variant --
25447 ------------------------
25449 -- pragma Subprogram_Variant ( SUBPROGRAM_VARIANT_LIST );
25451 -- SUBPROGRAM_VARIANT_LIST ::= STRUCTURAL_SUBPROGRAM_VARIANT_ITEM
25452 -- | NUMERIC_SUBPROGRAM_VARIANT_ITEMS
25453 -- NUMERIC_SUBPROGRAM_VARIANT_ITEMS ::=
25454 -- NUMERIC_SUBPROGRAM_VARIANT_ITEM
25455 -- {, NUMERIC_SUBPROGRAM_VARIANT_ITEM}
25456 -- NUMERIC_SUBPROGRAM_VARIANT_ITEM ::= CHANGE_DIRECTION => EXPRESSION
25457 -- STRUCTURAL_SUBPROGRAM_VARIANT_ITEM ::= Structural => EXPRESSION
25458 -- CHANGE_DIRECTION ::= Increases | Decreases
25460 -- Characteristics:
25462 -- * Analysis - The annotation undergoes initial checks to verify
25463 -- the legal placement and context. Secondary checks preanalyze the
25464 -- expressions in:
25466 -- Analyze_Subprogram_Variant_In_Decl_Part
25468 -- * Expansion - The annotation is expanded during the expansion of
25469 -- the related subprogram [body] contract as performed in:
25471 -- Expand_Subprogram_Contract
25473 -- * Template - The annotation utilizes the generic template of the
25474 -- related subprogram [body] when it is:
25476 -- aspect on subprogram declaration
25477 -- aspect on stand-alone subprogram body
25478 -- pragma on stand-alone subprogram body
25480 -- The annotation must prepare its own template when it is:
25482 -- pragma on subprogram declaration
25484 -- * Globals - Capture of global references must occur after full
25485 -- analysis.
25487 -- * Instance - The annotation is instantiated automatically when
25488 -- the related generic subprogram [body] is instantiated except for
25489 -- the "pragma on subprogram declaration" case. In that scenario
25490 -- the annotation must instantiate itself.
25492 when Pragma_Subprogram_Variant => Subprogram_Variant : declare
25493 Spec_Id : Entity_Id;
25494 Subp_Decl : Node_Id;
25495 Subp_Spec : Node_Id;
25497 begin
25498 GNAT_Pragma;
25499 Check_No_Identifiers;
25500 Check_Arg_Count (1);
25502 -- Ensure the proper placement of the pragma. Subprogram_Variant
25503 -- must be associated with a subprogram declaration or a body that
25504 -- acts as a spec.
25506 Subp_Decl :=
25507 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
25509 -- Generic subprogram
25511 if Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
25512 null;
25514 -- Body acts as spec
25516 elsif Nkind (Subp_Decl) = N_Subprogram_Body
25517 and then No (Corresponding_Spec (Subp_Decl))
25518 then
25519 null;
25521 -- Body stub acts as spec
25523 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
25524 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
25525 then
25526 null;
25528 -- Subprogram
25530 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
25531 Subp_Spec := Specification (Subp_Decl);
25533 -- Pragma Subprogram_Variant is forbidden on null procedures,
25534 -- as this may lead to potential ambiguities in behavior when
25535 -- interface null procedures are involved. Also, it just
25536 -- wouldn't make sense, because null procedure is not
25537 -- recursive.
25539 if Nkind (Subp_Spec) = N_Procedure_Specification
25540 and then Null_Present (Subp_Spec)
25541 then
25542 Error_Msg_N (Fix_Error
25543 ("pragma % cannot apply to null procedure"), N);
25544 return;
25545 end if;
25547 else
25548 Pragma_Misplaced;
25549 end if;
25551 Spec_Id := Unique_Defining_Entity (Subp_Decl);
25553 -- A pragma that applies to a Ghost entity becomes Ghost for the
25554 -- purposes of legality checks and removal of ignored Ghost code.
25556 Mark_Ghost_Pragma (N, Spec_Id);
25557 Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
25559 -- Chain the pragma on the contract for further processing by
25560 -- Analyze_Subprogram_Variant_In_Decl_Part.
25562 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
25564 -- Fully analyze the pragma when it appears inside a subprogram
25565 -- body because it cannot benefit from forward references.
25567 if Nkind (Subp_Decl) in N_Subprogram_Body
25568 | N_Subprogram_Body_Stub
25569 then
25570 -- The legality checks of pragma Subprogram_Variant are
25571 -- affected by the SPARK mode in effect and the volatility
25572 -- of the context. Analyze all pragmas in a specific order.
25574 Analyze_If_Present (Pragma_SPARK_Mode);
25575 Analyze_If_Present (Pragma_Volatile_Function);
25576 Analyze_Subprogram_Variant_In_Decl_Part (N);
25577 end if;
25578 end Subprogram_Variant;
25580 --------------
25581 -- Subtitle --
25582 --------------
25584 -- pragma Subtitle ([Subtitle =>] STRING_LITERAL);
25586 when Pragma_Subtitle =>
25587 GNAT_Pragma;
25588 Check_Arg_Count (1);
25589 Check_Optional_Identifier (Arg1, Name_Subtitle);
25590 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
25591 Store_Note (N);
25593 --------------
25594 -- Suppress --
25595 --------------
25597 -- pragma Suppress (IDENTIFIER [, [On =>] NAME]);
25599 when Pragma_Suppress =>
25600 Process_Suppress_Unsuppress (Suppress_Case => True);
25602 ------------------
25603 -- Suppress_All --
25604 ------------------
25606 -- pragma Suppress_All;
25608 -- The only check made here is that the pragma has no arguments.
25609 -- There are no placement rules, and the processing required (setting
25610 -- the Has_Pragma_Suppress_All flag in the compilation unit node was
25611 -- taken care of by the parser). Process_Compilation_Unit_Pragmas
25612 -- then creates and inserts a pragma Suppress (All_Checks).
25614 when Pragma_Suppress_All =>
25615 GNAT_Pragma;
25616 Check_Arg_Count (0);
25618 -------------------------
25619 -- Suppress_Debug_Info --
25620 -------------------------
25622 -- pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
25624 when Pragma_Suppress_Debug_Info => Suppress_Debug_Info : declare
25625 Nam_Id : Entity_Id;
25627 begin
25628 GNAT_Pragma;
25629 Check_Arg_Count (1);
25630 Check_Optional_Identifier (Arg1, Name_Entity);
25631 Check_Arg_Is_Local_Name (Arg1);
25633 Nam_Id := Entity (Get_Pragma_Arg (Arg1));
25635 -- A pragma that applies to a Ghost entity becomes Ghost for the
25636 -- purposes of legality checks and removal of ignored Ghost code.
25638 Mark_Ghost_Pragma (N, Nam_Id);
25639 Set_Debug_Info_Off (Nam_Id);
25640 end Suppress_Debug_Info;
25642 ----------------------------------
25643 -- Suppress_Exception_Locations --
25644 ----------------------------------
25646 -- pragma Suppress_Exception_Locations;
25648 when Pragma_Suppress_Exception_Locations =>
25649 GNAT_Pragma;
25650 Check_Arg_Count (0);
25651 Check_Valid_Configuration_Pragma;
25652 Exception_Locations_Suppressed := True;
25654 -----------------------------
25655 -- Suppress_Initialization --
25656 -----------------------------
25658 -- pragma Suppress_Initialization ([Entity =>] type_LOCAL_NAME);
25660 when Pragma_Suppress_Initialization => Suppress_Init : declare
25661 E : Entity_Id;
25662 E_Id : Node_Id;
25664 begin
25665 GNAT_Pragma;
25666 Check_Arg_Count (1);
25667 Check_Optional_Identifier (Arg1, Name_Entity);
25668 Check_Arg_Is_Local_Name (Arg1);
25670 E_Id := Get_Pragma_Arg (Arg1);
25672 if Etype (E_Id) = Any_Type then
25673 return;
25674 end if;
25676 E := Entity (E_Id);
25678 -- A pragma that applies to a Ghost entity becomes Ghost for the
25679 -- purposes of legality checks and removal of ignored Ghost code.
25681 Mark_Ghost_Pragma (N, E);
25683 if not Is_Type (E) and then Ekind (E) /= E_Variable then
25684 Error_Pragma_Arg
25685 ("pragma% requires variable, type or subtype", Arg1);
25686 end if;
25688 if Rep_Item_Too_Early (E, N)
25689 or else
25690 Rep_Item_Too_Late (E, N, FOnly => True)
25691 then
25692 return;
25693 end if;
25695 -- For incomplete/private type, set flag on full view
25697 if Is_Incomplete_Or_Private_Type (E) then
25698 if No (Full_View (Base_Type (E))) then
25699 Error_Pragma_Arg
25700 ("argument of pragma% cannot be an incomplete type", Arg1);
25701 else
25702 Set_Suppress_Initialization (Full_View (E));
25703 end if;
25705 -- For first subtype, set flag on base type
25707 elsif Is_First_Subtype (E) then
25708 Set_Suppress_Initialization (Base_Type (E));
25710 -- For other than first subtype, set flag on subtype or variable
25712 else
25713 Set_Suppress_Initialization (E);
25714 end if;
25715 end Suppress_Init;
25717 -----------------
25718 -- System_Name --
25719 -----------------
25721 -- pragma System_Name (DIRECT_NAME);
25723 -- Syntax check: one argument, which must be the identifier GNAT or
25724 -- the identifier GCC, no other identifiers are acceptable.
25726 when Pragma_System_Name =>
25727 GNAT_Pragma;
25728 Check_No_Identifiers;
25729 Check_Arg_Count (1);
25730 Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
25732 -----------------------------
25733 -- Task_Dispatching_Policy --
25734 -----------------------------
25736 -- pragma Task_Dispatching_Policy (policy_IDENTIFIER);
25738 when Pragma_Task_Dispatching_Policy => declare
25739 DP : Character;
25741 begin
25742 Check_Ada_83_Warning;
25743 Check_Arg_Count (1);
25744 Check_No_Identifiers;
25745 Check_Arg_Is_Task_Dispatching_Policy (Arg1);
25746 Check_Valid_Configuration_Pragma;
25747 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
25748 DP := Fold_Upper (Name_Buffer (1));
25750 if Task_Dispatching_Policy /= ' '
25751 and then Task_Dispatching_Policy /= DP
25752 then
25753 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
25754 Error_Pragma
25755 ("task dispatching policy incompatible with policy#");
25757 -- Set new policy, but always preserve System_Location since we
25758 -- like the error message with the run time name.
25760 else
25761 Task_Dispatching_Policy := DP;
25763 if Task_Dispatching_Policy_Sloc /= System_Location then
25764 Task_Dispatching_Policy_Sloc := Loc;
25765 end if;
25766 end if;
25767 end;
25769 ---------------
25770 -- Task_Info --
25771 ---------------
25773 -- pragma Task_Info (EXPRESSION);
25775 when Pragma_Task_Info => Task_Info : declare
25776 P : constant Node_Id := Parent (N);
25777 Ent : Entity_Id;
25779 begin
25780 GNAT_Pragma;
25782 if Warn_On_Obsolescent_Feature then
25783 Error_Msg_N
25784 ("'G'N'A'T pragma Task_Info is now obsolete, use 'C'P'U "
25785 & "instead?j?", N);
25786 end if;
25788 if Nkind (P) /= N_Task_Definition then
25789 Error_Pragma ("pragma% must appear in task definition");
25790 end if;
25792 Check_No_Identifiers;
25793 Check_Arg_Count (1);
25795 Analyze_And_Resolve
25796 (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
25798 if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
25799 return;
25800 end if;
25802 Ent := Defining_Identifier (Parent (P));
25804 -- Check duplicate pragma before we chain the pragma in the Rep
25805 -- Item chain of Ent.
25807 if Has_Rep_Pragma
25808 (Ent, Name_Task_Info, Check_Parents => False)
25809 then
25810 Error_Pragma ("duplicate pragma% not allowed");
25811 end if;
25813 Record_Rep_Item (Ent, N);
25814 end Task_Info;
25816 ---------------
25817 -- Task_Name --
25818 ---------------
25820 -- pragma Task_Name (string_EXPRESSION);
25822 when Pragma_Task_Name => Task_Name : declare
25823 P : constant Node_Id := Parent (N);
25824 Arg : Node_Id;
25825 Ent : Entity_Id;
25827 begin
25828 Check_No_Identifiers;
25829 Check_Arg_Count (1);
25831 Arg := Get_Pragma_Arg (Arg1);
25833 -- The expression is used in the call to Create_Task, and must be
25834 -- expanded there, not in the context of the current spec. It must
25835 -- however be analyzed to capture global references, in case it
25836 -- appears in a generic context.
25838 Preanalyze_And_Resolve (Arg, Standard_String);
25840 if Nkind (P) /= N_Task_Definition then
25841 Pragma_Misplaced;
25842 end if;
25844 Ent := Defining_Identifier (Parent (P));
25846 -- Check duplicate pragma before we chain the pragma in the Rep
25847 -- Item chain of Ent.
25849 if Has_Rep_Pragma
25850 (Ent, Name_Task_Name, Check_Parents => False)
25851 then
25852 Error_Pragma ("duplicate pragma% not allowed");
25853 end if;
25855 Record_Rep_Item (Ent, N);
25856 end Task_Name;
25858 ------------------
25859 -- Task_Storage --
25860 ------------------
25862 -- pragma Task_Storage (
25863 -- [Task_Type =>] LOCAL_NAME,
25864 -- [Top_Guard =>] static_integer_EXPRESSION);
25866 when Pragma_Task_Storage => Task_Storage : declare
25867 Args : Args_List (1 .. 2);
25868 Names : constant Name_List (1 .. 2) := (
25869 Name_Task_Type,
25870 Name_Top_Guard);
25872 Task_Type : Node_Id renames Args (1);
25873 Top_Guard : Node_Id renames Args (2);
25875 Ent : Entity_Id;
25877 begin
25878 GNAT_Pragma;
25879 Gather_Associations (Names, Args);
25881 if No (Task_Type) then
25882 Error_Pragma
25883 ("missing task_type argument for pragma%");
25884 end if;
25886 Check_Arg_Is_Local_Name (Task_Type);
25888 Ent := Entity (Task_Type);
25890 if not Is_Task_Type (Ent) then
25891 Error_Pragma_Arg
25892 ("argument for pragma% must be task type", Task_Type);
25893 end if;
25895 if No (Top_Guard) then
25896 Error_Pragma_Arg
25897 ("pragma% takes two arguments", Task_Type);
25898 else
25899 Check_Arg_Is_OK_Static_Expression (Top_Guard, Any_Integer);
25900 end if;
25902 Check_First_Subtype (Task_Type);
25904 if Rep_Item_Too_Late (Ent, N) then
25905 return;
25906 end if;
25907 end Task_Storage;
25909 ---------------
25910 -- Test_Case --
25911 ---------------
25913 -- pragma Test_Case
25914 -- ([Name =>] Static_String_EXPRESSION
25915 -- ,[Mode =>] MODE_TYPE
25916 -- [, Requires => Boolean_EXPRESSION]
25917 -- [, Ensures => Boolean_EXPRESSION]);
25919 -- MODE_TYPE ::= Nominal | Robustness
25921 -- Characteristics:
25923 -- * Analysis - The annotation undergoes initial checks to verify
25924 -- the legal placement and context. Secondary checks preanalyze the
25925 -- expressions in:
25927 -- Analyze_Test_Case_In_Decl_Part
25929 -- * Expansion - None.
25931 -- * Template - The annotation utilizes the generic template of the
25932 -- related subprogram when it is:
25934 -- aspect on subprogram declaration
25936 -- The annotation must prepare its own template when it is:
25938 -- pragma on subprogram declaration
25940 -- * Globals - Capture of global references must occur after full
25941 -- analysis.
25943 -- * Instance - The annotation is instantiated automatically when
25944 -- the related generic subprogram is instantiated except for the
25945 -- "pragma on subprogram declaration" case. In that scenario the
25946 -- annotation must instantiate itself.
25948 when Pragma_Test_Case => Test_Case : declare
25949 procedure Check_Distinct_Name (Subp_Id : Entity_Id);
25950 -- Ensure that the contract of subprogram Subp_Id does not contain
25951 -- another Test_Case pragma with the same Name as the current one.
25953 -------------------------
25954 -- Check_Distinct_Name --
25955 -------------------------
25957 procedure Check_Distinct_Name (Subp_Id : Entity_Id) is
25958 Items : constant Node_Id := Contract (Subp_Id);
25959 Name : constant String_Id := Get_Name_From_CTC_Pragma (N);
25960 Prag : Node_Id;
25962 begin
25963 -- Inspect all Test_Case pragma of the related subprogram
25964 -- looking for one with a duplicate "Name" argument.
25966 if Present (Items) then
25967 Prag := Contract_Test_Cases (Items);
25968 while Present (Prag) loop
25969 if Pragma_Name (Prag) = Name_Test_Case
25970 and then Prag /= N
25971 and then String_Equal
25972 (Name, Get_Name_From_CTC_Pragma (Prag))
25973 then
25974 Error_Msg_Sloc := Sloc (Prag);
25975 Error_Pragma ("name for pragma % is already used #");
25976 end if;
25978 Prag := Next_Pragma (Prag);
25979 end loop;
25980 end if;
25981 end Check_Distinct_Name;
25983 -- Local variables
25985 Pack_Decl : constant Node_Id := Unit (Cunit (Current_Sem_Unit));
25986 Asp_Arg : Node_Id;
25987 Context : Node_Id;
25988 Subp_Decl : Node_Id;
25989 Subp_Id : Entity_Id;
25991 -- Start of processing for Test_Case
25993 begin
25994 GNAT_Pragma;
25995 Check_At_Least_N_Arguments (2);
25996 Check_At_Most_N_Arguments (4);
25997 Check_Arg_Order
25998 ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
26000 -- Argument "Name"
26002 Check_Optional_Identifier (Arg1, Name_Name);
26003 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
26005 -- Argument "Mode"
26007 Check_Optional_Identifier (Arg2, Name_Mode);
26008 Check_Arg_Is_One_Of (Arg2, Name_Nominal, Name_Robustness);
26010 -- Arguments "Requires" and "Ensures"
26012 if Present (Arg3) then
26013 if Present (Arg4) then
26014 Check_Identifier (Arg3, Name_Requires);
26015 Check_Identifier (Arg4, Name_Ensures);
26016 else
26017 Check_Identifier_Is_One_Of
26018 (Arg3, Name_Requires, Name_Ensures);
26019 end if;
26020 end if;
26022 -- Pragma Test_Case must be associated with a subprogram declared
26023 -- in a library-level package. First determine whether the current
26024 -- compilation unit is a legal context.
26026 if Nkind (Pack_Decl) in N_Package_Declaration
26027 | N_Generic_Package_Declaration
26028 then
26029 null;
26031 -- Otherwise the placement is illegal
26033 else
26034 Error_Pragma
26035 ("pragma % must be specified within a package declaration");
26036 end if;
26038 Subp_Decl := Find_Related_Declaration_Or_Body (N);
26040 -- Find the enclosing context
26042 Context := Parent (Subp_Decl);
26044 if Present (Context) then
26045 Context := Parent (Context);
26046 end if;
26048 -- Verify the placement of the pragma
26050 if Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
26051 Error_Pragma
26052 ("pragma % cannot be applied to abstract subprogram");
26054 elsif Nkind (Subp_Decl) = N_Entry_Declaration then
26055 Error_Pragma ("pragma % cannot be applied to entry");
26057 -- The context is a [generic] subprogram declared at the top level
26058 -- of the [generic] package unit.
26060 elsif Nkind (Subp_Decl) in N_Generic_Subprogram_Declaration
26061 | N_Subprogram_Declaration
26062 and then Present (Context)
26063 and then Nkind (Context) in N_Generic_Package_Declaration
26064 | N_Package_Declaration
26065 then
26066 null;
26068 -- Otherwise the placement is illegal
26070 else
26071 Error_Pragma
26072 ("pragma % must be applied to a library-level subprogram "
26073 & "declaration");
26074 end if;
26076 Subp_Id := Defining_Entity (Subp_Decl);
26078 -- A pragma that applies to a Ghost entity becomes Ghost for the
26079 -- purposes of legality checks and removal of ignored Ghost code.
26081 Mark_Ghost_Pragma (N, Subp_Id);
26083 -- Chain the pragma on the contract for further processing by
26084 -- Analyze_Test_Case_In_Decl_Part.
26086 Add_Contract_Item (N, Subp_Id);
26088 -- Preanalyze the original aspect argument "Name" for a generic
26089 -- subprogram to properly capture global references.
26091 if Is_Generic_Subprogram (Subp_Id) then
26092 Asp_Arg := Test_Case_Arg (N, Name_Name, From_Aspect => True);
26094 if Present (Asp_Arg) then
26096 -- The argument appears with an identifier in association
26097 -- form.
26099 if Nkind (Asp_Arg) = N_Component_Association then
26100 Asp_Arg := Expression (Asp_Arg);
26101 end if;
26103 Check_Expr_Is_OK_Static_Expression
26104 (Asp_Arg, Standard_String);
26105 end if;
26106 end if;
26108 -- Ensure that the all Test_Case pragmas of the related subprogram
26109 -- have distinct names.
26111 Check_Distinct_Name (Subp_Id);
26113 -- Fully analyze the pragma when it appears inside an entry
26114 -- or subprogram body because it cannot benefit from forward
26115 -- references.
26117 if Nkind (Subp_Decl) in N_Entry_Body
26118 | N_Subprogram_Body
26119 | N_Subprogram_Body_Stub
26120 then
26121 -- The legality checks of pragma Test_Case are affected by the
26122 -- SPARK mode in effect and the volatility of the context.
26123 -- Analyze all pragmas in a specific order.
26125 Analyze_If_Present (Pragma_SPARK_Mode);
26126 Analyze_If_Present (Pragma_Volatile_Function);
26127 Analyze_Test_Case_In_Decl_Part (N);
26128 end if;
26129 end Test_Case;
26131 --------------------------
26132 -- Thread_Local_Storage --
26133 --------------------------
26135 -- pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
26137 when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
26138 E : Entity_Id;
26139 Id : Node_Id;
26141 begin
26142 GNAT_Pragma;
26143 Check_Arg_Count (1);
26144 Check_Optional_Identifier (Arg1, Name_Entity);
26145 Check_Arg_Is_Library_Level_Local_Name (Arg1);
26147 Id := Get_Pragma_Arg (Arg1);
26149 if not Is_Entity_Name (Id)
26150 or else Ekind (Entity (Id)) /= E_Variable
26151 then
26152 Error_Pragma_Arg ("local variable name required", Arg1);
26153 end if;
26155 E := Entity (Id);
26157 -- A pragma that applies to a Ghost entity becomes Ghost for the
26158 -- purposes of legality checks and removal of ignored Ghost code.
26160 Mark_Ghost_Pragma (N, E);
26162 if Rep_Item_Too_Early (E, N)
26163 or else
26164 Rep_Item_Too_Late (E, N)
26165 then
26166 return;
26167 end if;
26169 Set_Has_Pragma_Thread_Local_Storage (E);
26170 Set_Has_Gigi_Rep_Item (E);
26171 end Thread_Local_Storage;
26173 ----------------
26174 -- Time_Slice --
26175 ----------------
26177 -- pragma Time_Slice (static_duration_EXPRESSION);
26179 when Pragma_Time_Slice => Time_Slice : declare
26180 Val : Ureal;
26181 Nod : Node_Id;
26183 begin
26184 GNAT_Pragma;
26185 Check_Arg_Count (1);
26186 Check_No_Identifiers;
26187 Check_In_Main_Program;
26188 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_Duration);
26190 if not Error_Posted (Arg1) then
26191 Nod := Next (N);
26192 while Present (Nod) loop
26193 if Nkind (Nod) = N_Pragma
26194 and then Pragma_Name (Nod) = Name_Time_Slice
26195 then
26196 Error_Msg_Name_1 := Pname;
26197 Error_Msg_N ("duplicate pragma% not permitted", Nod);
26198 end if;
26200 Next (Nod);
26201 end loop;
26202 end if;
26204 -- Process only if in main unit
26206 if Get_Source_Unit (Loc) = Main_Unit then
26207 Opt.Time_Slice_Set := True;
26208 Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
26210 if Val <= Ureal_0 then
26211 Opt.Time_Slice_Value := 0;
26213 elsif Val > UR_From_Uint (UI_From_Int (1000)) then
26214 Opt.Time_Slice_Value := 1_000_000_000;
26216 else
26217 Opt.Time_Slice_Value :=
26218 UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
26219 end if;
26220 end if;
26221 end Time_Slice;
26223 -----------
26224 -- Title --
26225 -----------
26227 -- pragma Title (TITLING_OPTION [, TITLING OPTION]);
26229 -- TITLING_OPTION ::=
26230 -- [Title =>] STRING_LITERAL
26231 -- | [Subtitle =>] STRING_LITERAL
26233 when Pragma_Title => Title : declare
26234 Args : Args_List (1 .. 2);
26235 Names : constant Name_List (1 .. 2) := (
26236 Name_Title,
26237 Name_Subtitle);
26239 begin
26240 GNAT_Pragma;
26241 Gather_Associations (Names, Args);
26242 Store_Note (N);
26244 for J in 1 .. 2 loop
26245 if Present (Args (J)) then
26246 Check_Arg_Is_OK_Static_Expression
26247 (Args (J), Standard_String);
26248 end if;
26249 end loop;
26250 end Title;
26252 ----------------------------
26253 -- Type_Invariant[_Class] --
26254 ----------------------------
26256 -- pragma Type_Invariant[_Class]
26257 -- ([Entity =>] type_LOCAL_NAME,
26258 -- [Check =>] EXPRESSION);
26260 when Pragma_Type_Invariant
26261 | Pragma_Type_Invariant_Class
26263 Type_Invariant : declare
26264 I_Pragma : Node_Id;
26266 begin
26267 Check_Arg_Count (2);
26269 -- Rewrite Type_Invariant[_Class] pragma as an Invariant pragma,
26270 -- setting Class_Present for the Type_Invariant_Class case.
26272 Set_Class_Present (N, Prag_Id = Pragma_Type_Invariant_Class);
26273 I_Pragma := New_Copy (N);
26274 Set_Pragma_Identifier
26275 (I_Pragma, Make_Identifier (Loc, Name_Invariant));
26276 Rewrite (N, I_Pragma);
26277 Set_Analyzed (N, False);
26278 Analyze (N);
26279 end Type_Invariant;
26281 ---------------------
26282 -- Unchecked_Union --
26283 ---------------------
26285 -- pragma Unchecked_Union (first_subtype_LOCAL_NAME);
26287 when Pragma_Unchecked_Union => Unchecked_Union : declare
26288 Assoc : constant Node_Id := Arg1;
26289 Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
26290 Clist : Node_Id;
26291 Comp : Node_Id;
26292 Tdef : Node_Id;
26293 Typ : Entity_Id;
26294 Variant : Node_Id;
26295 Vpart : Node_Id;
26297 begin
26298 Ada_2005_Pragma;
26299 Check_No_Identifiers;
26300 Check_Arg_Count (1);
26301 Check_Arg_Is_Local_Name (Arg1);
26303 Find_Type (Type_Id);
26305 Typ := Entity (Type_Id);
26307 -- A pragma that applies to a Ghost entity becomes Ghost for the
26308 -- purposes of legality checks and removal of ignored Ghost code.
26310 Mark_Ghost_Pragma (N, Typ);
26312 if Typ = Any_Type
26313 or else Rep_Item_Too_Early (Typ, N)
26314 then
26315 return;
26316 else
26317 Typ := Underlying_Type (Typ);
26318 end if;
26320 if Rep_Item_Too_Late (Typ, N) then
26321 return;
26322 end if;
26324 Check_First_Subtype (Arg1);
26326 -- Note remaining cases are references to a type in the current
26327 -- declarative part. If we find an error, we post the error on
26328 -- the relevant type declaration at an appropriate point.
26330 if not Is_Record_Type (Typ) then
26331 Error_Msg_N ("unchecked union must be record type", Typ);
26332 return;
26334 elsif Is_Tagged_Type (Typ) then
26335 Error_Msg_N ("unchecked union must not be tagged", Typ);
26336 return;
26338 elsif not Has_Discriminants (Typ) then
26339 Error_Msg_N
26340 ("unchecked union must have one discriminant", Typ);
26341 return;
26343 -- Note: in previous versions of GNAT we used to check for limited
26344 -- types and give an error, but in fact the standard does allow
26345 -- Unchecked_Union on limited types, so this check was removed.
26347 -- Similarly, GNAT used to require that all discriminants have
26348 -- default values, but this is not mandated by the RM.
26350 -- Proceed with basic error checks completed
26352 else
26353 Tdef := Type_Definition (Declaration_Node (Typ));
26354 Clist := Component_List (Tdef);
26356 -- Check presence of component list and variant part
26358 if No (Clist) or else No (Variant_Part (Clist)) then
26359 Error_Msg_N
26360 ("unchecked union must have variant part", Tdef);
26361 return;
26362 end if;
26364 -- Check components
26366 Comp := First_Non_Pragma (Component_Items (Clist));
26367 while Present (Comp) loop
26368 Check_Component (Comp, Typ);
26369 Next_Non_Pragma (Comp);
26370 end loop;
26372 -- Check variant part
26374 Vpart := Variant_Part (Clist);
26376 Variant := First_Non_Pragma (Variants (Vpart));
26377 while Present (Variant) loop
26378 Check_Variant (Variant, Typ);
26379 Next_Non_Pragma (Variant);
26380 end loop;
26381 end if;
26383 Set_Is_Unchecked_Union (Typ);
26384 Set_Convention (Typ, Convention_C);
26385 Set_Has_Unchecked_Union (Base_Type (Typ));
26386 Set_Is_Unchecked_Union (Base_Type (Typ));
26387 end Unchecked_Union;
26389 ----------------------------
26390 -- Unevaluated_Use_Of_Old --
26391 ----------------------------
26393 -- pragma Unevaluated_Use_Of_Old (Error | Warn | Allow);
26395 when Pragma_Unevaluated_Use_Of_Old =>
26396 GNAT_Pragma;
26397 Check_Arg_Count (1);
26398 Check_No_Identifiers;
26399 Check_Arg_Is_One_Of (Arg1, Name_Error, Name_Warn, Name_Allow);
26401 -- Suppress/Unsuppress can appear as a configuration pragma, or in
26402 -- a declarative part or a package spec.
26404 if not Is_Configuration_Pragma then
26405 Check_Is_In_Decl_Part_Or_Package_Spec;
26406 end if;
26408 -- Store proper setting of Uneval_Old
26410 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
26411 Uneval_Old := Fold_Upper (Name_Buffer (1));
26413 ------------------------
26414 -- Unimplemented_Unit --
26415 ------------------------
26417 -- pragma Unimplemented_Unit;
26419 -- Note: this only gives an error if we are generating code, or if
26420 -- we are in a generic library unit (where the pragma appears in the
26421 -- body, not in the spec).
26423 when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
26424 Cunitent : constant Entity_Id :=
26425 Cunit_Entity (Get_Source_Unit (Loc));
26427 begin
26428 GNAT_Pragma;
26429 Check_Arg_Count (0);
26431 if Operating_Mode = Generate_Code
26432 or else Is_Generic_Unit (Cunitent)
26433 then
26434 Get_Name_String (Chars (Cunitent));
26435 Set_Casing (Mixed_Case);
26436 Write_Str (Name_Buffer (1 .. Name_Len));
26437 Write_Str (" is not supported in this configuration");
26438 Write_Eol;
26439 raise Unrecoverable_Error;
26440 end if;
26441 end Unimplemented_Unit;
26443 ------------------------
26444 -- Universal_Aliasing --
26445 ------------------------
26447 -- pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
26449 when Pragma_Universal_Aliasing => Universal_Alias : declare
26450 E : Entity_Id;
26451 E_Id : Node_Id;
26453 begin
26454 GNAT_Pragma;
26455 Check_Arg_Count (1);
26456 Check_Optional_Identifier (Arg2, Name_Entity);
26457 Check_Arg_Is_Local_Name (Arg1);
26458 E_Id := Get_Pragma_Arg (Arg1);
26460 if Etype (E_Id) = Any_Type then
26461 return;
26462 end if;
26464 E := Entity (E_Id);
26466 if not Is_Type (E) then
26467 Error_Pragma_Arg ("pragma% requires type", Arg1);
26468 end if;
26470 -- A pragma that applies to a Ghost entity becomes Ghost for the
26471 -- purposes of legality checks and removal of ignored Ghost code.
26473 Mark_Ghost_Pragma (N, E);
26474 Set_Universal_Aliasing (Base_Type (E));
26475 Record_Rep_Item (E, N);
26476 end Universal_Alias;
26478 ----------------
26479 -- Unmodified --
26480 ----------------
26482 -- pragma Unmodified (LOCAL_NAME {, LOCAL_NAME});
26484 when Pragma_Unmodified =>
26485 Analyze_Unmodified_Or_Unused;
26487 ------------------
26488 -- Unreferenced --
26489 ------------------
26491 -- pragma Unreferenced (LOCAL_NAME {, LOCAL_NAME});
26493 -- or when used in a context clause:
26495 -- pragma Unreferenced (library_unit_NAME {, library_unit_NAME});
26497 when Pragma_Unreferenced =>
26498 Analyze_Unreferenced_Or_Unused;
26500 --------------------------
26501 -- Unreferenced_Objects --
26502 --------------------------
26504 -- pragma Unreferenced_Objects (LOCAL_NAME {, LOCAL_NAME});
26506 when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
26507 Arg : Node_Id;
26508 Arg_Expr : Node_Id;
26509 Arg_Id : Entity_Id;
26511 Ghost_Error_Posted : Boolean := False;
26512 -- Flag set when an error concerning the illegal mix of Ghost and
26513 -- non-Ghost types is emitted.
26515 Ghost_Id : Entity_Id := Empty;
26516 -- The entity of the first Ghost type encountered while processing
26517 -- the arguments of the pragma.
26519 begin
26520 GNAT_Pragma;
26521 Check_At_Least_N_Arguments (1);
26523 Arg := Arg1;
26524 while Present (Arg) loop
26525 Check_No_Identifier (Arg);
26526 Check_Arg_Is_Local_Name (Arg);
26527 Arg_Expr := Get_Pragma_Arg (Arg);
26529 if Is_Entity_Name (Arg_Expr) then
26530 Arg_Id := Entity (Arg_Expr);
26532 if Is_Type (Arg_Id) then
26533 Set_Has_Pragma_Unreferenced_Objects (Arg_Id);
26535 -- A pragma that applies to a Ghost entity becomes Ghost
26536 -- for the purposes of legality checks and removal of
26537 -- ignored Ghost code.
26539 Mark_Ghost_Pragma (N, Arg_Id);
26541 -- Capture the entity of the first Ghost type being
26542 -- processed for error detection purposes.
26544 if Is_Ghost_Entity (Arg_Id) then
26545 if No (Ghost_Id) then
26546 Ghost_Id := Arg_Id;
26547 end if;
26549 -- Otherwise the type is non-Ghost. It is illegal to mix
26550 -- references to Ghost and non-Ghost entities
26551 -- (SPARK RM 6.9).
26553 elsif Present (Ghost_Id)
26554 and then not Ghost_Error_Posted
26555 then
26556 Ghost_Error_Posted := True;
26558 Error_Msg_Name_1 := Pname;
26559 Error_Msg_N
26560 ("pragma % cannot mention ghost and non-ghost types",
26563 Error_Msg_Sloc := Sloc (Ghost_Id);
26564 Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
26566 Error_Msg_Sloc := Sloc (Arg_Id);
26567 Error_Msg_NE ("\& # declared as non-ghost", N, Arg_Id);
26568 end if;
26569 else
26570 Error_Pragma_Arg
26571 ("argument for pragma% must be type or subtype", Arg);
26572 end if;
26573 else
26574 Error_Pragma_Arg
26575 ("argument for pragma% must be type or subtype", Arg);
26576 end if;
26578 Next (Arg);
26579 end loop;
26580 end Unreferenced_Objects;
26582 ------------------------------
26583 -- Unreserve_All_Interrupts --
26584 ------------------------------
26586 -- pragma Unreserve_All_Interrupts;
26588 when Pragma_Unreserve_All_Interrupts =>
26589 GNAT_Pragma;
26590 Check_Arg_Count (0);
26592 if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
26593 Unreserve_All_Interrupts := True;
26594 end if;
26596 ----------------
26597 -- Unsuppress --
26598 ----------------
26600 -- pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
26602 when Pragma_Unsuppress =>
26603 Ada_2005_Pragma;
26604 Process_Suppress_Unsuppress (Suppress_Case => False);
26606 ------------
26607 -- Unused --
26608 ------------
26610 -- pragma Unused (LOCAL_NAME {, LOCAL_NAME});
26612 when Pragma_Unused =>
26613 Analyze_Unmodified_Or_Unused (Is_Unused => True);
26614 Analyze_Unreferenced_Or_Unused (Is_Unused => True);
26616 -------------------
26617 -- Use_VADS_Size --
26618 -------------------
26620 -- pragma Use_VADS_Size;
26622 when Pragma_Use_VADS_Size =>
26623 GNAT_Pragma;
26624 Check_Arg_Count (0);
26625 Check_Valid_Configuration_Pragma;
26626 Use_VADS_Size := True;
26628 ----------------------------
26629 -- User_Aspect_Definition --
26630 ----------------------------
26632 -- pragma User_Aspect_Definition
26633 -- (Identifier, {, Identifier [(Identifier {, Identifier})]});
26635 when Pragma_User_Aspect_Definition =>
26636 GNAT_Pragma;
26637 Check_Valid_Configuration_Pragma;
26638 declare
26639 Arg : Node_Id :=
26640 First (Pragma_Argument_Associations (N));
26641 User_Aspect_Name : constant Name_Id := Chars (Expression (Arg));
26642 Expr : Node_Id;
26643 Aspect : Aspect_Id;
26644 begin
26645 if Get_Aspect_Id (User_Aspect_Name) /= No_Aspect then
26646 Error_Pragma_Arg
26647 ("User-defined aspect name for pragma% is the name " &
26648 "of an existing aspect", Arg);
26649 end if;
26651 Next (Arg); -- skip first argument, the name of the aspect
26653 while Present (Arg) loop
26654 Expr := Expression (Arg);
26655 case Nkind (Expr) is
26656 when N_Identifier =>
26657 Aspect := Get_Aspect_Id (Chars (Expr));
26658 if Aspect in Boolean_Aspects
26659 and not Is_Representation_Aspect (Aspect)
26660 then
26661 -- If we allowed representation aspects such as
26662 -- Pack here, then User_Aspect itself would need
26663 -- to be a representation aspect.
26665 null;
26666 elsif Aspect = No_Aspect and then
26667 Present (User_Aspect_Support.Registered_UAD_Pragma
26668 (User_Aspect_Name))
26669 then
26670 null;
26671 else
26672 Error_Pragma_Arg
26673 ("unparameterized argument for pragma% must be " &
26674 "either a Boolean-valued non-representation " &
26675 "aspect or user-defined", Arg);
26676 end if;
26677 when N_Indexed_Component =>
26678 Aspect := Get_Aspect_Id (Chars (Prefix (Expr)));
26680 -- Aspect should be an aspect that takes
26681 -- identifier arguments that do not refer to
26682 -- declarations, but rather to undeclared entities
26683 -- such as GNATProve or No_Secondary_Stack for
26684 -- which the notion of visibility does not apply.
26686 case Aspect is
26687 when Aspect_Annotate =>
26688 if List_Length (Expressions (Expr)) /= 2 then
26689 Error_Pragma_Arg
26690 ("Annotate argument for pragma% takes " &
26691 "two parameters", Arg);
26692 end if;
26694 when Aspect_Local_Restrictions =>
26695 null;
26697 when others =>
26698 Error_Pragma_Arg
26699 ("parameterized argument for pragma% must be " &
26700 "Annotate or Local_Restrictions aspect", Arg);
26701 end case;
26702 when others =>
26703 raise Program_Error; -- parsing error
26704 end case;
26705 Next (Arg);
26706 end loop;
26708 declare
26709 Registered : constant Node_Id :=
26710 User_Aspect_Support.Registered_UAD_Pragma
26711 (User_Aspect_Name);
26713 -- Given two User_Aspect_Definition pragmas with
26714 -- matching names for the first argument, check that
26715 -- subsequent arguments also match; complain if they differ.
26716 procedure Check_UAD_Conformance
26717 (New_Pragma, Old_Pragma : Node_Id);
26719 ---------------------------
26720 -- Check_UAD_Conformance --
26721 ---------------------------
26723 procedure Check_UAD_Conformance
26724 (New_Pragma, Old_Pragma : Node_Id)
26726 Old_Arg : Node_Id :=
26727 First (Pragma_Argument_Associations (Old_Pragma));
26728 New_Arg : Node_Id :=
26729 First (Pragma_Argument_Associations (New_Pragma));
26730 OK : Boolean := True;
26732 function Same_Chars (Id1, Id2 : Node_Id) return Boolean
26733 is (Chars (Id1) = Chars (Id2));
26735 function Same_Identifier_List (Id1, Id2 : Node_Id)
26736 return Boolean
26737 is (if No (Id1) and No (Id2) then True
26738 elsif No (Id1) or No (Id2) then False
26739 else (Same_Chars (Id1, Id2) and then
26740 Same_Identifier_List (Next (Id1), Next (Id2))));
26741 begin
26742 -- We could skip the first argument pair since those
26743 -- are already known to match (or we wouldn't be
26744 -- calling this procedure).
26746 while Present (Old_Arg) or Present (New_Arg) loop
26747 if Present (Old_Arg) /= Present (New_Arg) then
26748 OK := False;
26749 elsif Nkind (Expression (Old_Arg)) /=
26750 Nkind (Expression (New_Arg))
26751 then
26752 OK := False;
26753 else
26754 case Nkind (Expression (Old_Arg)) is
26755 when N_Identifier =>
26756 OK := Same_Chars (Expression (Old_Arg),
26757 Expression (New_Arg));
26759 when N_Indexed_Component =>
26760 OK := Same_Chars
26761 (Prefix (Expression (Old_Arg)),
26762 Prefix (Expression (New_Arg)))
26763 and then Same_Identifier_List
26764 (First (Expressions
26765 (Expression (Old_Arg))),
26766 First (Expressions
26767 (Expression (New_Arg))));
26769 when others =>
26770 OK := False;
26771 pragma Assert (False);
26772 end case;
26773 end if;
26775 if not OK then
26776 Error_Msg_Sloc := Sloc (Old_Pragma);
26777 Error_Msg_N
26778 ("Nonconforming definitions for user-defined " &
26779 "aspect #", New_Pragma);
26780 return;
26781 end if;
26783 Next (Old_Arg);
26784 Next (New_Arg);
26785 end loop;
26786 end Check_UAD_Conformance;
26787 begin
26788 if Present (Registered) then
26789 -- If we have already seen a UAD pragma with this name,
26790 -- then check that the two pragmas conform (which means
26791 -- that the new pragma is redundant and can be ignored).
26793 -- ??? We could also perform a similar bind-time check,
26794 -- since it is possible that an incompatible pair of
26795 -- UAD pragmas might not be detected by this check.
26796 -- This could arise if no unit's compilation closure
26797 -- includes both of the two. The major downside of
26798 -- failing to detect this case is possible confusion
26799 -- for human readers.
26801 Check_UAD_Conformance (New_Pragma => N,
26802 Old_Pragma => Registered);
26803 else
26804 User_Aspect_Support.Register_UAD_Pragma (N);
26805 end if;
26806 end;
26807 end;
26809 ---------------------
26810 -- Validity_Checks --
26811 ---------------------
26813 -- pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
26815 when Pragma_Validity_Checks => Validity_Checks : declare
26816 A : constant Node_Id := Get_Pragma_Arg (Arg1);
26817 S : String_Id;
26818 C : Char_Code;
26820 begin
26821 GNAT_Pragma;
26822 Check_Arg_Count (1);
26823 Check_No_Identifiers;
26825 -- Pragma always active unless in CodePeer or GNATprove modes,
26826 -- which use a fixed configuration of validity checks.
26828 if not (CodePeer_Mode or GNATprove_Mode) then
26829 if Nkind (A) = N_String_Literal then
26830 S := Strval (A);
26832 declare
26833 Slen : constant Natural := Natural (String_Length (S));
26834 Options : String (1 .. Slen);
26835 J : Positive;
26837 begin
26838 -- Couldn't we use a for loop here over Options'Range???
26840 J := 1;
26841 loop
26842 C := Get_String_Char (S, Pos (J));
26844 -- This is a weird test, it skips setting validity
26845 -- checks entirely if any element of S is out of
26846 -- range of Character, what is that about ???
26848 exit when not In_Character_Range (C);
26849 Options (J) := Get_Character (C);
26851 if J = Slen then
26852 Set_Validity_Check_Options (Options);
26853 exit;
26854 else
26855 J := J + 1;
26856 end if;
26857 end loop;
26858 end;
26860 elsif Nkind (A) = N_Identifier then
26861 if Chars (A) = Name_All_Checks then
26862 Set_Validity_Check_Options ("a");
26863 elsif Chars (A) = Name_On then
26864 Validity_Checks_On := True;
26865 elsif Chars (A) = Name_Off then
26866 Validity_Checks_On := False;
26867 end if;
26868 end if;
26869 end if;
26870 end Validity_Checks;
26872 --------------
26873 -- Volatile --
26874 --------------
26876 -- pragma Volatile (LOCAL_NAME);
26878 when Pragma_Volatile =>
26879 Process_Atomic_Independent_Shared_Volatile;
26881 -------------------------
26882 -- Volatile_Components --
26883 -------------------------
26885 -- pragma Volatile_Components (array_LOCAL_NAME);
26887 -- Volatile is handled by the same circuit as Atomic_Components
26889 --------------------------
26890 -- Volatile_Full_Access --
26891 --------------------------
26893 -- pragma Volatile_Full_Access (LOCAL_NAME);
26895 when Pragma_Volatile_Full_Access =>
26896 GNAT_Pragma;
26897 Process_Atomic_Independent_Shared_Volatile;
26899 -----------------------
26900 -- Volatile_Function --
26901 -----------------------
26903 -- pragma Volatile_Function [ (static_boolean_EXPRESSION) ];
26905 when Pragma_Volatile_Function => Volatile_Function : declare
26906 Over_Id : Entity_Id;
26907 Spec_Id : Entity_Id;
26908 Subp_Decl : Node_Id;
26910 begin
26911 GNAT_Pragma;
26912 Check_No_Identifiers;
26913 Check_At_Most_N_Arguments (1);
26915 Subp_Decl :=
26916 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
26918 -- Generic subprogram
26920 if Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
26921 null;
26923 -- Body acts as spec
26925 elsif Nkind (Subp_Decl) = N_Subprogram_Body
26926 and then No (Corresponding_Spec (Subp_Decl))
26927 then
26928 null;
26930 -- Body stub acts as spec
26932 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
26933 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
26934 then
26935 null;
26937 -- Subprogram
26939 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
26940 null;
26942 else
26943 Pragma_Misplaced;
26944 end if;
26946 Spec_Id := Unique_Defining_Entity (Subp_Decl);
26948 if Ekind (Spec_Id) not in E_Function | E_Generic_Function then
26949 Pragma_Misplaced;
26950 end if;
26952 -- A pragma that applies to a Ghost entity becomes Ghost for the
26953 -- purposes of legality checks and removal of ignored Ghost code.
26955 Mark_Ghost_Pragma (N, Spec_Id);
26957 -- Chain the pragma on the contract for completeness
26959 Add_Contract_Item (N, Spec_Id);
26961 -- The legality checks of pragma Volatile_Function are affected by
26962 -- the SPARK mode in effect. Analyze all pragmas in a specific
26963 -- order.
26965 Analyze_If_Present (Pragma_SPARK_Mode);
26967 -- A volatile function cannot override a non-volatile function
26968 -- (SPARK RM 7.1.2(15)). Overriding checks are usually performed
26969 -- in New_Overloaded_Entity, however at that point the pragma has
26970 -- not been processed yet.
26972 Over_Id := Overridden_Operation (Spec_Id);
26974 if Present (Over_Id)
26975 and then not Is_Volatile_Function (Over_Id)
26976 then
26977 Error_Msg_N
26978 ("incompatible volatile function values in effect", Spec_Id);
26980 Error_Msg_Sloc := Sloc (Over_Id);
26981 Error_Msg_N
26982 ("\& declared # with Volatile_Function value False",
26983 Spec_Id);
26985 Error_Msg_Sloc := Sloc (Spec_Id);
26986 Error_Msg_N
26987 ("\overridden # with Volatile_Function value True",
26988 Spec_Id);
26989 end if;
26991 -- Analyze the Boolean expression (if any)
26993 if Present (Arg1) then
26994 Check_Static_Boolean_Expression (Get_Pragma_Arg (Arg1));
26995 end if;
26996 end Volatile_Function;
26998 ----------------------
26999 -- Warning_As_Error --
27000 ----------------------
27002 -- pragma Warning_As_Error (static_string_EXPRESSION);
27004 when Pragma_Warning_As_Error =>
27005 GNAT_Pragma;
27006 Check_Arg_Count (1);
27007 Check_No_Identifiers;
27008 Check_Valid_Configuration_Pragma;
27010 if not Is_Static_String_Expression (Arg1) then
27011 Error_Pragma_Arg
27012 ("argument of pragma% must be static string expression",
27013 Arg1);
27015 -- OK static string expression
27017 else
27018 Warnings_As_Errors_Count := Warnings_As_Errors_Count + 1;
27019 Warnings_As_Errors (Warnings_As_Errors_Count) :=
27020 new String'(Acquire_Warning_Match_String
27021 (Expr_Value_S (Get_Pragma_Arg (Arg1))));
27022 end if;
27024 --------------
27025 -- Warnings --
27026 --------------
27028 -- pragma Warnings ([TOOL_NAME,] DETAILS [, REASON]);
27030 -- DETAILS ::= On | Off
27031 -- DETAILS ::= On | Off, local_NAME
27032 -- DETAILS ::= static_string_EXPRESSION
27033 -- DETAILS ::= On | Off, static_string_EXPRESSION
27035 -- TOOL_NAME ::= GNAT | GNATprove
27037 -- REASON ::= Reason => STRING_LITERAL {& STRING_LITERAL}
27039 -- Note: If the first argument matches an allowed tool name, it is
27040 -- always considered to be a tool name, even if there is a string
27041 -- variable of that name.
27043 -- Note if the second argument of DETAILS is a local_NAME then the
27044 -- second form is always understood. If the intention is to use
27045 -- the fourth form, then you can write NAME & "" to force the
27046 -- intepretation as a static_string_EXPRESSION.
27048 when Pragma_Warnings => Warnings : declare
27049 Reason : String_Id;
27051 begin
27052 GNAT_Pragma;
27053 Check_At_Least_N_Arguments (1);
27055 -- See if last argument is labeled Reason. If so, make sure we
27056 -- have a string literal or a concatenation of string literals,
27057 -- and acquire the REASON string. Then remove the REASON argument
27058 -- by decreasing Num_Args by one; Remaining processing looks only
27059 -- at first Num_Args arguments).
27061 declare
27062 Last_Arg : constant Node_Id :=
27063 Last (Pragma_Argument_Associations (N));
27065 begin
27066 if Nkind (Last_Arg) = N_Pragma_Argument_Association
27067 and then Chars (Last_Arg) = Name_Reason
27068 then
27069 Start_String;
27070 Get_Reason_String (Get_Pragma_Arg (Last_Arg));
27071 Reason := End_String;
27072 Arg_Count := Arg_Count - 1;
27074 -- No REASON string, set null string as reason
27076 else
27077 Reason := Null_String_Id;
27078 end if;
27079 end;
27081 -- Now proceed with REASON taken care of and eliminated
27083 Check_No_Identifiers;
27085 -- If debug flag -gnatd.i is set, pragma is ignored
27087 if Debug_Flag_Dot_I then
27088 return;
27089 end if;
27091 -- Process various forms of the pragma
27093 declare
27094 Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
27095 Shifted_Args : List_Id;
27097 begin
27098 -- See if first argument is a tool name, currently either
27099 -- GNAT or GNATprove. If so, either ignore the pragma if the
27100 -- tool used does not match, or continue as if no tool name
27101 -- was given otherwise, by shifting the arguments.
27103 if Nkind (Argx) = N_Identifier
27104 and then Chars (Argx) in Name_Gnat | Name_Gnatprove
27105 then
27106 if Chars (Argx) = Name_Gnat then
27107 if CodePeer_Mode or GNATprove_Mode then
27108 Rewrite (N, Make_Null_Statement (Loc));
27109 Analyze (N);
27110 return;
27111 end if;
27113 elsif Chars (Argx) = Name_Gnatprove then
27114 if not GNATprove_Mode then
27115 Rewrite (N, Make_Null_Statement (Loc));
27116 Analyze (N);
27117 return;
27118 end if;
27119 else
27120 raise Program_Error;
27121 end if;
27123 -- At this point, the pragma Warnings applies to the tool,
27124 -- so continue with shifted arguments.
27126 Arg_Count := Arg_Count - 1;
27128 if Arg_Count = 1 then
27129 Shifted_Args := New_List (New_Copy (Arg2));
27130 elsif Arg_Count = 2 then
27131 Shifted_Args := New_List (New_Copy (Arg2),
27132 New_Copy (Arg3));
27133 elsif Arg_Count = 3 then
27134 Shifted_Args := New_List (New_Copy (Arg2),
27135 New_Copy (Arg3),
27136 New_Copy (Arg4));
27137 else
27138 raise Program_Error;
27139 end if;
27141 Rewrite (N,
27142 Make_Pragma (Loc,
27143 Chars => Name_Warnings,
27144 Pragma_Argument_Associations => Shifted_Args));
27145 Analyze (N);
27146 return;
27147 end if;
27149 -- One argument case
27151 if Arg_Count = 1 then
27153 -- On/Off one argument case was processed by parser
27155 if Nkind (Argx) = N_Identifier
27156 and then Chars (Argx) in Name_On | Name_Off
27157 then
27158 null;
27160 -- One argument case must be ON/OFF or static string expr
27162 elsif not Is_Static_String_Expression (Arg1) then
27163 Error_Pragma_Arg
27164 ("argument of pragma% must be On/Off or static string "
27165 & "expression", Arg1);
27167 -- Use of pragma Warnings to set warning switches is
27168 -- ignored in GNATprove mode, as these switches apply to
27169 -- the compiler only.
27171 elsif GNATprove_Mode then
27172 null;
27174 -- One argument string expression case
27176 else
27177 declare
27178 Lit : constant Node_Id := Expr_Value_S (Argx);
27179 Str : constant String_Id := Strval (Lit);
27180 Len : constant Nat := String_Length (Str);
27181 C : Char_Code;
27182 J : Nat;
27183 OK : Boolean;
27184 Chr : Character;
27186 begin
27187 J := 1;
27188 while J <= Len loop
27189 C := Get_String_Char (Str, J);
27190 OK := In_Character_Range (C);
27192 if OK then
27193 Chr := Get_Character (C);
27195 -- Dash case: only -Wxxx is accepted
27197 if J = 1
27198 and then J < Len
27199 and then Chr = '-'
27200 then
27201 J := J + 1;
27202 C := Get_String_Char (Str, J);
27203 Chr := Get_Character (C);
27204 exit when Chr = 'W';
27205 OK := False;
27207 -- Dot case
27209 elsif J < Len and then Chr = '.' then
27210 J := J + 1;
27211 C := Get_String_Char (Str, J);
27212 Chr := Get_Character (C);
27214 if not Set_Warning_Switch ('.', Chr) then
27215 Error_Pragma_Arg
27216 ("invalid warning switch character "
27217 & '.' & Chr, Arg1);
27218 end if;
27220 -- Non-Dot case
27222 else
27223 OK := Set_Warning_Switch (Plain, Chr);
27224 end if;
27226 if not OK then
27227 Error_Pragma_Arg
27228 ("invalid warning switch character " & Chr,
27229 Arg1);
27230 end if;
27232 else
27233 Error_Pragma_Arg
27234 ("invalid wide character in warning switch ",
27235 Arg1);
27236 end if;
27238 J := J + 1;
27239 end loop;
27240 end;
27241 end if;
27243 -- Two or more arguments (must be two)
27245 else
27246 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
27247 Check_Arg_Count (2);
27249 declare
27250 E_Id : Node_Id;
27251 E : Entity_Id;
27252 Err : Boolean;
27254 begin
27255 E_Id := Get_Pragma_Arg (Arg2);
27256 Analyze (E_Id);
27258 -- In the expansion of an inlined body, a reference to
27259 -- the formal may be wrapped in a conversion if the
27260 -- actual is a conversion. Retrieve the real entity name.
27262 if (In_Instance_Body or In_Inlined_Body)
27263 and then Nkind (E_Id) = N_Unchecked_Type_Conversion
27264 then
27265 E_Id := Expression (E_Id);
27266 end if;
27268 -- Entity name case
27270 if Is_Entity_Name (E_Id) then
27271 E := Entity (E_Id);
27273 if E = Any_Id then
27274 return;
27275 else
27276 loop
27277 Set_Warnings_Off
27278 (E, (Chars (Get_Pragma_Arg (Arg1)) =
27279 Name_Off));
27281 -- Suppress elaboration warnings if the entity
27282 -- denotes an elaboration target.
27284 if Is_Elaboration_Target (E) then
27285 Set_Is_Elaboration_Warnings_OK_Id (E, False);
27286 end if;
27288 -- For OFF case, make entry in warnings off
27289 -- pragma table for later processing. But we do
27290 -- not do that within an instance, since these
27291 -- warnings are about what is needed in the
27292 -- template, not an instance of it.
27294 if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
27295 and then Warn_On_Warnings_Off
27296 and then not In_Instance
27297 then
27298 Warnings_Off_Pragmas.Append ((N, E, Reason));
27299 end if;
27301 if Is_Enumeration_Type (E) then
27302 declare
27303 Lit : Entity_Id;
27304 begin
27305 Lit := First_Literal (E);
27306 while Present (Lit) loop
27307 Set_Warnings_Off (Lit);
27308 Next_Literal (Lit);
27309 end loop;
27310 end;
27311 end if;
27313 exit when No (Homonym (E));
27314 E := Homonym (E);
27315 end loop;
27316 end if;
27318 -- Error if not entity or static string expression case
27320 elsif not Is_Static_String_Expression (Arg2) then
27321 Error_Pragma_Arg
27322 ("second argument of pragma% must be entity name "
27323 & "or static string expression", Arg2);
27325 -- Static string expression case
27327 else
27328 -- Note on configuration pragma case: If this is a
27329 -- configuration pragma, then for an OFF pragma, we
27330 -- just set Config True in the call, which is all
27331 -- that needs to be done. For the case of ON, this
27332 -- is normally an error, unless it is canceling the
27333 -- effect of a previous OFF pragma in the same file.
27334 -- In any other case, an error will be signalled (ON
27335 -- with no matching OFF).
27337 -- Note: We set Used if we are inside a generic to
27338 -- disable the test that the non-config case actually
27339 -- cancels a warning. That's because we can't be sure
27340 -- there isn't an instantiation in some other unit
27341 -- where a warning is suppressed.
27343 -- We could do a little better here by checking if the
27344 -- generic unit we are inside is public, but for now
27345 -- we don't bother with that refinement.
27347 declare
27348 Message : constant String :=
27349 Acquire_Warning_Match_String
27350 (Expr_Value_S (Get_Pragma_Arg (Arg2)));
27351 begin
27352 if Chars (Argx) = Name_Off then
27353 Set_Specific_Warning_Off
27354 (N, Message, Reason,
27355 Config => Is_Configuration_Pragma,
27356 Used => Inside_A_Generic or else In_Instance);
27358 elsif Chars (Argx) = Name_On then
27359 Set_Specific_Warning_On (Loc, Message, Err);
27361 if Err then
27362 Error_Msg_N
27363 ("??pragma Warnings On with no matching "
27364 & "Warnings Off", N);
27365 end if;
27366 end if;
27367 end;
27368 end if;
27369 end;
27370 end if;
27371 end;
27372 end Warnings;
27374 -------------------
27375 -- Weak_External --
27376 -------------------
27378 -- pragma Weak_External ([Entity =>] LOCAL_NAME);
27380 when Pragma_Weak_External => Weak_External : declare
27381 Ent : Entity_Id;
27383 begin
27384 GNAT_Pragma;
27385 Check_Arg_Count (1);
27386 Check_Optional_Identifier (Arg1, Name_Entity);
27387 Check_Arg_Is_Library_Level_Local_Name (Arg1);
27388 Ent := Entity (Get_Pragma_Arg (Arg1));
27390 if Rep_Item_Too_Early (Ent, N) then
27391 return;
27392 else
27393 Ent := Underlying_Type (Ent);
27394 end if;
27396 -- The pragma applies to entities with addresses
27398 if Is_Type (Ent) then
27399 Error_Pragma ("pragma applies to objects and subprograms");
27400 end if;
27402 -- The only processing required is to link this item on to the
27403 -- list of rep items for the given entity. This is accomplished
27404 -- by the call to Rep_Item_Too_Late (when no error is detected
27405 -- and False is returned).
27407 if Rep_Item_Too_Late (Ent, N) then
27408 return;
27409 else
27410 Set_Has_Gigi_Rep_Item (Ent);
27411 end if;
27412 end Weak_External;
27414 -----------------------------
27415 -- Wide_Character_Encoding --
27416 -----------------------------
27418 -- pragma Wide_Character_Encoding (IDENTIFIER);
27420 when Pragma_Wide_Character_Encoding =>
27421 GNAT_Pragma;
27423 -- Nothing to do, handled in parser. Note that we do not enforce
27424 -- configuration pragma placement, this pragma can appear at any
27425 -- place in the source, allowing mixed encodings within a single
27426 -- source program.
27428 null;
27430 --------------------
27431 -- Unknown_Pragma --
27432 --------------------
27434 -- Should be impossible, since the case of an unknown pragma is
27435 -- separately processed before the case statement is entered.
27437 when Unknown_Pragma =>
27438 raise Program_Error;
27439 end case;
27441 -- AI05-0144: detect dangerous order dependence. Disabled for now,
27442 -- until AI is formally approved.
27444 -- Check_Order_Dependence;
27446 exception
27447 when Pragma_Exit => null;
27448 end Analyze_Pragma;
27450 --------------------------------
27451 -- Analyze_Pragmas_If_Present --
27452 --------------------------------
27454 procedure Analyze_Pragmas_If_Present (Decl : Node_Id; Id : Pragma_Id) is
27455 Prag : Node_Id;
27456 begin
27457 if Nkind (Parent (Decl)) = N_Compilation_Unit then
27458 Prag := First (Pragmas_After (Aux_Decls_Node (Parent (Decl))));
27459 else
27460 pragma Assert (Is_List_Member (Decl));
27461 Prag := Next (Decl);
27462 end if;
27464 if Present (Prag) then
27465 Analyze_If_Present_Internal (Prag, Id, Included => True);
27466 end if;
27467 end Analyze_Pragmas_If_Present;
27469 ---------------------------------------------
27470 -- Analyze_Pre_Post_Condition_In_Decl_Part --
27471 ---------------------------------------------
27473 -- WARNING: This routine manages Ghost regions. Return statements must be
27474 -- replaced by gotos which jump to the end of the routine and restore the
27475 -- Ghost mode.
27477 procedure Analyze_Pre_Post_Condition_In_Decl_Part
27478 (N : Node_Id;
27479 Freeze_Id : Entity_Id := Empty)
27481 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
27482 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
27484 Disp_Typ : Entity_Id;
27485 -- The dispatching type of the subprogram subject to the pre- or
27486 -- postcondition.
27488 function Check_References (Nod : Node_Id) return Traverse_Result;
27489 -- Check that expression Nod does not mention non-primitives of the
27490 -- type, global objects of the type, or other illegalities described
27491 -- and implied by AI12-0113.
27493 ----------------------
27494 -- Check_References --
27495 ----------------------
27497 function Check_References (Nod : Node_Id) return Traverse_Result is
27498 begin
27499 if Nkind (Nod) = N_Function_Call
27500 and then Is_Entity_Name (Name (Nod))
27501 then
27502 declare
27503 Func : constant Entity_Id := Entity (Name (Nod));
27504 Form : Entity_Id;
27506 begin
27507 -- An operation of the type must be a primitive
27509 if No (Find_Dispatching_Type (Func)) then
27510 Form := First_Formal (Func);
27511 while Present (Form) loop
27512 if Etype (Form) = Disp_Typ then
27513 Error_Msg_NE
27514 ("operation in class-wide condition must be "
27515 & "primitive of &", Nod, Disp_Typ);
27516 end if;
27518 Next_Formal (Form);
27519 end loop;
27521 -- A return object of the type is illegal as well
27523 if Etype (Func) = Disp_Typ
27524 or else Etype (Func) = Class_Wide_Type (Disp_Typ)
27525 then
27526 Error_Msg_NE
27527 ("operation in class-wide condition must be primitive "
27528 & "of &", Nod, Disp_Typ);
27529 end if;
27530 end if;
27531 end;
27533 elsif Is_Entity_Name (Nod)
27534 and then
27535 (Etype (Nod) = Disp_Typ
27536 or else Etype (Nod) = Class_Wide_Type (Disp_Typ))
27537 and then Ekind (Entity (Nod)) in E_Constant | E_Variable
27538 then
27539 Error_Msg_NE
27540 ("object in class-wide condition must be formal of type &",
27541 Nod, Disp_Typ);
27543 elsif Nkind (Nod) = N_Explicit_Dereference
27544 and then (Etype (Nod) = Disp_Typ
27545 or else Etype (Nod) = Class_Wide_Type (Disp_Typ))
27546 and then (not Is_Entity_Name (Prefix (Nod))
27547 or else not Is_Formal (Entity (Prefix (Nod))))
27548 then
27549 Error_Msg_NE
27550 ("operation in class-wide condition must be primitive of &",
27551 Nod, Disp_Typ);
27552 end if;
27554 return OK;
27555 end Check_References;
27557 procedure Check_Class_Wide_Condition is
27558 new Traverse_Proc (Check_References);
27560 -- Local variables
27562 Expr : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
27564 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
27565 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
27566 -- Save the Ghost-related attributes to restore on exit
27568 Errors : Nat;
27569 Restore_Scope : Boolean := False;
27571 -- Start of processing for Analyze_Pre_Post_Condition_In_Decl_Part
27573 begin
27574 -- Do not analyze the pragma multiple times
27576 if Is_Analyzed_Pragma (N) then
27577 return;
27578 end if;
27580 -- Set the Ghost mode in effect from the pragma. Due to the delayed
27581 -- analysis of the pragma, the Ghost mode at point of declaration and
27582 -- point of analysis may not necessarily be the same. Use the mode in
27583 -- effect at the point of declaration.
27585 Set_Ghost_Mode (N);
27587 -- Ensure that the subprogram and its formals are visible when analyzing
27588 -- the expression of the pragma.
27590 if not In_Open_Scopes (Spec_Id) then
27591 Restore_Scope := True;
27593 if Is_Generic_Subprogram (Spec_Id) then
27594 Push_Scope (Spec_Id);
27595 Install_Generic_Formals (Spec_Id);
27596 elsif Is_Access_Subprogram_Type (Spec_Id) then
27597 Push_Scope (Designated_Type (Spec_Id));
27598 Install_Formals (Designated_Type (Spec_Id));
27599 else
27600 Push_Scope (Spec_Id);
27601 Install_Formals (Spec_Id);
27602 end if;
27603 end if;
27605 Errors := Serious_Errors_Detected;
27606 Preanalyze_Assert_Expression (Expr, Standard_Boolean);
27608 -- Emit a clarification message when the expression contains at least
27609 -- one undefined reference, possibly due to contract freezing.
27611 if Errors /= Serious_Errors_Detected
27612 and then Present (Freeze_Id)
27613 and then Has_Undefined_Reference (Expr)
27614 then
27615 Contract_Freeze_Error (Spec_Id, Freeze_Id);
27616 end if;
27618 if Class_Present (N) then
27620 -- Verify that a class-wide condition is legal, i.e. the operation is
27621 -- a primitive of a tagged type.
27623 if not Is_Dispatching_Operation (Spec_Id) then
27624 Error_Msg_Name_1 := Original_Aspect_Pragma_Name (N);
27626 if From_Aspect_Specification (N) then
27627 Error_Msg_N
27628 ("aspect % can only be specified for a primitive operation "
27629 & "of a tagged type", Corresponding_Aspect (N));
27631 -- The pragma is a source construct
27633 else
27634 Error_Msg_N
27635 ("pragma % can only be specified for a primitive operation "
27636 & "of a tagged type", N);
27637 end if;
27639 -- Remaining semantic checks require a full tree traversal
27641 else
27642 Disp_Typ := Find_Dispatching_Type (Spec_Id);
27643 Check_Class_Wide_Condition (Expr);
27644 end if;
27646 end if;
27648 if Restore_Scope then
27649 End_Scope;
27650 end if;
27652 -- Currently it is not possible to inline pre/postconditions on a
27653 -- subprogram subject to pragma Inline_Always.
27655 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
27656 Set_Is_Analyzed_Pragma (N);
27658 Restore_Ghost_Region (Saved_GM, Saved_IGR);
27659 end Analyze_Pre_Post_Condition_In_Decl_Part;
27661 ------------------------------------------
27662 -- Analyze_Refined_Depends_In_Decl_Part --
27663 ------------------------------------------
27665 procedure Analyze_Refined_Depends_In_Decl_Part (N : Node_Id) is
27666 procedure Check_Dependency_Clause
27667 (Spec_Id : Entity_Id;
27668 Dep_Clause : Node_Id;
27669 Dep_States : Elist_Id;
27670 Refinements : List_Id;
27671 Matched_Items : in out Elist_Id);
27672 -- Try to match a single dependency clause Dep_Clause against one or
27673 -- more refinement clauses found in list Refinements. Each successful
27674 -- match eliminates at least one refinement clause from Refinements.
27675 -- Spec_Id denotes the entity of the related subprogram. Dep_States
27676 -- denotes the entities of all abstract states which appear in pragma
27677 -- Depends. Matched_Items contains the entities of all successfully
27678 -- matched items found in pragma Depends.
27680 procedure Check_Output_States
27681 (Spec_Inputs : Elist_Id;
27682 Spec_Outputs : Elist_Id;
27683 Body_Inputs : Elist_Id;
27684 Body_Outputs : Elist_Id);
27685 -- Determine whether pragma Depends contains an output state with a
27686 -- visible refinement and if so, ensure that pragma Refined_Depends
27687 -- mentions all its constituents as outputs. Spec_Inputs and
27688 -- Spec_Outputs denote the inputs and outputs of the subprogram spec
27689 -- synthesized from pragma Depends. Body_Inputs and Body_Outputs denote
27690 -- the inputs and outputs of the subprogram body synthesized from pragma
27691 -- Refined_Depends.
27693 function Collect_States (Clauses : List_Id) return Elist_Id;
27694 -- Given a normalized list of dependencies obtained from calling
27695 -- Normalize_Clauses, return a list containing the entities of all
27696 -- states appearing in dependencies. It helps in checking refinements
27697 -- involving a state and a corresponding constituent which is not a
27698 -- direct constituent of the state.
27700 procedure Normalize_Clauses (Clauses : List_Id);
27701 -- Given a list of dependence or refinement clauses Clauses, normalize
27702 -- each clause by creating multiple dependencies with exactly one input
27703 -- and one output.
27705 procedure Remove_Extra_Clauses
27706 (Clauses : List_Id;
27707 Matched_Items : Elist_Id);
27708 -- Given a list of refinement clauses Clauses, remove all clauses whose
27709 -- inputs and/or outputs have been previously matched. See the body for
27710 -- all special cases. Matched_Items contains the entities of all matched
27711 -- items found in pragma Depends.
27713 procedure Report_Extra_Clauses (Clauses : List_Id);
27714 -- Emit an error for each extra clause found in list Clauses
27716 -----------------------------
27717 -- Check_Dependency_Clause --
27718 -----------------------------
27720 procedure Check_Dependency_Clause
27721 (Spec_Id : Entity_Id;
27722 Dep_Clause : Node_Id;
27723 Dep_States : Elist_Id;
27724 Refinements : List_Id;
27725 Matched_Items : in out Elist_Id)
27727 Dep_Input : constant Node_Id := Expression (Dep_Clause);
27728 Dep_Output : constant Node_Id := First (Choices (Dep_Clause));
27730 function Is_Already_Matched (Dep_Item : Node_Id) return Boolean;
27731 -- Determine whether dependency item Dep_Item has been matched in a
27732 -- previous clause.
27734 function Is_In_Out_State_Clause return Boolean;
27735 -- Determine whether dependence clause Dep_Clause denotes an abstract
27736 -- state that depends on itself (State => State).
27738 function Is_Null_Refined_State (Item : Node_Id) return Boolean;
27739 -- Determine whether item Item denotes an abstract state with visible
27740 -- null refinement.
27742 procedure Match_Items
27743 (Dep_Item : Node_Id;
27744 Ref_Item : Node_Id;
27745 Matched : out Boolean);
27746 -- Try to match dependence item Dep_Item against refinement item
27747 -- Ref_Item. To match against a possible null refinement (see 2, 9),
27748 -- set Ref_Item to Empty. Flag Matched is set to True when one of
27749 -- the following conformance scenarios is in effect:
27750 -- 1) Both items denote null
27751 -- 2) Dep_Item denotes null and Ref_Item is Empty (special case)
27752 -- 3) Both items denote attribute 'Result
27753 -- 4) Both items denote the same object
27754 -- 5) Both items denote the same formal parameter
27755 -- 6) Both items denote the same current instance of a type
27756 -- 7) Both items denote the same discriminant
27757 -- 8) Dep_Item is an abstract state with visible null refinement
27758 -- and Ref_Item denotes null.
27759 -- 9) Dep_Item is an abstract state with visible null refinement
27760 -- and Ref_Item is Empty (special case).
27761 -- 10) Dep_Item is an abstract state with full or partial visible
27762 -- non-null refinement and Ref_Item denotes one of its
27763 -- constituents.
27764 -- 11) Dep_Item is an abstract state without a full visible
27765 -- refinement and Ref_Item denotes the same state.
27766 -- When scenario 10 is in effect, the entity of the abstract state
27767 -- denoted by Dep_Item is added to list Refined_States.
27769 procedure Record_Item (Item_Id : Entity_Id);
27770 -- Store the entity of an item denoted by Item_Id in Matched_Items
27772 ------------------------
27773 -- Is_Already_Matched --
27774 ------------------------
27776 function Is_Already_Matched (Dep_Item : Node_Id) return Boolean is
27777 Item_Id : Entity_Id := Empty;
27779 begin
27780 -- When the dependency item denotes attribute 'Result, check for
27781 -- the entity of the related subprogram.
27783 if Is_Attribute_Result (Dep_Item) then
27784 Item_Id := Spec_Id;
27786 elsif Is_Entity_Name (Dep_Item) then
27787 Item_Id := Available_View (Entity_Of (Dep_Item));
27788 end if;
27790 return
27791 Present (Item_Id) and then Contains (Matched_Items, Item_Id);
27792 end Is_Already_Matched;
27794 ----------------------------
27795 -- Is_In_Out_State_Clause --
27796 ----------------------------
27798 function Is_In_Out_State_Clause return Boolean is
27799 Dep_Input_Id : Entity_Id;
27800 Dep_Output_Id : Entity_Id;
27802 begin
27803 -- Detect the following clause:
27804 -- State => State
27806 if Is_Entity_Name (Dep_Input)
27807 and then Is_Entity_Name (Dep_Output)
27808 then
27809 -- Handle abstract views generated for limited with clauses
27811 Dep_Input_Id := Available_View (Entity_Of (Dep_Input));
27812 Dep_Output_Id := Available_View (Entity_Of (Dep_Output));
27814 return
27815 Ekind (Dep_Input_Id) = E_Abstract_State
27816 and then Dep_Input_Id = Dep_Output_Id;
27817 else
27818 return False;
27819 end if;
27820 end Is_In_Out_State_Clause;
27822 ---------------------------
27823 -- Is_Null_Refined_State --
27824 ---------------------------
27826 function Is_Null_Refined_State (Item : Node_Id) return Boolean is
27827 Item_Id : Entity_Id;
27829 begin
27830 if Is_Entity_Name (Item) then
27832 -- Handle abstract views generated for limited with clauses
27834 Item_Id := Available_View (Entity_Of (Item));
27836 return
27837 Ekind (Item_Id) = E_Abstract_State
27838 and then Has_Null_Visible_Refinement (Item_Id);
27839 else
27840 return False;
27841 end if;
27842 end Is_Null_Refined_State;
27844 -----------------
27845 -- Match_Items --
27846 -----------------
27848 procedure Match_Items
27849 (Dep_Item : Node_Id;
27850 Ref_Item : Node_Id;
27851 Matched : out Boolean)
27853 Dep_Item_Id : Entity_Id;
27854 Ref_Item_Id : Entity_Id;
27856 begin
27857 -- Assume that the two items do not match
27859 Matched := False;
27861 -- A null matches null or Empty (special case)
27863 if Nkind (Dep_Item) = N_Null
27864 and then (No (Ref_Item) or else Nkind (Ref_Item) = N_Null)
27865 then
27866 Matched := True;
27868 -- Attribute 'Result matches attribute 'Result
27870 elsif Is_Attribute_Result (Dep_Item)
27871 and then Is_Attribute_Result (Ref_Item)
27872 then
27873 -- Put the entity of the related function on the list of
27874 -- matched items because attribute 'Result does not carry
27875 -- an entity similar to states and constituents.
27877 Record_Item (Spec_Id);
27878 Matched := True;
27880 -- Abstract states, current instances of concurrent types,
27881 -- discriminants, formal parameters and objects.
27883 elsif Is_Entity_Name (Dep_Item) then
27885 -- Handle abstract views generated for limited with clauses
27887 Dep_Item_Id := Available_View (Entity_Of (Dep_Item));
27889 if Ekind (Dep_Item_Id) = E_Abstract_State then
27891 -- An abstract state with visible null refinement matches
27892 -- null or Empty (special case).
27894 if Has_Null_Visible_Refinement (Dep_Item_Id)
27895 and then (No (Ref_Item) or else Nkind (Ref_Item) = N_Null)
27896 then
27897 Record_Item (Dep_Item_Id);
27898 Matched := True;
27900 -- An abstract state with visible non-null refinement
27901 -- matches one of its constituents, or itself for an
27902 -- abstract state with partial visible refinement.
27904 elsif Has_Non_Null_Visible_Refinement (Dep_Item_Id) then
27905 if Is_Entity_Name (Ref_Item) then
27906 Ref_Item_Id := Entity_Of (Ref_Item);
27908 if Ekind (Ref_Item_Id) in
27909 E_Abstract_State | E_Constant | E_Variable
27910 and then Present (Encapsulating_State (Ref_Item_Id))
27911 and then Find_Encapsulating_State
27912 (Dep_States, Ref_Item_Id) = Dep_Item_Id
27913 then
27914 Record_Item (Dep_Item_Id);
27915 Matched := True;
27917 elsif not Has_Visible_Refinement (Dep_Item_Id)
27918 and then Ref_Item_Id = Dep_Item_Id
27919 then
27920 Record_Item (Dep_Item_Id);
27921 Matched := True;
27922 end if;
27923 end if;
27925 -- An abstract state without a visible refinement matches
27926 -- itself.
27928 elsif Is_Entity_Name (Ref_Item)
27929 and then Entity_Of (Ref_Item) = Dep_Item_Id
27930 then
27931 Record_Item (Dep_Item_Id);
27932 Matched := True;
27933 end if;
27935 -- A current instance of a concurrent type, discriminant,
27936 -- formal parameter or an object matches itself.
27938 elsif Is_Entity_Name (Ref_Item)
27939 and then Entity_Of (Ref_Item) = Dep_Item_Id
27940 then
27941 Record_Item (Dep_Item_Id);
27942 Matched := True;
27943 end if;
27944 end if;
27945 end Match_Items;
27947 -----------------
27948 -- Record_Item --
27949 -----------------
27951 procedure Record_Item (Item_Id : Entity_Id) is
27952 begin
27953 if No (Matched_Items) then
27954 Matched_Items := New_Elmt_List;
27955 end if;
27957 Append_Unique_Elmt (Item_Id, Matched_Items);
27958 end Record_Item;
27960 -- Local variables
27962 Clause_Matched : Boolean := False;
27963 Dummy : Boolean := False;
27964 Inputs_Match : Boolean;
27965 Next_Ref_Clause : Node_Id;
27966 Outputs_Match : Boolean;
27967 Ref_Clause : Node_Id;
27968 Ref_Input : Node_Id;
27969 Ref_Output : Node_Id;
27971 -- Start of processing for Check_Dependency_Clause
27973 begin
27974 -- Examine all refinement clauses and compare them against the
27975 -- dependence clause.
27977 Ref_Clause := First (Refinements);
27978 while Present (Ref_Clause) loop
27979 Next_Ref_Clause := Next (Ref_Clause);
27981 -- Obtain the attributes of the current refinement clause
27983 Ref_Input := Expression (Ref_Clause);
27984 Ref_Output := First (Choices (Ref_Clause));
27986 -- The current refinement clause matches the dependence clause
27987 -- when both outputs match and both inputs match. See routine
27988 -- Match_Items for all possible conformance scenarios.
27990 -- Depends Dep_Output => Dep_Input
27991 -- ^ ^
27992 -- match ? match ?
27993 -- v v
27994 -- Refined_Depends Ref_Output => Ref_Input
27996 Match_Items
27997 (Dep_Item => Dep_Input,
27998 Ref_Item => Ref_Input,
27999 Matched => Inputs_Match);
28001 Match_Items
28002 (Dep_Item => Dep_Output,
28003 Ref_Item => Ref_Output,
28004 Matched => Outputs_Match);
28006 -- An In_Out state clause may be matched against a refinement with
28007 -- a null input or null output as long as the non-null side of the
28008 -- relation contains a valid constituent of the In_Out_State.
28010 if Is_In_Out_State_Clause then
28012 -- Depends => (State => State)
28013 -- Refined_Depends => (null => Constit) -- OK
28015 if Inputs_Match
28016 and then not Outputs_Match
28017 and then Nkind (Ref_Output) = N_Null
28018 then
28019 Outputs_Match := True;
28020 end if;
28022 -- Depends => (State => State)
28023 -- Refined_Depends => (Constit => null) -- OK
28025 if not Inputs_Match
28026 and then Outputs_Match
28027 and then Nkind (Ref_Input) = N_Null
28028 then
28029 Inputs_Match := True;
28030 end if;
28031 end if;
28033 -- The current refinement clause is legally constructed following
28034 -- the rules in SPARK RM 7.2.5, therefore it can be removed from
28035 -- the pool of candidates. The search continues because a single
28036 -- dependence clause may have multiple matching refinements.
28038 if Inputs_Match and Outputs_Match then
28039 Clause_Matched := True;
28040 Remove (Ref_Clause);
28041 end if;
28043 Ref_Clause := Next_Ref_Clause;
28044 end loop;
28046 -- Depending on the order or composition of refinement clauses, an
28047 -- In_Out state clause may not be directly refinable.
28049 -- Refined_State => (State => (Constit_1, Constit_2))
28050 -- Depends => ((Output, State) => (Input, State))
28051 -- Refined_Depends => (Constit_1 => Input, Output => Constit_2)
28053 -- Matching normalized clause (State => State) fails because there is
28054 -- no direct refinement capable of satisfying this relation. Another
28055 -- similar case arises when clauses (Constit_1 => Input) and (Output
28056 -- => Constit_2) are matched first, leaving no candidates for clause
28057 -- (State => State). Both scenarios are legal as long as one of the
28058 -- previous clauses mentioned a valid constituent of State.
28060 if not Clause_Matched
28061 and then Is_In_Out_State_Clause
28062 and then Is_Already_Matched (Dep_Input)
28063 then
28064 Clause_Matched := True;
28065 end if;
28067 -- A clause where the input is an abstract state with visible null
28068 -- refinement or a 'Result attribute is implicitly matched when the
28069 -- output has already been matched in a previous clause.
28071 -- Refined_State => (State => null)
28072 -- Depends => (Output => State) -- implicitly OK
28073 -- Refined_Depends => (Output => ...)
28074 -- Depends => (...'Result => State) -- implicitly OK
28075 -- Refined_Depends => (...'Result => ...)
28077 if not Clause_Matched
28078 and then Is_Null_Refined_State (Dep_Input)
28079 and then Is_Already_Matched (Dep_Output)
28080 then
28081 Clause_Matched := True;
28082 end if;
28084 -- A clause where the output is an abstract state with visible null
28085 -- refinement is implicitly matched when the input has already been
28086 -- matched in a previous clause.
28088 -- Refined_State => (State => null)
28089 -- Depends => (State => Input) -- implicitly OK
28090 -- Refined_Depends => (... => Input)
28092 if not Clause_Matched
28093 and then Is_Null_Refined_State (Dep_Output)
28094 and then Is_Already_Matched (Dep_Input)
28095 then
28096 Clause_Matched := True;
28097 end if;
28099 -- At this point either all refinement clauses have been examined or
28100 -- pragma Refined_Depends contains a solitary null. Only an abstract
28101 -- state with null refinement can possibly match these cases.
28103 -- Refined_State => (State => null)
28104 -- Depends => (State => null)
28105 -- Refined_Depends => null -- OK
28107 if not Clause_Matched then
28108 Match_Items
28109 (Dep_Item => Dep_Input,
28110 Ref_Item => Empty,
28111 Matched => Inputs_Match);
28113 Match_Items
28114 (Dep_Item => Dep_Output,
28115 Ref_Item => Empty,
28116 Matched => Outputs_Match);
28118 Clause_Matched := Inputs_Match and Outputs_Match;
28119 end if;
28121 -- If the contents of Refined_Depends are legal, then the current
28122 -- dependence clause should be satisfied either by an explicit match
28123 -- or by one of the special cases.
28125 if not Clause_Matched then
28126 SPARK_Msg_NE
28127 (Fix_Msg (Spec_Id, "dependence clause of subprogram & has no "
28128 & "matching refinement in body"), Dep_Clause, Spec_Id);
28129 end if;
28130 end Check_Dependency_Clause;
28132 -------------------------
28133 -- Check_Output_States --
28134 -------------------------
28136 procedure Check_Output_States
28137 (Spec_Inputs : Elist_Id;
28138 Spec_Outputs : Elist_Id;
28139 Body_Inputs : Elist_Id;
28140 Body_Outputs : Elist_Id)
28142 procedure Check_Constituent_Usage (State_Id : Entity_Id);
28143 -- Determine whether all constituents of state State_Id with full
28144 -- visible refinement are used as outputs in pragma Refined_Depends.
28145 -- Emit an error if this is not the case (SPARK RM 7.2.4(5)).
28147 -----------------------------
28148 -- Check_Constituent_Usage --
28149 -----------------------------
28151 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
28152 Constits : constant Elist_Id :=
28153 Partial_Refinement_Constituents (State_Id);
28154 Constit_Elmt : Elmt_Id;
28155 Constit_Id : Entity_Id;
28156 Only_Partial : constant Boolean :=
28157 not Has_Visible_Refinement (State_Id);
28158 Posted : Boolean := False;
28160 begin
28161 if Present (Constits) then
28162 Constit_Elmt := First_Elmt (Constits);
28163 while Present (Constit_Elmt) loop
28164 Constit_Id := Node (Constit_Elmt);
28166 -- Issue an error when a constituent of State_Id is used,
28167 -- and State_Id has only partial visible refinement
28168 -- (SPARK RM 7.2.4(3d)).
28170 if Only_Partial then
28171 if (Present (Body_Inputs)
28172 and then Appears_In (Body_Inputs, Constit_Id))
28173 or else
28174 (Present (Body_Outputs)
28175 and then Appears_In (Body_Outputs, Constit_Id))
28176 then
28177 Error_Msg_Name_1 := Chars (State_Id);
28178 SPARK_Msg_NE
28179 ("constituent & of state % cannot be used in "
28180 & "dependence refinement", N, Constit_Id);
28181 Error_Msg_Name_1 := Chars (State_Id);
28182 SPARK_Msg_N ("\use state % instead", N);
28183 end if;
28185 -- The constituent acts as an input (SPARK RM 7.2.5(3))
28187 elsif Present (Body_Inputs)
28188 and then Appears_In (Body_Inputs, Constit_Id)
28189 then
28190 Error_Msg_Name_1 := Chars (State_Id);
28191 SPARK_Msg_NE
28192 ("constituent & of state % must act as output in "
28193 & "dependence refinement", N, Constit_Id);
28195 -- The constituent is altogether missing (SPARK RM 7.2.5(3))
28197 elsif No (Body_Outputs)
28198 or else not Appears_In (Body_Outputs, Constit_Id)
28199 then
28200 if not Posted then
28201 Posted := True;
28202 SPARK_Msg_NE
28203 ("output state & must be replaced by all its "
28204 & "constituents in dependence refinement",
28205 N, State_Id);
28206 end if;
28208 SPARK_Msg_NE
28209 ("\constituent & is missing in output list",
28210 N, Constit_Id);
28211 end if;
28213 Next_Elmt (Constit_Elmt);
28214 end loop;
28215 end if;
28216 end Check_Constituent_Usage;
28218 -- Local variables
28220 Item : Node_Id;
28221 Item_Elmt : Elmt_Id;
28222 Item_Id : Entity_Id;
28224 -- Start of processing for Check_Output_States
28226 begin
28227 -- Inspect the outputs of pragma Depends looking for a state with a
28228 -- visible refinement.
28230 if Present (Spec_Outputs) then
28231 Item_Elmt := First_Elmt (Spec_Outputs);
28232 while Present (Item_Elmt) loop
28233 Item := Node (Item_Elmt);
28235 -- Deal with the mixed nature of the input and output lists
28237 if Nkind (Item) = N_Defining_Identifier then
28238 Item_Id := Item;
28239 else
28240 Item_Id := Available_View (Entity_Of (Item));
28241 end if;
28243 if Ekind (Item_Id) = E_Abstract_State then
28245 -- The state acts as an input-output, skip it
28247 if Present (Spec_Inputs)
28248 and then Appears_In (Spec_Inputs, Item_Id)
28249 then
28250 null;
28252 -- Ensure that all of the constituents are utilized as
28253 -- outputs in pragma Refined_Depends.
28255 elsif Has_Non_Null_Visible_Refinement (Item_Id) then
28256 Check_Constituent_Usage (Item_Id);
28257 end if;
28258 end if;
28260 Next_Elmt (Item_Elmt);
28261 end loop;
28262 end if;
28263 end Check_Output_States;
28265 --------------------
28266 -- Collect_States --
28267 --------------------
28269 function Collect_States (Clauses : List_Id) return Elist_Id is
28270 procedure Collect_State
28271 (Item : Node_Id;
28272 States : in out Elist_Id);
28273 -- Add the entity of Item to list States when it denotes to a state
28275 -------------------
28276 -- Collect_State --
28277 -------------------
28279 procedure Collect_State
28280 (Item : Node_Id;
28281 States : in out Elist_Id)
28283 Id : Entity_Id;
28285 begin
28286 if Is_Entity_Name (Item) then
28287 Id := Entity_Of (Item);
28289 if Ekind (Id) = E_Abstract_State then
28290 if No (States) then
28291 States := New_Elmt_List;
28292 end if;
28294 Append_Unique_Elmt (Id, States);
28295 end if;
28296 end if;
28297 end Collect_State;
28299 -- Local variables
28301 Clause : Node_Id;
28302 Input : Node_Id;
28303 Output : Node_Id;
28304 States : Elist_Id := No_Elist;
28306 -- Start of processing for Collect_States
28308 begin
28309 Clause := First (Clauses);
28310 while Present (Clause) loop
28311 Input := Expression (Clause);
28312 Output := First (Choices (Clause));
28314 Collect_State (Input, States);
28315 Collect_State (Output, States);
28317 Next (Clause);
28318 end loop;
28320 return States;
28321 end Collect_States;
28323 -----------------------
28324 -- Normalize_Clauses --
28325 -----------------------
28327 procedure Normalize_Clauses (Clauses : List_Id) is
28328 procedure Normalize_Inputs (Clause : Node_Id);
28329 -- Normalize clause Clause by creating multiple clauses for each
28330 -- input item of Clause. It is assumed that Clause has exactly one
28331 -- output. The transformation is as follows:
28333 -- Output => (Input_1, Input_2) -- original
28335 -- Output => Input_1 -- normalizations
28336 -- Output => Input_2
28338 procedure Normalize_Outputs (Clause : Node_Id);
28339 -- Normalize clause Clause by creating multiple clause for each
28340 -- output item of Clause. The transformation is as follows:
28342 -- (Output_1, Output_2) => Input -- original
28344 -- Output_1 => Input -- normalization
28345 -- Output_2 => Input
28347 ----------------------
28348 -- Normalize_Inputs --
28349 ----------------------
28351 procedure Normalize_Inputs (Clause : Node_Id) is
28352 Inputs : constant Node_Id := Expression (Clause);
28353 Loc : constant Source_Ptr := Sloc (Clause);
28354 Output : constant List_Id := Choices (Clause);
28355 Last_Input : Node_Id;
28356 Input : Node_Id;
28357 New_Clause : Node_Id;
28358 Next_Input : Node_Id;
28360 begin
28361 -- Normalization is performed only when the original clause has
28362 -- more than one input. Multiple inputs appear as an aggregate.
28364 if Nkind (Inputs) = N_Aggregate then
28365 Last_Input := Last (Expressions (Inputs));
28367 -- Create a new clause for each input
28369 Input := First (Expressions (Inputs));
28370 while Present (Input) loop
28371 Next_Input := Next (Input);
28373 -- Unhook the current input from the original input list
28374 -- because it will be relocated to a new clause.
28376 Remove (Input);
28378 -- Special processing for the last input. At this point the
28379 -- original aggregate has been stripped down to one element.
28380 -- Replace the aggregate by the element itself.
28382 if Input = Last_Input then
28383 Rewrite (Inputs, Input);
28385 -- Generate a clause of the form:
28386 -- Output => Input
28388 else
28389 New_Clause :=
28390 Make_Component_Association (Loc,
28391 Choices => New_Copy_List_Tree (Output),
28392 Expression => Input);
28394 -- The new clause contains replicated content that has
28395 -- already been analyzed, mark the clause as analyzed.
28397 Set_Analyzed (New_Clause);
28398 Insert_After (Clause, New_Clause);
28399 end if;
28401 Input := Next_Input;
28402 end loop;
28403 end if;
28404 end Normalize_Inputs;
28406 -----------------------
28407 -- Normalize_Outputs --
28408 -----------------------
28410 procedure Normalize_Outputs (Clause : Node_Id) is
28411 Inputs : constant Node_Id := Expression (Clause);
28412 Loc : constant Source_Ptr := Sloc (Clause);
28413 Outputs : constant Node_Id := First (Choices (Clause));
28414 Last_Output : Node_Id;
28415 New_Clause : Node_Id;
28416 Next_Output : Node_Id;
28417 Output : Node_Id;
28419 begin
28420 -- Multiple outputs appear as an aggregate. Nothing to do when
28421 -- the clause has exactly one output.
28423 if Nkind (Outputs) = N_Aggregate then
28424 Last_Output := Last (Expressions (Outputs));
28426 -- Create a clause for each output. Note that each time a new
28427 -- clause is created, the original output list slowly shrinks
28428 -- until there is one item left.
28430 Output := First (Expressions (Outputs));
28431 while Present (Output) loop
28432 Next_Output := Next (Output);
28434 -- Unhook the output from the original output list as it
28435 -- will be relocated to a new clause.
28437 Remove (Output);
28439 -- Special processing for the last output. At this point
28440 -- the original aggregate has been stripped down to one
28441 -- element. Replace the aggregate by the element itself.
28443 if Output = Last_Output then
28444 Rewrite (Outputs, Output);
28446 else
28447 -- Generate a clause of the form:
28448 -- (Output => Inputs)
28450 New_Clause :=
28451 Make_Component_Association (Loc,
28452 Choices => New_List (Output),
28453 Expression => New_Copy_Tree (Inputs));
28455 -- The new clause contains replicated content that has
28456 -- already been analyzed. There is not need to reanalyze
28457 -- them.
28459 Set_Analyzed (New_Clause);
28460 Insert_After (Clause, New_Clause);
28461 end if;
28463 Output := Next_Output;
28464 end loop;
28465 end if;
28466 end Normalize_Outputs;
28468 -- Local variables
28470 Clause : Node_Id;
28472 -- Start of processing for Normalize_Clauses
28474 begin
28475 Clause := First (Clauses);
28476 while Present (Clause) loop
28477 Normalize_Outputs (Clause);
28478 Next (Clause);
28479 end loop;
28481 Clause := First (Clauses);
28482 while Present (Clause) loop
28483 Normalize_Inputs (Clause);
28484 Next (Clause);
28485 end loop;
28486 end Normalize_Clauses;
28488 --------------------------
28489 -- Remove_Extra_Clauses --
28490 --------------------------
28492 procedure Remove_Extra_Clauses
28493 (Clauses : List_Id;
28494 Matched_Items : Elist_Id)
28496 Clause : Node_Id;
28497 Input : Node_Id;
28498 Input_Id : Entity_Id;
28499 Next_Clause : Node_Id;
28500 Output : Node_Id;
28501 State_Id : Entity_Id;
28503 begin
28504 Clause := First (Clauses);
28505 while Present (Clause) loop
28506 Next_Clause := Next (Clause);
28508 Input := Expression (Clause);
28509 Output := First (Choices (Clause));
28511 -- Recognize a clause of the form
28513 -- null => Input
28515 -- where Input is a constituent of a state which was already
28516 -- successfully matched. This clause must be removed because it
28517 -- simply indicates that some of the constituents of the state
28518 -- are not used.
28520 -- Refined_State => (State => (Constit_1, Constit_2))
28521 -- Depends => (Output => State)
28522 -- Refined_Depends => ((Output => Constit_1), -- State matched
28523 -- (null => Constit_2)) -- OK
28525 if Nkind (Output) = N_Null and then Is_Entity_Name (Input) then
28527 -- Handle abstract views generated for limited with clauses
28529 Input_Id := Available_View (Entity_Of (Input));
28531 -- The input must be a constituent of a state
28533 if Ekind (Input_Id) in
28534 E_Abstract_State | E_Constant | E_Variable
28535 and then Present (Encapsulating_State (Input_Id))
28536 then
28537 State_Id := Encapsulating_State (Input_Id);
28539 -- The state must have a non-null visible refinement and be
28540 -- matched in a previous clause.
28542 if Has_Non_Null_Visible_Refinement (State_Id)
28543 and then Contains (Matched_Items, State_Id)
28544 then
28545 Remove (Clause);
28546 end if;
28547 end if;
28549 -- Recognize a clause of the form
28551 -- Output => null
28553 -- where Output is an arbitrary item. This clause must be removed
28554 -- because a null input legitimately matches anything.
28556 elsif Nkind (Input) = N_Null then
28557 Remove (Clause);
28558 end if;
28560 Clause := Next_Clause;
28561 end loop;
28562 end Remove_Extra_Clauses;
28564 --------------------------
28565 -- Report_Extra_Clauses --
28566 --------------------------
28568 procedure Report_Extra_Clauses (Clauses : List_Id) is
28569 Clause : Node_Id;
28571 begin
28572 Clause := First (Clauses);
28573 while Present (Clause) loop
28574 SPARK_Msg_N
28575 ("unmatched or extra clause in dependence refinement", Clause);
28577 Next (Clause);
28578 end loop;
28579 end Report_Extra_Clauses;
28581 -- Local variables
28583 Body_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
28584 Body_Id : constant Entity_Id := Defining_Entity (Body_Decl);
28585 Errors : constant Nat := Serious_Errors_Detected;
28587 Clause : Node_Id;
28588 Deps : Node_Id;
28589 Dummy : Boolean;
28590 Refs : Node_Id;
28592 Body_Inputs : Elist_Id := No_Elist;
28593 Body_Outputs : Elist_Id := No_Elist;
28594 -- The inputs and outputs of the subprogram body synthesized from pragma
28595 -- Refined_Depends.
28597 Dependencies : List_Id := No_List;
28598 Depends : Node_Id;
28599 -- The corresponding Depends pragma along with its clauses
28601 Matched_Items : Elist_Id := No_Elist;
28602 -- A list containing the entities of all successfully matched items
28603 -- found in pragma Depends.
28605 Refinements : List_Id := No_List;
28606 -- The clauses of pragma Refined_Depends
28608 Spec_Id : Entity_Id;
28609 -- The entity of the subprogram subject to pragma Refined_Depends
28611 Spec_Inputs : Elist_Id := No_Elist;
28612 Spec_Outputs : Elist_Id := No_Elist;
28613 -- The inputs and outputs of the subprogram spec synthesized from pragma
28614 -- Depends.
28616 States : Elist_Id := No_Elist;
28617 -- A list containing the entities of all states whose constituents
28618 -- appear in pragma Depends.
28620 -- Start of processing for Analyze_Refined_Depends_In_Decl_Part
28622 begin
28623 -- Do not analyze the pragma multiple times
28625 if Is_Analyzed_Pragma (N) then
28626 return;
28627 end if;
28629 Spec_Id := Unique_Defining_Entity (Body_Decl);
28631 -- Use the anonymous object as the proper spec when Refined_Depends
28632 -- applies to the body of a single task type. The object carries the
28633 -- proper Chars as well as all non-refined versions of pragmas.
28635 if Is_Single_Concurrent_Type (Spec_Id) then
28636 Spec_Id := Anonymous_Object (Spec_Id);
28637 end if;
28639 Depends := Get_Pragma (Spec_Id, Pragma_Depends);
28641 -- Subprogram declarations lacks pragma Depends. Refined_Depends is
28642 -- rendered useless as there is nothing to refine (SPARK RM 7.2.5(2)).
28644 if No (Depends) then
28645 SPARK_Msg_NE
28646 (Fix_Msg (Spec_Id, "useless refinement, declaration of subprogram "
28647 & "& lacks aspect or pragma Depends"), N, Spec_Id);
28648 goto Leave;
28649 end if;
28651 Deps := Expression (Get_Argument (Depends, Spec_Id));
28653 -- A null dependency relation renders the refinement useless because it
28654 -- cannot possibly mention abstract states with visible refinement. Note
28655 -- that the inverse is not true as states may be refined to null
28656 -- (SPARK RM 7.2.5(2)).
28658 if Nkind (Deps) = N_Null then
28659 SPARK_Msg_NE
28660 (Fix_Msg (Spec_Id, "useless refinement, subprogram & does not "
28661 & "depend on abstract state with visible refinement"), N, Spec_Id);
28662 goto Leave;
28663 end if;
28665 -- Analyze Refined_Depends as if it behaved as a regular pragma Depends.
28666 -- This ensures that the categorization of all refined dependency items
28667 -- is consistent with their role.
28669 Analyze_Depends_In_Decl_Part (N);
28671 -- Do not perform these checks in an instance because they were already
28672 -- performed successfully in the generic template.
28674 if In_Instance then
28675 goto Leave;
28676 end if;
28678 -- Do not match dependencies against refinements if Refined_Depends is
28679 -- illegal to avoid emitting misleading error.
28681 if Serious_Errors_Detected = Errors then
28683 -- The related subprogram lacks pragma [Refined_]Global. Synthesize
28684 -- the inputs and outputs of the subprogram spec and body to verify
28685 -- the use of states with visible refinement and their constituents.
28687 if No (Get_Pragma (Spec_Id, Pragma_Global))
28688 or else No (Get_Pragma (Body_Id, Pragma_Refined_Global))
28689 then
28690 Collect_Subprogram_Inputs_Outputs
28691 (Subp_Id => Spec_Id,
28692 Synthesize => True,
28693 Subp_Inputs => Spec_Inputs,
28694 Subp_Outputs => Spec_Outputs,
28695 Global_Seen => Dummy);
28697 Collect_Subprogram_Inputs_Outputs
28698 (Subp_Id => Body_Id,
28699 Synthesize => True,
28700 Subp_Inputs => Body_Inputs,
28701 Subp_Outputs => Body_Outputs,
28702 Global_Seen => Dummy);
28704 -- For an output state with a visible refinement, ensure that all
28705 -- constituents appear as outputs in the dependency refinement.
28707 Check_Output_States
28708 (Spec_Inputs => Spec_Inputs,
28709 Spec_Outputs => Spec_Outputs,
28710 Body_Inputs => Body_Inputs,
28711 Body_Outputs => Body_Outputs);
28712 end if;
28714 -- Multiple dependency clauses appear as component associations of an
28715 -- aggregate. Note that the clauses are copied because the algorithm
28716 -- modifies them and this should not be visible in Depends.
28718 pragma Assert (Nkind (Deps) = N_Aggregate);
28719 Dependencies := New_Copy_List_Tree (Component_Associations (Deps));
28720 Normalize_Clauses (Dependencies);
28722 -- Gather all states which appear in Depends
28724 States := Collect_States (Dependencies);
28726 Refs := Expression (Get_Argument (N, Spec_Id));
28728 if Nkind (Refs) = N_Null then
28729 Refinements := No_List;
28731 -- Multiple dependency clauses appear as component associations of an
28732 -- aggregate. Note that the clauses are copied because the algorithm
28733 -- modifies them and this should not be visible in Refined_Depends.
28735 else pragma Assert (Nkind (Refs) = N_Aggregate);
28736 Refinements := New_Copy_List_Tree (Component_Associations (Refs));
28737 Normalize_Clauses (Refinements);
28738 end if;
28740 -- At this point the clauses of pragmas Depends and Refined_Depends
28741 -- have been normalized into simple dependencies between one output
28742 -- and one input. Examine all clauses of pragma Depends looking for
28743 -- matching clauses in pragma Refined_Depends.
28745 Clause := First (Dependencies);
28746 while Present (Clause) loop
28747 Check_Dependency_Clause
28748 (Spec_Id => Spec_Id,
28749 Dep_Clause => Clause,
28750 Dep_States => States,
28751 Refinements => Refinements,
28752 Matched_Items => Matched_Items);
28754 Next (Clause);
28755 end loop;
28757 -- Pragma Refined_Depends may contain multiple clarification clauses
28758 -- which indicate that certain constituents do not influence the data
28759 -- flow in any way. Such clauses must be removed as long as the state
28760 -- has been matched, otherwise they will be incorrectly flagged as
28761 -- unmatched.
28763 -- Refined_State => (State => (Constit_1, Constit_2))
28764 -- Depends => (Output => State)
28765 -- Refined_Depends => ((Output => Constit_1), -- State matched
28766 -- (null => Constit_2)) -- must be removed
28768 Remove_Extra_Clauses (Refinements, Matched_Items);
28770 if Serious_Errors_Detected = Errors then
28771 Report_Extra_Clauses (Refinements);
28772 end if;
28773 end if;
28775 <<Leave>>
28776 Set_Is_Analyzed_Pragma (N);
28777 end Analyze_Refined_Depends_In_Decl_Part;
28779 -----------------------------------------
28780 -- Analyze_Refined_Global_In_Decl_Part --
28781 -----------------------------------------
28783 procedure Analyze_Refined_Global_In_Decl_Part (N : Node_Id) is
28784 Global : Node_Id;
28785 -- The corresponding Global pragma
28787 Has_In_State : Boolean := False;
28788 Has_In_Out_State : Boolean := False;
28789 Has_Out_State : Boolean := False;
28790 Has_Proof_In_State : Boolean := False;
28791 -- These flags are set when the corresponding Global pragma has a state
28792 -- of mode Input, In_Out, Output or Proof_In respectively with a visible
28793 -- refinement.
28795 Has_Null_State : Boolean := False;
28796 -- This flag is set when the corresponding Global pragma has at least
28797 -- one state with a null refinement.
28799 In_Constits : Elist_Id := No_Elist;
28800 In_Out_Constits : Elist_Id := No_Elist;
28801 Out_Constits : Elist_Id := No_Elist;
28802 Proof_In_Constits : Elist_Id := No_Elist;
28803 -- These lists contain the entities of all Input, In_Out, Output and
28804 -- Proof_In constituents that appear in Refined_Global and participate
28805 -- in state refinement.
28807 In_Items : Elist_Id := No_Elist;
28808 In_Out_Items : Elist_Id := No_Elist;
28809 Out_Items : Elist_Id := No_Elist;
28810 Proof_In_Items : Elist_Id := No_Elist;
28811 -- These lists contain the entities of all Input, In_Out, Output and
28812 -- Proof_In items defined in the corresponding Global pragma.
28814 Repeat_Items : Elist_Id := No_Elist;
28815 -- A list of all global items without full visible refinement found
28816 -- in pragma Global. These states should be repeated in the global
28817 -- refinement (SPARK RM 7.2.4(3c)) unless they have a partial visible
28818 -- refinement, in which case they may be repeated (SPARK RM 7.2.4(3d)).
28820 Spec_Id : Entity_Id;
28821 -- The entity of the subprogram subject to pragma Refined_Global
28823 States : Elist_Id := No_Elist;
28824 -- A list of all states with full or partial visible refinement found in
28825 -- pragma Global.
28827 procedure Check_In_Out_States;
28828 -- Determine whether the corresponding Global pragma mentions In_Out
28829 -- states with visible refinement and if so, ensure that one of the
28830 -- following completions apply to the constituents of the state:
28831 -- 1) there is at least one constituent of mode In_Out
28832 -- 2) there is at least one Input and one Output constituent
28833 -- 3) not all constituents are present and one of them is of mode
28834 -- Output.
28835 -- This routine may remove elements from In_Constits, In_Out_Constits,
28836 -- Out_Constits and Proof_In_Constits.
28838 procedure Check_Input_States;
28839 -- Determine whether the corresponding Global pragma mentions Input
28840 -- states with visible refinement and if so, ensure that at least one of
28841 -- its constituents appears as an Input item in Refined_Global.
28842 -- This routine may remove elements from In_Constits, In_Out_Constits,
28843 -- Out_Constits and Proof_In_Constits.
28845 procedure Check_Output_States;
28846 -- Determine whether the corresponding Global pragma mentions Output
28847 -- states with visible refinement and if so, ensure that all of its
28848 -- constituents appear as Output items in Refined_Global.
28849 -- This routine may remove elements from In_Constits, In_Out_Constits,
28850 -- Out_Constits and Proof_In_Constits.
28852 procedure Check_Proof_In_States;
28853 -- Determine whether the corresponding Global pragma mentions Proof_In
28854 -- states with visible refinement and if so, ensure that at least one of
28855 -- its constituents appears as a Proof_In item in Refined_Global.
28856 -- This routine may remove elements from In_Constits, In_Out_Constits,
28857 -- Out_Constits and Proof_In_Constits.
28859 procedure Check_Refined_Global_List
28860 (List : Node_Id;
28861 Global_Mode : Name_Id := Name_Input);
28862 -- Verify the legality of a single global list declaration. Global_Mode
28863 -- denotes the current mode in effect.
28865 procedure Collect_Global_Items
28866 (List : Node_Id;
28867 Mode : Name_Id := Name_Input);
28868 -- Gather all Input, In_Out, Output and Proof_In items from node List
28869 -- and separate them in lists In_Items, In_Out_Items, Out_Items and
28870 -- Proof_In_Items. Flags Has_In_State, Has_In_Out_State, Has_Out_State
28871 -- and Has_Proof_In_State are set when there is at least one abstract
28872 -- state with full or partial visible refinement available in the
28873 -- corresponding mode. Flag Has_Null_State is set when at least state
28874 -- has a null refinement. Mode denotes the current global mode in
28875 -- effect.
28877 function Present_Then_Remove
28878 (List : Elist_Id;
28879 Item : Entity_Id) return Boolean;
28880 -- Search List for a particular entity Item. If Item has been found,
28881 -- remove it from List. This routine is used to strip lists In_Constits,
28882 -- In_Out_Constits and Out_Constits of valid constituents.
28884 procedure Present_Then_Remove (List : Elist_Id; Item : Entity_Id);
28885 -- Same as function Present_Then_Remove, but do not report the presence
28886 -- of Item in List.
28888 procedure Report_Extra_Constituents;
28889 -- Emit an error for each constituent found in lists In_Constits,
28890 -- In_Out_Constits and Out_Constits.
28892 procedure Report_Missing_Items;
28893 -- Emit an error for each global item not repeated found in list
28894 -- Repeat_Items.
28896 -------------------------
28897 -- Check_In_Out_States --
28898 -------------------------
28900 procedure Check_In_Out_States is
28901 procedure Check_Constituent_Usage (State_Id : Entity_Id);
28902 -- Determine whether one of the following coverage scenarios is in
28903 -- effect:
28904 -- 1) there is at least one constituent of mode In_Out or Output
28905 -- 2) there is at least one pair of constituents with modes Input
28906 -- and Output, or Proof_In and Output.
28907 -- 3) there is at least one constituent of mode Output and not all
28908 -- constituents are present.
28909 -- If this is not the case, emit an error (SPARK RM 7.2.4(5)).
28911 -----------------------------
28912 -- Check_Constituent_Usage --
28913 -----------------------------
28915 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
28916 Constits : constant Elist_Id :=
28917 Partial_Refinement_Constituents (State_Id);
28918 Constit_Elmt : Elmt_Id;
28919 Constit_Id : Entity_Id;
28920 Has_Missing : Boolean := False;
28921 In_Out_Seen : Boolean := False;
28922 Input_Seen : Boolean := False;
28923 Output_Seen : Boolean := False;
28924 Proof_In_Seen : Boolean := False;
28926 begin
28927 -- Process all the constituents of the state and note their modes
28928 -- within the global refinement.
28930 if Present (Constits) then
28931 Constit_Elmt := First_Elmt (Constits);
28932 while Present (Constit_Elmt) loop
28933 Constit_Id := Node (Constit_Elmt);
28935 if Present_Then_Remove (In_Constits, Constit_Id) then
28936 Input_Seen := True;
28938 elsif Present_Then_Remove (In_Out_Constits, Constit_Id) then
28939 In_Out_Seen := True;
28941 elsif Present_Then_Remove (Out_Constits, Constit_Id) then
28942 Output_Seen := True;
28944 elsif Present_Then_Remove (Proof_In_Constits, Constit_Id)
28945 then
28946 Proof_In_Seen := True;
28948 else
28949 Has_Missing := True;
28950 end if;
28952 Next_Elmt (Constit_Elmt);
28953 end loop;
28954 end if;
28956 -- An In_Out constituent is a valid completion
28958 if In_Out_Seen then
28959 null;
28961 -- A pair of one Input/Proof_In and one Output constituent is a
28962 -- valid completion.
28964 elsif (Input_Seen or Proof_In_Seen) and Output_Seen then
28965 null;
28967 elsif Output_Seen then
28969 -- A single Output constituent is a valid completion only when
28970 -- some of the other constituents are missing.
28972 if Has_Missing then
28973 null;
28975 -- Otherwise all constituents are of mode Output
28977 else
28978 SPARK_Msg_NE
28979 ("global refinement of state & must include at least one "
28980 & "constituent of mode `In_Out`, `Input`, or `Proof_In`",
28981 N, State_Id);
28982 end if;
28984 -- The state lacks a completion. When full refinement is visible,
28985 -- always emit an error (SPARK RM 7.2.4(3a)). When only partial
28986 -- refinement is visible, emit an error if the abstract state
28987 -- itself is not utilized (SPARK RM 7.2.4(3d)). In the case where
28988 -- both are utilized, Check_State_And_Constituent_Use. will issue
28989 -- the error.
28991 elsif not Input_Seen
28992 and then not In_Out_Seen
28993 and then not Output_Seen
28994 and then not Proof_In_Seen
28995 then
28996 if Has_Visible_Refinement (State_Id)
28997 or else Contains (Repeat_Items, State_Id)
28998 then
28999 SPARK_Msg_NE
29000 ("missing global refinement of state &", N, State_Id);
29001 end if;
29003 -- Otherwise the state has a malformed completion where at least
29004 -- one of the constituents has a different mode.
29006 else
29007 SPARK_Msg_NE
29008 ("global refinement of state & redefines the mode of its "
29009 & "constituents", N, State_Id);
29010 end if;
29011 end Check_Constituent_Usage;
29013 -- Local variables
29015 Item_Elmt : Elmt_Id;
29016 Item_Id : Entity_Id;
29018 -- Start of processing for Check_In_Out_States
29020 begin
29021 -- Inspect the In_Out items of the corresponding Global pragma
29022 -- looking for a state with a visible refinement.
29024 if Has_In_Out_State and then Present (In_Out_Items) then
29025 Item_Elmt := First_Elmt (In_Out_Items);
29026 while Present (Item_Elmt) loop
29027 Item_Id := Node (Item_Elmt);
29029 -- Ensure that one of the three coverage variants is satisfied
29031 if Ekind (Item_Id) = E_Abstract_State
29032 and then Has_Non_Null_Visible_Refinement (Item_Id)
29033 then
29034 Check_Constituent_Usage (Item_Id);
29035 end if;
29037 Next_Elmt (Item_Elmt);
29038 end loop;
29039 end if;
29040 end Check_In_Out_States;
29042 ------------------------
29043 -- Check_Input_States --
29044 ------------------------
29046 procedure Check_Input_States is
29047 procedure Check_Constituent_Usage (State_Id : Entity_Id);
29048 -- Determine whether at least one constituent of state State_Id with
29049 -- full or partial visible refinement is used and has mode Input.
29050 -- Ensure that the remaining constituents do not have In_Out or
29051 -- Output modes. Emit an error if this is not the case
29052 -- (SPARK RM 7.2.4(5)).
29054 -----------------------------
29055 -- Check_Constituent_Usage --
29056 -----------------------------
29058 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
29059 Constits : constant Elist_Id :=
29060 Partial_Refinement_Constituents (State_Id);
29061 Constit_Elmt : Elmt_Id;
29062 Constit_Id : Entity_Id;
29063 In_Seen : Boolean := False;
29065 begin
29066 if Present (Constits) then
29067 Constit_Elmt := First_Elmt (Constits);
29068 while Present (Constit_Elmt) loop
29069 Constit_Id := Node (Constit_Elmt);
29071 -- At least one of the constituents appears as an Input
29073 if Present_Then_Remove (In_Constits, Constit_Id) then
29074 In_Seen := True;
29076 -- A Proof_In constituent can refine an Input state as long
29077 -- as there is at least one Input constituent present.
29079 elsif Present_Then_Remove (Proof_In_Constits, Constit_Id)
29080 then
29081 null;
29083 -- The constituent appears in the global refinement, but has
29084 -- mode In_Out or Output (SPARK RM 7.2.4(5)).
29086 elsif Present_Then_Remove (In_Out_Constits, Constit_Id)
29087 or else Present_Then_Remove (Out_Constits, Constit_Id)
29088 then
29089 Error_Msg_Name_1 := Chars (State_Id);
29090 SPARK_Msg_NE
29091 ("constituent & of state % must have mode `Input` in "
29092 & "global refinement", N, Constit_Id);
29093 end if;
29095 Next_Elmt (Constit_Elmt);
29096 end loop;
29097 end if;
29099 -- Not one of the constituents appeared as Input. Always emit an
29100 -- error when the full refinement is visible (SPARK RM 7.2.4(3a)).
29101 -- When only partial refinement is visible, emit an error if the
29102 -- abstract state itself is not utilized (SPARK RM 7.2.4(3d)). In
29103 -- the case where both are utilized, an error will be issued in
29104 -- Check_State_And_Constituent_Use.
29106 if not In_Seen
29107 and then (Has_Visible_Refinement (State_Id)
29108 or else Contains (Repeat_Items, State_Id))
29109 then
29110 SPARK_Msg_NE
29111 ("global refinement of state & must include at least one "
29112 & "constituent of mode `Input`", N, State_Id);
29113 end if;
29114 end Check_Constituent_Usage;
29116 -- Local variables
29118 Item_Elmt : Elmt_Id;
29119 Item_Id : Entity_Id;
29121 -- Start of processing for Check_Input_States
29123 begin
29124 -- Inspect the Input items of the corresponding Global pragma looking
29125 -- for a state with a visible refinement.
29127 if Has_In_State and then Present (In_Items) then
29128 Item_Elmt := First_Elmt (In_Items);
29129 while Present (Item_Elmt) loop
29130 Item_Id := Node (Item_Elmt);
29132 -- When full refinement is visible, ensure that at least one of
29133 -- the constituents is utilized and is of mode Input. When only
29134 -- partial refinement is visible, ensure that either one of
29135 -- the constituents is utilized and is of mode Input, or the
29136 -- abstract state is repeated and no constituent is utilized.
29138 if Ekind (Item_Id) = E_Abstract_State
29139 and then Has_Non_Null_Visible_Refinement (Item_Id)
29140 then
29141 Check_Constituent_Usage (Item_Id);
29142 end if;
29144 Next_Elmt (Item_Elmt);
29145 end loop;
29146 end if;
29147 end Check_Input_States;
29149 -------------------------
29150 -- Check_Output_States --
29151 -------------------------
29153 procedure Check_Output_States is
29154 procedure Check_Constituent_Usage (State_Id : Entity_Id);
29155 -- Determine whether all constituents of state State_Id with full
29156 -- visible refinement are used and have mode Output. Emit an error
29157 -- if this is not the case (SPARK RM 7.2.4(5)).
29159 -----------------------------
29160 -- Check_Constituent_Usage --
29161 -----------------------------
29163 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
29164 Constits : constant Elist_Id :=
29165 Partial_Refinement_Constituents (State_Id);
29166 Only_Partial : constant Boolean :=
29167 not Has_Visible_Refinement (State_Id);
29168 Constit_Elmt : Elmt_Id;
29169 Constit_Id : Entity_Id;
29170 Posted : Boolean := False;
29172 begin
29173 if Present (Constits) then
29174 Constit_Elmt := First_Elmt (Constits);
29175 while Present (Constit_Elmt) loop
29176 Constit_Id := Node (Constit_Elmt);
29178 -- Issue an error when a constituent of State_Id is utilized
29179 -- and State_Id has only partial visible refinement
29180 -- (SPARK RM 7.2.4(3d)).
29182 if Only_Partial then
29183 if Present_Then_Remove (Out_Constits, Constit_Id)
29184 or else Present_Then_Remove (In_Constits, Constit_Id)
29185 or else
29186 Present_Then_Remove (In_Out_Constits, Constit_Id)
29187 or else
29188 Present_Then_Remove (Proof_In_Constits, Constit_Id)
29189 then
29190 Error_Msg_Name_1 := Chars (State_Id);
29191 SPARK_Msg_NE
29192 ("constituent & of state % cannot be used in global "
29193 & "refinement", N, Constit_Id);
29194 Error_Msg_Name_1 := Chars (State_Id);
29195 SPARK_Msg_N ("\use state % instead", N);
29196 end if;
29198 elsif Present_Then_Remove (Out_Constits, Constit_Id) then
29199 null;
29201 -- The constituent appears in the global refinement, but has
29202 -- mode Input, In_Out or Proof_In (SPARK RM 7.2.4(5)).
29204 elsif Present_Then_Remove (In_Constits, Constit_Id)
29205 or else Present_Then_Remove (In_Out_Constits, Constit_Id)
29206 or else Present_Then_Remove (Proof_In_Constits, Constit_Id)
29207 then
29208 Error_Msg_Name_1 := Chars (State_Id);
29209 SPARK_Msg_NE
29210 ("constituent & of state % must have mode `Output` in "
29211 & "global refinement", N, Constit_Id);
29213 -- The constituent is altogether missing (SPARK RM 7.2.5(3))
29215 else
29216 if not Posted then
29217 Posted := True;
29218 SPARK_Msg_NE
29219 ("`Output` state & must be replaced by all its "
29220 & "constituents in global refinement", N, State_Id);
29221 end if;
29223 SPARK_Msg_NE
29224 ("\constituent & is missing in output list",
29225 N, Constit_Id);
29226 end if;
29228 Next_Elmt (Constit_Elmt);
29229 end loop;
29230 end if;
29231 end Check_Constituent_Usage;
29233 -- Local variables
29235 Item_Elmt : Elmt_Id;
29236 Item_Id : Entity_Id;
29238 -- Start of processing for Check_Output_States
29240 begin
29241 -- Inspect the Output items of the corresponding Global pragma
29242 -- looking for a state with a visible refinement.
29244 if Has_Out_State and then Present (Out_Items) then
29245 Item_Elmt := First_Elmt (Out_Items);
29246 while Present (Item_Elmt) loop
29247 Item_Id := Node (Item_Elmt);
29249 -- When full refinement is visible, ensure that all of the
29250 -- constituents are utilized and they have mode Output. When
29251 -- only partial refinement is visible, ensure that no
29252 -- constituent is utilized.
29254 if Ekind (Item_Id) = E_Abstract_State
29255 and then Has_Non_Null_Visible_Refinement (Item_Id)
29256 then
29257 Check_Constituent_Usage (Item_Id);
29258 end if;
29260 Next_Elmt (Item_Elmt);
29261 end loop;
29262 end if;
29263 end Check_Output_States;
29265 ---------------------------
29266 -- Check_Proof_In_States --
29267 ---------------------------
29269 procedure Check_Proof_In_States is
29270 procedure Check_Constituent_Usage (State_Id : Entity_Id);
29271 -- Determine whether at least one constituent of state State_Id with
29272 -- full or partial visible refinement is used and has mode Proof_In.
29273 -- Ensure that the remaining constituents do not have Input, In_Out,
29274 -- or Output modes. Emit an error if this is not the case
29275 -- (SPARK RM 7.2.4(5)).
29277 -----------------------------
29278 -- Check_Constituent_Usage --
29279 -----------------------------
29281 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
29282 Constits : constant Elist_Id :=
29283 Partial_Refinement_Constituents (State_Id);
29284 Constit_Elmt : Elmt_Id;
29285 Constit_Id : Entity_Id;
29286 Proof_In_Seen : Boolean := False;
29288 begin
29289 if Present (Constits) then
29290 Constit_Elmt := First_Elmt (Constits);
29291 while Present (Constit_Elmt) loop
29292 Constit_Id := Node (Constit_Elmt);
29294 -- At least one of the constituents appears as Proof_In
29296 if Present_Then_Remove (Proof_In_Constits, Constit_Id) then
29297 Proof_In_Seen := True;
29299 -- The constituent appears in the global refinement, but has
29300 -- mode Input, In_Out or Output (SPARK RM 7.2.4(5)).
29302 elsif Present_Then_Remove (In_Constits, Constit_Id)
29303 or else Present_Then_Remove (In_Out_Constits, Constit_Id)
29304 or else Present_Then_Remove (Out_Constits, Constit_Id)
29305 then
29306 Error_Msg_Name_1 := Chars (State_Id);
29307 SPARK_Msg_NE
29308 ("constituent & of state % must have mode `Proof_In` "
29309 & "in global refinement", N, Constit_Id);
29310 end if;
29312 Next_Elmt (Constit_Elmt);
29313 end loop;
29314 end if;
29316 -- Not one of the constituents appeared as Proof_In. Always emit
29317 -- an error when full refinement is visible (SPARK RM 7.2.4(3a)).
29318 -- When only partial refinement is visible, emit an error if the
29319 -- abstract state itself is not utilized (SPARK RM 7.2.4(3d)). In
29320 -- the case where both are utilized, an error will be issued by
29321 -- Check_State_And_Constituent_Use.
29323 if not Proof_In_Seen
29324 and then (Has_Visible_Refinement (State_Id)
29325 or else Contains (Repeat_Items, State_Id))
29326 then
29327 SPARK_Msg_NE
29328 ("global refinement of state & must include at least one "
29329 & "constituent of mode `Proof_In`", N, State_Id);
29330 end if;
29331 end Check_Constituent_Usage;
29333 -- Local variables
29335 Item_Elmt : Elmt_Id;
29336 Item_Id : Entity_Id;
29338 -- Start of processing for Check_Proof_In_States
29340 begin
29341 -- Inspect the Proof_In items of the corresponding Global pragma
29342 -- looking for a state with a visible refinement.
29344 if Has_Proof_In_State and then Present (Proof_In_Items) then
29345 Item_Elmt := First_Elmt (Proof_In_Items);
29346 while Present (Item_Elmt) loop
29347 Item_Id := Node (Item_Elmt);
29349 -- Ensure that at least one of the constituents is utilized
29350 -- and is of mode Proof_In. When only partial refinement is
29351 -- visible, ensure that either one of the constituents is
29352 -- utilized and is of mode Proof_In, or the abstract state
29353 -- is repeated and no constituent is utilized.
29355 if Ekind (Item_Id) = E_Abstract_State
29356 and then Has_Non_Null_Visible_Refinement (Item_Id)
29357 then
29358 Check_Constituent_Usage (Item_Id);
29359 end if;
29361 Next_Elmt (Item_Elmt);
29362 end loop;
29363 end if;
29364 end Check_Proof_In_States;
29366 -------------------------------
29367 -- Check_Refined_Global_List --
29368 -------------------------------
29370 procedure Check_Refined_Global_List
29371 (List : Node_Id;
29372 Global_Mode : Name_Id := Name_Input)
29374 procedure Check_Refined_Global_Item
29375 (Item : Node_Id;
29376 Global_Mode : Name_Id);
29377 -- Verify the legality of a single global item declaration. Parameter
29378 -- Global_Mode denotes the current mode in effect.
29380 -------------------------------
29381 -- Check_Refined_Global_Item --
29382 -------------------------------
29384 procedure Check_Refined_Global_Item
29385 (Item : Node_Id;
29386 Global_Mode : Name_Id)
29388 Item_Id : constant Entity_Id := Entity_Of (Item);
29390 procedure Inconsistent_Mode_Error (Expect : Name_Id);
29391 -- Issue a common error message for all mode mismatches. Expect
29392 -- denotes the expected mode.
29394 -----------------------------
29395 -- Inconsistent_Mode_Error --
29396 -----------------------------
29398 procedure Inconsistent_Mode_Error (Expect : Name_Id) is
29399 begin
29400 SPARK_Msg_NE
29401 ("global item & has inconsistent modes", Item, Item_Id);
29403 Error_Msg_Name_1 := Global_Mode;
29404 Error_Msg_Name_2 := Expect;
29405 SPARK_Msg_N ("\expected mode %, found mode %", Item);
29406 end Inconsistent_Mode_Error;
29408 -- Local variables
29410 Enc_State : Entity_Id := Empty;
29411 -- Encapsulating state for constituent, Empty otherwise
29413 -- Start of processing for Check_Refined_Global_Item
29415 begin
29416 if Ekind (Item_Id) in E_Abstract_State | E_Constant | E_Variable
29417 then
29418 Enc_State := Find_Encapsulating_State (States, Item_Id);
29419 end if;
29421 -- When the state or object acts as a constituent of another
29422 -- state with a visible refinement, collect it for the state
29423 -- completeness checks performed later on. Note that the item
29424 -- acts as a constituent only when the encapsulating state is
29425 -- present in pragma Global.
29427 if Present (Enc_State)
29428 and then (Has_Visible_Refinement (Enc_State)
29429 or else Has_Partial_Visible_Refinement (Enc_State))
29430 and then Contains (States, Enc_State)
29431 then
29432 -- If the state has only partial visible refinement, remove it
29433 -- from the list of items that should be repeated from pragma
29434 -- Global.
29436 if not Has_Visible_Refinement (Enc_State) then
29437 Present_Then_Remove (Repeat_Items, Enc_State);
29438 end if;
29440 if Global_Mode = Name_Input then
29441 Append_New_Elmt (Item_Id, In_Constits);
29443 elsif Global_Mode = Name_In_Out then
29444 Append_New_Elmt (Item_Id, In_Out_Constits);
29446 elsif Global_Mode = Name_Output then
29447 Append_New_Elmt (Item_Id, Out_Constits);
29449 elsif Global_Mode = Name_Proof_In then
29450 Append_New_Elmt (Item_Id, Proof_In_Constits);
29451 end if;
29453 -- When not a constituent, ensure that both occurrences of the
29454 -- item in pragmas Global and Refined_Global match. Also remove
29455 -- it when present from the list of items that should be repeated
29456 -- from pragma Global.
29458 else
29459 Present_Then_Remove (Repeat_Items, Item_Id);
29461 if Contains (In_Items, Item_Id) then
29462 if Global_Mode /= Name_Input then
29463 Inconsistent_Mode_Error (Name_Input);
29464 end if;
29466 elsif Contains (In_Out_Items, Item_Id) then
29467 if Global_Mode /= Name_In_Out then
29468 Inconsistent_Mode_Error (Name_In_Out);
29469 end if;
29471 elsif Contains (Out_Items, Item_Id) then
29472 if Global_Mode /= Name_Output then
29473 Inconsistent_Mode_Error (Name_Output);
29474 end if;
29476 elsif Contains (Proof_In_Items, Item_Id) then
29477 null;
29479 -- The item does not appear in the corresponding Global pragma,
29480 -- it must be an extra (SPARK RM 7.2.4(3)).
29482 else
29483 pragma Assert (Present (Global));
29484 Error_Msg_Sloc := Sloc (Global);
29485 SPARK_Msg_NE
29486 ("extra global item & does not refine or repeat any "
29487 & "global item #", Item, Item_Id);
29488 end if;
29489 end if;
29490 end Check_Refined_Global_Item;
29492 -- Local variables
29494 Item : Node_Id;
29496 -- Start of processing for Check_Refined_Global_List
29498 begin
29499 if Nkind (List) = N_Null then
29500 null;
29502 -- Single global item declaration
29504 elsif Nkind (List) in N_Expanded_Name
29505 | N_Identifier
29506 | N_Selected_Component
29507 then
29508 Check_Refined_Global_Item (List, Global_Mode);
29510 -- Simple global list or moded global list declaration
29512 elsif Nkind (List) = N_Aggregate then
29514 -- The declaration of a simple global list appear as a collection
29515 -- of expressions.
29517 if Present (Expressions (List)) then
29518 Item := First (Expressions (List));
29519 while Present (Item) loop
29520 Check_Refined_Global_Item (Item, Global_Mode);
29521 Next (Item);
29522 end loop;
29524 -- The declaration of a moded global list appears as a collection
29525 -- of component associations where individual choices denote
29526 -- modes.
29528 elsif Present (Component_Associations (List)) then
29529 Item := First (Component_Associations (List));
29530 while Present (Item) loop
29531 Check_Refined_Global_List
29532 (List => Expression (Item),
29533 Global_Mode => Chars (First (Choices (Item))));
29535 Next (Item);
29536 end loop;
29538 -- Invalid tree
29540 else
29541 raise Program_Error;
29542 end if;
29544 -- Invalid list
29546 else
29547 raise Program_Error;
29548 end if;
29549 end Check_Refined_Global_List;
29551 --------------------------
29552 -- Collect_Global_Items --
29553 --------------------------
29555 procedure Collect_Global_Items
29556 (List : Node_Id;
29557 Mode : Name_Id := Name_Input)
29559 procedure Collect_Global_Item
29560 (Item : Node_Id;
29561 Item_Mode : Name_Id);
29562 -- Add a single item to the appropriate list. Item_Mode denotes the
29563 -- current mode in effect.
29565 -------------------------
29566 -- Collect_Global_Item --
29567 -------------------------
29569 procedure Collect_Global_Item
29570 (Item : Node_Id;
29571 Item_Mode : Name_Id)
29573 Item_Id : constant Entity_Id := Available_View (Entity_Of (Item));
29574 -- The above handles abstract views of variables and states built
29575 -- for limited with clauses.
29577 begin
29578 -- Signal that the global list contains at least one abstract
29579 -- state with a visible refinement. Note that the refinement may
29580 -- be null in which case there are no constituents.
29582 if Ekind (Item_Id) = E_Abstract_State then
29583 if Has_Null_Visible_Refinement (Item_Id) then
29584 Has_Null_State := True;
29586 elsif Has_Non_Null_Visible_Refinement (Item_Id) then
29587 Append_New_Elmt (Item_Id, States);
29589 if Item_Mode = Name_Input then
29590 Has_In_State := True;
29591 elsif Item_Mode = Name_In_Out then
29592 Has_In_Out_State := True;
29593 elsif Item_Mode = Name_Output then
29594 Has_Out_State := True;
29595 elsif Item_Mode = Name_Proof_In then
29596 Has_Proof_In_State := True;
29597 end if;
29598 end if;
29599 end if;
29601 -- Record global items without full visible refinement found in
29602 -- pragma Global which should be repeated in the global refinement
29603 -- (SPARK RM 7.2.4(3c), SPARK RM 7.2.4(3d)).
29605 if Ekind (Item_Id) /= E_Abstract_State
29606 or else not Has_Visible_Refinement (Item_Id)
29607 then
29608 Append_New_Elmt (Item_Id, Repeat_Items);
29609 end if;
29611 -- Add the item to the proper list
29613 if Item_Mode = Name_Input then
29614 Append_New_Elmt (Item_Id, In_Items);
29615 elsif Item_Mode = Name_In_Out then
29616 Append_New_Elmt (Item_Id, In_Out_Items);
29617 elsif Item_Mode = Name_Output then
29618 Append_New_Elmt (Item_Id, Out_Items);
29619 elsif Item_Mode = Name_Proof_In then
29620 Append_New_Elmt (Item_Id, Proof_In_Items);
29621 end if;
29622 end Collect_Global_Item;
29624 -- Local variables
29626 Item : Node_Id;
29628 -- Start of processing for Collect_Global_Items
29630 begin
29631 if Nkind (List) = N_Null then
29632 null;
29634 -- Single global item declaration
29636 elsif Nkind (List) in N_Expanded_Name
29637 | N_Identifier
29638 | N_Selected_Component
29639 then
29640 Collect_Global_Item (List, Mode);
29642 -- Single global list or moded global list declaration
29644 elsif Nkind (List) = N_Aggregate then
29646 -- The declaration of a simple global list appear as a collection
29647 -- of expressions.
29649 if Present (Expressions (List)) then
29650 Item := First (Expressions (List));
29651 while Present (Item) loop
29652 Collect_Global_Item (Item, Mode);
29653 Next (Item);
29654 end loop;
29656 -- The declaration of a moded global list appears as a collection
29657 -- of component associations where individual choices denote mode.
29659 elsif Present (Component_Associations (List)) then
29660 Item := First (Component_Associations (List));
29661 while Present (Item) loop
29662 Collect_Global_Items
29663 (List => Expression (Item),
29664 Mode => Chars (First (Choices (Item))));
29666 Next (Item);
29667 end loop;
29669 -- Invalid tree
29671 else
29672 raise Program_Error;
29673 end if;
29675 -- To accommodate partial decoration of disabled SPARK features, this
29676 -- routine may be called with illegal input. If this is the case, do
29677 -- not raise Program_Error.
29679 else
29680 null;
29681 end if;
29682 end Collect_Global_Items;
29684 -------------------------
29685 -- Present_Then_Remove --
29686 -------------------------
29688 function Present_Then_Remove
29689 (List : Elist_Id;
29690 Item : Entity_Id) return Boolean
29692 Elmt : Elmt_Id;
29694 begin
29695 if Present (List) then
29696 Elmt := First_Elmt (List);
29697 while Present (Elmt) loop
29698 if Node (Elmt) = Item then
29699 Remove_Elmt (List, Elmt);
29700 return True;
29701 end if;
29703 Next_Elmt (Elmt);
29704 end loop;
29705 end if;
29707 return False;
29708 end Present_Then_Remove;
29710 procedure Present_Then_Remove (List : Elist_Id; Item : Entity_Id) is
29711 Ignore : Boolean;
29712 begin
29713 Ignore := Present_Then_Remove (List, Item);
29714 end Present_Then_Remove;
29716 -------------------------------
29717 -- Report_Extra_Constituents --
29718 -------------------------------
29720 procedure Report_Extra_Constituents is
29721 procedure Report_Extra_Constituents_In_List (List : Elist_Id);
29722 -- Emit an error for every element of List
29724 ---------------------------------------
29725 -- Report_Extra_Constituents_In_List --
29726 ---------------------------------------
29728 procedure Report_Extra_Constituents_In_List (List : Elist_Id) is
29729 Constit_Elmt : Elmt_Id;
29731 begin
29732 if Present (List) then
29733 Constit_Elmt := First_Elmt (List);
29734 while Present (Constit_Elmt) loop
29735 SPARK_Msg_NE ("extra constituent &", N, Node (Constit_Elmt));
29736 Next_Elmt (Constit_Elmt);
29737 end loop;
29738 end if;
29739 end Report_Extra_Constituents_In_List;
29741 -- Start of processing for Report_Extra_Constituents
29743 begin
29744 Report_Extra_Constituents_In_List (In_Constits);
29745 Report_Extra_Constituents_In_List (In_Out_Constits);
29746 Report_Extra_Constituents_In_List (Out_Constits);
29747 Report_Extra_Constituents_In_List (Proof_In_Constits);
29748 end Report_Extra_Constituents;
29750 --------------------------
29751 -- Report_Missing_Items --
29752 --------------------------
29754 procedure Report_Missing_Items is
29755 Item_Elmt : Elmt_Id;
29756 Item_Id : Entity_Id;
29758 begin
29759 if Present (Repeat_Items) then
29760 Item_Elmt := First_Elmt (Repeat_Items);
29761 while Present (Item_Elmt) loop
29762 Item_Id := Node (Item_Elmt);
29763 SPARK_Msg_NE ("missing global item &", N, Item_Id);
29764 Next_Elmt (Item_Elmt);
29765 end loop;
29766 end if;
29767 end Report_Missing_Items;
29769 -- Local variables
29771 Body_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
29772 Errors : constant Nat := Serious_Errors_Detected;
29773 Items : Node_Id;
29774 No_Constit : Boolean;
29776 -- Start of processing for Analyze_Refined_Global_In_Decl_Part
29778 begin
29779 -- Do not analyze the pragma multiple times
29781 if Is_Analyzed_Pragma (N) then
29782 return;
29783 end if;
29785 Spec_Id := Unique_Defining_Entity (Body_Decl);
29787 -- Use the anonymous object as the proper spec when Refined_Global
29788 -- applies to the body of a single task type. The object carries the
29789 -- proper Chars as well as all non-refined versions of pragmas.
29791 if Is_Single_Concurrent_Type (Spec_Id) then
29792 Spec_Id := Anonymous_Object (Spec_Id);
29793 end if;
29795 Global := Get_Pragma (Spec_Id, Pragma_Global);
29796 Items := Expression (Get_Argument (N, Spec_Id));
29798 -- The subprogram declaration lacks pragma Global. This renders
29799 -- Refined_Global useless as there is nothing to refine.
29801 if No (Global) then
29802 SPARK_Msg_NE
29803 (Fix_Msg (Spec_Id, "useless refinement, declaration of subprogram "
29804 & "& lacks aspect or pragma Global"), N, Spec_Id);
29805 goto Leave;
29806 end if;
29808 -- Extract all relevant items from the corresponding Global pragma
29810 Collect_Global_Items (Expression (Get_Argument (Global, Spec_Id)));
29812 -- Package and subprogram bodies are instantiated individually in
29813 -- a separate compiler pass. Due to this mode of instantiation, the
29814 -- refinement of a state may no longer be visible when a subprogram
29815 -- body contract is instantiated. Since the generic template is legal,
29816 -- do not perform this check in the instance to circumvent this oddity.
29818 if In_Instance then
29819 null;
29821 -- Non-instance case
29823 else
29824 -- The corresponding Global pragma must mention at least one
29825 -- state with a visible refinement at the point Refined_Global
29826 -- is processed. States with null refinements need Refined_Global
29827 -- pragma (SPARK RM 7.2.4(2)).
29829 if not Has_In_State
29830 and then not Has_In_Out_State
29831 and then not Has_Out_State
29832 and then not Has_Proof_In_State
29833 and then not Has_Null_State
29834 then
29835 SPARK_Msg_NE
29836 (Fix_Msg (Spec_Id, "useless refinement, subprogram & does not "
29837 & "depend on abstract state with visible refinement"),
29838 N, Spec_Id);
29839 goto Leave;
29841 -- The global refinement of inputs and outputs cannot be null when
29842 -- the corresponding Global pragma contains at least one item except
29843 -- in the case where we have states with null refinements.
29845 elsif Nkind (Items) = N_Null
29846 and then
29847 (Present (In_Items)
29848 or else Present (In_Out_Items)
29849 or else Present (Out_Items)
29850 or else Present (Proof_In_Items))
29851 and then not Has_Null_State
29852 then
29853 SPARK_Msg_NE
29854 (Fix_Msg (Spec_Id, "refinement cannot be null, subprogram & has "
29855 & "global items"), N, Spec_Id);
29856 goto Leave;
29857 end if;
29858 end if;
29860 -- Analyze Refined_Global as if it behaved as a regular pragma Global.
29861 -- This ensures that the categorization of all refined global items is
29862 -- consistent with their role.
29864 Analyze_Global_In_Decl_Part (N);
29866 -- Do not perform these checks in an instance because they were already
29867 -- performed successfully in the generic template.
29869 if In_Instance then
29870 goto Leave;
29871 end if;
29873 -- Perform all refinement checks with respect to completeness and mode
29874 -- matching.
29876 if Serious_Errors_Detected = Errors then
29877 Check_Refined_Global_List (Items);
29878 end if;
29880 -- Store the information that no constituent is used in the global
29881 -- refinement, prior to calling checking procedures which remove items
29882 -- from the list of constituents.
29884 No_Constit :=
29885 No (In_Constits)
29886 and then No (In_Out_Constits)
29887 and then No (Out_Constits)
29888 and then No (Proof_In_Constits);
29890 -- For Input states with visible refinement, at least one constituent
29891 -- must be used as an Input in the global refinement.
29893 if Serious_Errors_Detected = Errors then
29894 Check_Input_States;
29895 end if;
29897 -- Verify all possible completion variants for In_Out states with
29898 -- visible refinement.
29900 if Serious_Errors_Detected = Errors then
29901 Check_In_Out_States;
29902 end if;
29904 -- For Output states with visible refinement, all constituents must be
29905 -- used as Outputs in the global refinement.
29907 if Serious_Errors_Detected = Errors then
29908 Check_Output_States;
29909 end if;
29911 -- For Proof_In states with visible refinement, at least one constituent
29912 -- must be used as Proof_In in the global refinement.
29914 if Serious_Errors_Detected = Errors then
29915 Check_Proof_In_States;
29916 end if;
29918 -- Emit errors for all constituents that belong to other states with
29919 -- visible refinement that do not appear in Global.
29921 if Serious_Errors_Detected = Errors then
29922 Report_Extra_Constituents;
29923 end if;
29925 -- Emit errors for all items in Global that are not repeated in the
29926 -- global refinement and for which there is no full visible refinement
29927 -- and, in the case of states with partial visible refinement, no
29928 -- constituent is mentioned in the global refinement.
29930 if Serious_Errors_Detected = Errors then
29931 Report_Missing_Items;
29932 end if;
29934 -- Emit an error if no constituent is used in the global refinement
29935 -- (SPARK RM 7.2.4(3f)). Emit this error last, in case a more precise
29936 -- one may be issued by the checking procedures. Do not perform this
29937 -- check in an instance because it was already performed successfully
29938 -- in the generic template.
29940 if Serious_Errors_Detected = Errors
29941 and then not Has_Null_State
29942 and then No_Constit
29943 then
29944 SPARK_Msg_N ("missing refinement", N);
29945 end if;
29947 <<Leave>>
29948 Set_Is_Analyzed_Pragma (N);
29949 end Analyze_Refined_Global_In_Decl_Part;
29951 ----------------------------------------
29952 -- Analyze_Refined_State_In_Decl_Part --
29953 ----------------------------------------
29955 procedure Analyze_Refined_State_In_Decl_Part
29956 (N : Node_Id;
29957 Freeze_Id : Entity_Id := Empty)
29959 Body_Decl : constant Node_Id := Find_Related_Package_Or_Body (N);
29960 Body_Id : constant Entity_Id := Defining_Entity (Body_Decl);
29961 Spec_Id : constant Entity_Id := Corresponding_Spec (Body_Decl);
29963 Available_States : Elist_Id := No_Elist;
29964 -- A list of all abstract states defined in the package declaration that
29965 -- are available for refinement. The list is used to report unrefined
29966 -- states.
29968 Body_States : Elist_Id := No_Elist;
29969 -- A list of all hidden states that appear in the body of the related
29970 -- package. The list is used to report unused hidden states.
29972 Constituents_Seen : Elist_Id := No_Elist;
29973 -- A list that contains all constituents processed so far. The list is
29974 -- used to detect multiple uses of the same constituent.
29976 Freeze_Posted : Boolean := False;
29977 -- A flag that controls the output of a freezing-related error (see use
29978 -- below).
29980 Refined_States_Seen : Elist_Id := No_Elist;
29981 -- A list that contains all refined states processed so far. The list is
29982 -- used to detect duplicate refinements.
29984 procedure Analyze_Refinement_Clause (Clause : Node_Id);
29985 -- Perform full analysis of a single refinement clause
29987 procedure Report_Unrefined_States (States : Elist_Id);
29988 -- Emit errors for all unrefined abstract states found in list States
29990 -------------------------------
29991 -- Analyze_Refinement_Clause --
29992 -------------------------------
29994 procedure Analyze_Refinement_Clause (Clause : Node_Id) is
29995 AR_Constit : Entity_Id := Empty;
29996 AW_Constit : Entity_Id := Empty;
29997 ER_Constit : Entity_Id := Empty;
29998 EW_Constit : Entity_Id := Empty;
29999 -- The entities of external constituents that contain one of the
30000 -- following enabled properties: Async_Readers, Async_Writers,
30001 -- Effective_Reads and Effective_Writes.
30003 External_Constit_Seen : Boolean := False;
30004 -- Flag used to mark when at least one external constituent is part
30005 -- of the state refinement.
30007 Non_Null_Seen : Boolean := False;
30008 Null_Seen : Boolean := False;
30009 -- Flags used to detect multiple uses of null in a single clause or a
30010 -- mixture of null and non-null constituents.
30012 Part_Of_Constits : Elist_Id := No_Elist;
30013 -- A list of all candidate constituents subject to indicator Part_Of
30014 -- where the encapsulating state is the current state.
30016 State : Node_Id;
30017 State_Id : Entity_Id;
30018 -- The current state being refined
30020 procedure Analyze_Constituent (Constit : Node_Id);
30021 -- Perform full analysis of a single constituent
30023 procedure Check_External_Property
30024 (Prop_Nam : Name_Id;
30025 Enabled : Boolean;
30026 Constit : Entity_Id);
30027 -- Determine whether a property denoted by name Prop_Nam is present
30028 -- in the refined state. Emit an error if this is not the case. Flag
30029 -- Enabled should be set when the property applies to the refined
30030 -- state. Constit denotes the constituent (if any) which introduces
30031 -- the property in the refinement.
30033 procedure Match_State;
30034 -- Determine whether the state being refined appears in list
30035 -- Available_States. Emit an error when attempting to re-refine the
30036 -- state or when the state is not defined in the package declaration,
30037 -- otherwise remove the state from Available_States.
30039 procedure Report_Unused_Constituents (Constits : Elist_Id);
30040 -- Emit errors for all unused Part_Of constituents in list Constits
30042 -------------------------
30043 -- Analyze_Constituent --
30044 -------------------------
30046 procedure Analyze_Constituent (Constit : Node_Id) is
30047 procedure Match_Constituent (Constit_Id : Entity_Id);
30048 -- Determine whether constituent Constit denoted by its entity
30049 -- Constit_Id appears in Body_States. Emit an error when the
30050 -- constituent is not a valid hidden state of the related package
30051 -- or when it is used more than once. Otherwise remove the
30052 -- constituent from Body_States.
30054 -----------------------
30055 -- Match_Constituent --
30056 -----------------------
30058 procedure Match_Constituent (Constit_Id : Entity_Id) is
30059 procedure Collect_Constituent;
30060 -- Verify the legality of constituent Constit_Id and add it to
30061 -- the refinements of State_Id.
30063 -------------------------
30064 -- Collect_Constituent --
30065 -------------------------
30067 procedure Collect_Constituent is
30068 Constits : Elist_Id;
30070 begin
30071 -- The Ghost policy in effect at the point of abstract state
30072 -- declaration and constituent must match (SPARK RM 6.9(17))
30074 Check_Ghost_Refinement
30075 (State, State_Id, Constit, Constit_Id);
30077 -- A synchronized state must be refined by a synchronized
30078 -- object or another synchronized state (SPARK RM 9.6).
30080 if Is_Synchronized_State (State_Id)
30081 and then not Is_Synchronized_Object (Constit_Id)
30082 and then not Is_Synchronized_State (Constit_Id)
30083 then
30084 SPARK_Msg_NE
30085 ("constituent of synchronized state & must be "
30086 & "synchronized", Constit, State_Id);
30087 end if;
30089 -- Add the constituent to the list of processed items to aid
30090 -- with the detection of duplicates.
30092 Append_New_Elmt (Constit_Id, Constituents_Seen);
30094 -- Collect the constituent in the list of refinement items
30095 -- and establish a relation between the refined state and
30096 -- the item.
30098 Constits := Refinement_Constituents (State_Id);
30100 if No (Constits) then
30101 Constits := New_Elmt_List;
30102 Set_Refinement_Constituents (State_Id, Constits);
30103 end if;
30105 Append_Elmt (Constit_Id, Constits);
30106 Set_Encapsulating_State (Constit_Id, State_Id);
30108 -- The state has at least one legal constituent, mark the
30109 -- start of the refinement region. The region ends when the
30110 -- body declarations end (see routine Analyze_Declarations).
30112 Set_Has_Visible_Refinement (State_Id);
30114 -- When the constituent is external, save its relevant
30115 -- property for further checks.
30117 if Async_Readers_Enabled (Constit_Id) then
30118 AR_Constit := Constit_Id;
30119 External_Constit_Seen := True;
30120 end if;
30122 if Async_Writers_Enabled (Constit_Id) then
30123 AW_Constit := Constit_Id;
30124 External_Constit_Seen := True;
30125 end if;
30127 if Effective_Reads_Enabled (Constit_Id) then
30128 ER_Constit := Constit_Id;
30129 External_Constit_Seen := True;
30130 end if;
30132 if Effective_Writes_Enabled (Constit_Id) then
30133 EW_Constit := Constit_Id;
30134 External_Constit_Seen := True;
30135 end if;
30136 end Collect_Constituent;
30138 -- Local variables
30140 State_Elmt : Elmt_Id;
30142 -- Start of processing for Match_Constituent
30144 begin
30145 -- Detect a duplicate use of a constituent
30147 if Contains (Constituents_Seen, Constit_Id) then
30148 SPARK_Msg_NE
30149 ("duplicate use of constituent &", Constit, Constit_Id);
30150 return;
30151 end if;
30153 -- The constituent is subject to a Part_Of indicator
30155 if Present (Encapsulating_State (Constit_Id)) then
30156 if Encapsulating_State (Constit_Id) = State_Id then
30157 Remove (Part_Of_Constits, Constit_Id);
30158 Collect_Constituent;
30160 -- The constituent is part of another state and is used
30161 -- incorrectly in the refinement of the current state.
30163 else
30164 Error_Msg_Name_1 := Chars (State_Id);
30165 SPARK_Msg_NE
30166 ("& cannot act as constituent of state %",
30167 Constit, Constit_Id);
30168 SPARK_Msg_NE
30169 ("\Part_Of indicator specifies encapsulator &",
30170 Constit, Encapsulating_State (Constit_Id));
30171 end if;
30173 else
30174 declare
30175 Pack_Id : Entity_Id;
30176 Placement : State_Space_Kind;
30177 begin
30178 -- Find where the constituent lives with respect to the
30179 -- state space.
30181 Find_Placement_In_State_Space
30182 (Item_Id => Constit_Id,
30183 Placement => Placement,
30184 Pack_Id => Pack_Id);
30186 -- The constituent is either part of the hidden state of
30187 -- the package or part of the visible state of a private
30188 -- child package, but lacks a Part_Of indicator.
30190 if (Placement = Private_State_Space
30191 and then Pack_Id = Spec_Id)
30192 or else
30193 (Placement = Visible_State_Space
30194 and then Is_Child_Unit (Pack_Id)
30195 and then not Is_Generic_Unit (Pack_Id)
30196 and then Is_Private_Descendant (Pack_Id))
30197 then
30198 Error_Msg_Name_1 := Chars (State_Id);
30199 SPARK_Msg_NE
30200 ("& cannot act as constituent of state %",
30201 Constit, Constit_Id);
30202 Error_Msg_Sloc :=
30203 Sloc (Enclosing_Declaration (Constit_Id));
30204 SPARK_Msg_NE
30205 ("\missing Part_Of indicator # should specify "
30206 & "encapsulator &",
30207 Constit, State_Id);
30209 -- The only other source of legal constituents is the
30210 -- body state space of the related package.
30212 else
30213 if Present (Body_States) then
30214 State_Elmt := First_Elmt (Body_States);
30215 while Present (State_Elmt) loop
30217 -- Consume a valid constituent to signal that it
30218 -- has been encountered.
30220 if Node (State_Elmt) = Constit_Id then
30221 Remove_Elmt (Body_States, State_Elmt);
30222 Collect_Constituent;
30223 return;
30224 end if;
30226 Next_Elmt (State_Elmt);
30227 end loop;
30228 end if;
30230 -- At this point it is known that the constituent is
30231 -- not part of the package hidden state and cannot be
30232 -- used in a refinement (SPARK RM 7.2.2(9)).
30234 Error_Msg_Name_1 := Chars (Spec_Id);
30235 SPARK_Msg_NE
30236 ("cannot use & in refinement, constituent is not a "
30237 & "hidden state of package %", Constit, Constit_Id);
30238 end if;
30239 end;
30240 end if;
30241 end Match_Constituent;
30243 -- Local variables
30245 Constit_Id : Entity_Id;
30246 Constits : Elist_Id;
30248 -- Start of processing for Analyze_Constituent
30250 begin
30251 -- Detect multiple uses of null in a single refinement clause or a
30252 -- mixture of null and non-null constituents.
30254 if Nkind (Constit) = N_Null then
30255 if Null_Seen then
30256 SPARK_Msg_N
30257 ("multiple null constituents not allowed", Constit);
30259 elsif Non_Null_Seen then
30260 SPARK_Msg_N
30261 ("cannot mix null and non-null constituents", Constit);
30263 else
30264 Null_Seen := True;
30266 -- Collect the constituent in the list of refinement items
30268 Constits := Refinement_Constituents (State_Id);
30270 if No (Constits) then
30271 Constits := New_Elmt_List;
30272 Set_Refinement_Constituents (State_Id, Constits);
30273 end if;
30275 Append_Elmt (Constit, Constits);
30277 -- The state has at least one legal constituent, mark the
30278 -- start of the refinement region. The region ends when the
30279 -- body declarations end (see Analyze_Declarations).
30281 Set_Has_Visible_Refinement (State_Id);
30282 end if;
30284 -- Non-null constituents
30286 else
30287 Non_Null_Seen := True;
30289 if Null_Seen then
30290 SPARK_Msg_N
30291 ("cannot mix null and non-null constituents", Constit);
30292 end if;
30294 Analyze (Constit);
30295 Resolve_State (Constit);
30297 -- Ensure that the constituent denotes a valid state or a
30298 -- whole object (SPARK RM 7.2.2(5)).
30300 if Is_Entity_Name (Constit) then
30301 Constit_Id := Entity_Of (Constit);
30303 -- When a constituent is declared after a subprogram body
30304 -- that caused freezing of the related contract where
30305 -- pragma Refined_State resides, the constituent appears
30306 -- undefined and carries Any_Id as its entity.
30308 -- package body Pack
30309 -- with Refined_State => (State => Constit)
30310 -- is
30311 -- procedure Proc
30312 -- with Refined_Global => (Input => Constit)
30313 -- is
30314 -- ...
30315 -- end Proc;
30317 -- Constit : ...;
30318 -- end Pack;
30320 if Constit_Id = Any_Id then
30321 SPARK_Msg_NE ("& is undefined", Constit, Constit_Id);
30323 -- Emit a specialized info message when the contract of
30324 -- the related package body was "frozen" by another body.
30325 -- Note that it is not possible to precisely identify why
30326 -- the constituent is undefined because it is not visible
30327 -- when pragma Refined_State is analyzed. This message is
30328 -- a reasonable approximation.
30330 if Present (Freeze_Id) and then not Freeze_Posted then
30331 Freeze_Posted := True;
30333 Error_Msg_Name_1 := Chars (Body_Id);
30334 Error_Msg_Sloc := Sloc (Freeze_Id);
30335 SPARK_Msg_NE
30336 ("body & declared # freezes the contract of %",
30337 N, Freeze_Id);
30338 SPARK_Msg_N
30339 ("\all constituents must be declared before body #",
30342 -- A misplaced constituent is a critical error because
30343 -- pragma Refined_Depends or Refined_Global depends on
30344 -- the proper link between a state and a constituent.
30345 -- Stop the compilation, as this leads to a multitude
30346 -- of misleading cascaded errors.
30348 raise Unrecoverable_Error;
30349 end if;
30351 -- The constituent is a valid state or object
30353 elsif Ekind (Constit_Id) in
30354 E_Abstract_State | E_Constant | E_Variable
30355 then
30356 Match_Constituent (Constit_Id);
30358 -- The variable may eventually become a constituent of a
30359 -- single protected/task type. Record the reference now
30360 -- and verify its legality when analyzing the contract of
30361 -- the variable (SPARK RM 9.3).
30363 if Ekind (Constit_Id) = E_Variable then
30364 Record_Possible_Part_Of_Reference
30365 (Var_Id => Constit_Id,
30366 Ref => Constit);
30367 end if;
30369 -- Otherwise the constituent is illegal
30371 else
30372 SPARK_Msg_NE
30373 ("constituent & must denote object or state",
30374 Constit, Constit_Id);
30375 end if;
30377 -- The constituent is illegal
30379 else
30380 SPARK_Msg_N ("malformed constituent", Constit);
30381 end if;
30382 end if;
30383 end Analyze_Constituent;
30385 -----------------------------
30386 -- Check_External_Property --
30387 -----------------------------
30389 procedure Check_External_Property
30390 (Prop_Nam : Name_Id;
30391 Enabled : Boolean;
30392 Constit : Entity_Id)
30394 begin
30395 -- The property is missing in the declaration of the state, but
30396 -- a constituent is introducing it in the state refinement
30397 -- (SPARK RM 7.2.8(2)).
30399 if not Enabled and then Present (Constit) then
30400 Error_Msg_Name_1 := Prop_Nam;
30401 Error_Msg_Name_2 := Chars (State_Id);
30402 SPARK_Msg_NE
30403 ("constituent & introduces external property % in refinement "
30404 & "of state %", State, Constit);
30406 Error_Msg_Sloc := Sloc (State_Id);
30407 SPARK_Msg_N
30408 ("\property is missing in abstract state declaration #",
30409 State);
30410 end if;
30411 end Check_External_Property;
30413 -----------------
30414 -- Match_State --
30415 -----------------
30417 procedure Match_State is
30418 State_Elmt : Elmt_Id;
30420 begin
30421 -- Detect a duplicate refinement of a state (SPARK RM 7.2.2(8))
30423 if Contains (Refined_States_Seen, State_Id) then
30424 SPARK_Msg_NE
30425 ("duplicate refinement of state &", State, State_Id);
30426 return;
30427 end if;
30429 -- Inspect the abstract states defined in the package declaration
30430 -- looking for a match.
30432 State_Elmt := First_Elmt (Available_States);
30433 while Present (State_Elmt) loop
30435 -- A valid abstract state is being refined in the body. Add
30436 -- the state to the list of processed refined states to aid
30437 -- with the detection of duplicate refinements. Remove the
30438 -- state from Available_States to signal that it has already
30439 -- been refined.
30441 if Node (State_Elmt) = State_Id then
30442 Append_New_Elmt (State_Id, Refined_States_Seen);
30443 Remove_Elmt (Available_States, State_Elmt);
30444 return;
30445 end if;
30447 Next_Elmt (State_Elmt);
30448 end loop;
30450 -- If we get here, we are refining a state that is not defined in
30451 -- the package declaration.
30453 Error_Msg_Name_1 := Chars (Spec_Id);
30454 SPARK_Msg_NE
30455 ("cannot refine state, & is not defined in package %",
30456 State, State_Id);
30457 end Match_State;
30459 --------------------------------
30460 -- Report_Unused_Constituents --
30461 --------------------------------
30463 procedure Report_Unused_Constituents (Constits : Elist_Id) is
30464 Constit_Elmt : Elmt_Id;
30465 Constit_Id : Entity_Id;
30466 Posted : Boolean := False;
30468 begin
30469 if Present (Constits) then
30470 Constit_Elmt := First_Elmt (Constits);
30471 while Present (Constit_Elmt) loop
30472 Constit_Id := Node (Constit_Elmt);
30474 -- Generate an error message of the form:
30476 -- state ... has unused Part_Of constituents
30477 -- abstract state ... defined at ...
30478 -- constant ... defined at ...
30479 -- variable ... defined at ...
30481 if not Posted then
30482 Posted := True;
30483 SPARK_Msg_NE
30484 ("state & has unused Part_Of constituents",
30485 State, State_Id);
30486 end if;
30488 Error_Msg_Sloc := Sloc (Constit_Id);
30490 if Ekind (Constit_Id) = E_Abstract_State then
30491 SPARK_Msg_NE
30492 ("\abstract state & defined #", State, Constit_Id);
30494 elsif Ekind (Constit_Id) = E_Constant then
30495 SPARK_Msg_NE
30496 ("\constant & defined #", State, Constit_Id);
30498 else
30499 pragma Assert (Ekind (Constit_Id) = E_Variable);
30500 SPARK_Msg_NE ("\variable & defined #", State, Constit_Id);
30501 end if;
30503 Next_Elmt (Constit_Elmt);
30504 end loop;
30505 end if;
30506 end Report_Unused_Constituents;
30508 -- Local declarations
30510 Body_Ref : Node_Id;
30511 Body_Ref_Elmt : Elmt_Id;
30512 Constit : Node_Id;
30513 Extra_State : Node_Id;
30515 -- Start of processing for Analyze_Refinement_Clause
30517 begin
30518 -- A refinement clause appears as a component association where the
30519 -- sole choice is the state and the expressions are the constituents.
30520 -- This is a syntax error, always report.
30522 if Nkind (Clause) /= N_Component_Association then
30523 Error_Msg_N ("malformed state refinement clause", Clause);
30524 return;
30525 end if;
30527 -- Analyze the state name of a refinement clause
30529 State := First (Choices (Clause));
30531 Analyze (State);
30532 Resolve_State (State);
30534 -- Ensure that the state name denotes a valid abstract state that is
30535 -- defined in the spec of the related package.
30537 if Is_Entity_Name (State) then
30538 State_Id := Entity_Of (State);
30540 -- When the abstract state is undefined, it appears as Any_Id. Do
30541 -- not continue with the analysis of the clause.
30543 if State_Id = Any_Id then
30544 return;
30546 -- Catch any attempts to re-refine a state or refine a state that
30547 -- is not defined in the package declaration.
30549 elsif Ekind (State_Id) = E_Abstract_State then
30550 Match_State;
30552 else
30553 SPARK_Msg_NE ("& must denote abstract state", State, State_Id);
30554 return;
30555 end if;
30557 -- References to a state with visible refinement are illegal.
30558 -- When nested packages are involved, detecting such references is
30559 -- tricky because pragma Refined_State is analyzed later than the
30560 -- offending pragma Depends or Global. References that occur in
30561 -- such nested context are stored in a list. Emit errors for all
30562 -- references found in Body_References (SPARK RM 6.1.4(8)).
30564 if Present (Body_References (State_Id)) then
30565 Body_Ref_Elmt := First_Elmt (Body_References (State_Id));
30566 while Present (Body_Ref_Elmt) loop
30567 Body_Ref := Node (Body_Ref_Elmt);
30569 SPARK_Msg_N ("reference to & not allowed", Body_Ref);
30570 Error_Msg_Sloc := Sloc (State);
30571 SPARK_Msg_N ("\refinement of & is visible#", Body_Ref);
30573 Next_Elmt (Body_Ref_Elmt);
30574 end loop;
30575 end if;
30577 -- The state name is illegal. This is a syntax error, always report.
30579 else
30580 Error_Msg_N ("malformed state name in refinement clause", State);
30581 return;
30582 end if;
30584 -- A refinement clause may only refine one state at a time
30586 Extra_State := Next (State);
30588 if Present (Extra_State) then
30589 SPARK_Msg_N
30590 ("refinement clause cannot cover multiple states", Extra_State);
30591 end if;
30593 -- Replicate the Part_Of constituents of the refined state because
30594 -- the algorithm will consume items.
30596 Part_Of_Constits := New_Copy_Elist (Part_Of_Constituents (State_Id));
30598 -- Analyze all constituents of the refinement. Multiple constituents
30599 -- appear as an aggregate.
30601 Constit := Expression (Clause);
30603 if Nkind (Constit) = N_Aggregate then
30604 if Present (Component_Associations (Constit)) then
30605 SPARK_Msg_N
30606 ("constituents of refinement clause must appear in "
30607 & "positional form", Constit);
30609 else pragma Assert (Present (Expressions (Constit)));
30610 Constit := First (Expressions (Constit));
30611 while Present (Constit) loop
30612 Analyze_Constituent (Constit);
30613 Next (Constit);
30614 end loop;
30615 end if;
30617 -- Various forms of a single constituent. Note that these may include
30618 -- malformed constituents.
30620 else
30621 Analyze_Constituent (Constit);
30622 end if;
30624 -- Verify that external constituents do not introduce new external
30625 -- property in the state refinement (SPARK RM 7.2.8(2)).
30627 if Is_External_State (State_Id) then
30628 Check_External_Property
30629 (Prop_Nam => Name_Async_Readers,
30630 Enabled => Async_Readers_Enabled (State_Id),
30631 Constit => AR_Constit);
30633 Check_External_Property
30634 (Prop_Nam => Name_Async_Writers,
30635 Enabled => Async_Writers_Enabled (State_Id),
30636 Constit => AW_Constit);
30638 Check_External_Property
30639 (Prop_Nam => Name_Effective_Reads,
30640 Enabled => Effective_Reads_Enabled (State_Id),
30641 Constit => ER_Constit);
30643 Check_External_Property
30644 (Prop_Nam => Name_Effective_Writes,
30645 Enabled => Effective_Writes_Enabled (State_Id),
30646 Constit => EW_Constit);
30648 -- When a refined state is not external, it should not have external
30649 -- constituents (SPARK RM 7.2.8(1)).
30651 elsif External_Constit_Seen then
30652 SPARK_Msg_NE
30653 ("non-external state & cannot contain external constituents in "
30654 & "refinement", State, State_Id);
30655 end if;
30657 -- Ensure that all Part_Of candidate constituents have been mentioned
30658 -- in the refinement clause.
30660 Report_Unused_Constituents (Part_Of_Constits);
30662 -- Avoid a cascading error reporting a missing refinement by adding a
30663 -- dummy constituent.
30665 if No (Refinement_Constituents (State_Id)) then
30666 Set_Refinement_Constituents (State_Id, New_Elmt_List (Any_Id));
30667 end if;
30669 -- At this point the refinement might be dummy, but must be
30670 -- well-formed, to prevent cascaded errors.
30672 pragma Assert (Has_Null_Refinement (State_Id)
30674 Has_Non_Null_Refinement (State_Id));
30675 end Analyze_Refinement_Clause;
30677 -----------------------------
30678 -- Report_Unrefined_States --
30679 -----------------------------
30681 procedure Report_Unrefined_States (States : Elist_Id) is
30682 State_Elmt : Elmt_Id;
30684 begin
30685 if Present (States) then
30686 State_Elmt := First_Elmt (States);
30687 while Present (State_Elmt) loop
30688 SPARK_Msg_N
30689 ("abstract state & must be refined", Node (State_Elmt));
30691 Next_Elmt (State_Elmt);
30692 end loop;
30693 end if;
30694 end Report_Unrefined_States;
30696 -- Local declarations
30698 Clauses : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
30699 Clause : Node_Id;
30701 -- Start of processing for Analyze_Refined_State_In_Decl_Part
30703 begin
30704 -- Do not analyze the pragma multiple times
30706 if Is_Analyzed_Pragma (N) then
30707 return;
30708 end if;
30710 -- Save the scenario for examination by the ABE Processing phase
30712 Record_Elaboration_Scenario (N);
30714 -- Replicate the abstract states declared by the package because the
30715 -- matching algorithm will consume states.
30717 Available_States := New_Copy_Elist (Abstract_States (Spec_Id));
30719 -- Gather all abstract states and objects declared in the visible
30720 -- state space of the package body. These items must be utilized as
30721 -- constituents in a state refinement.
30723 Body_States := Collect_Body_States (Body_Id);
30725 -- Multiple non-null state refinements appear as an aggregate
30727 if Nkind (Clauses) = N_Aggregate then
30728 if Present (Expressions (Clauses)) then
30729 SPARK_Msg_N
30730 ("state refinements must appear as component associations",
30731 Clauses);
30733 else pragma Assert (Present (Component_Associations (Clauses)));
30734 Clause := First (Component_Associations (Clauses));
30735 while Present (Clause) loop
30736 Analyze_Refinement_Clause (Clause);
30737 Next (Clause);
30738 end loop;
30739 end if;
30741 -- Various forms of a single state refinement. Note that these may
30742 -- include malformed refinements.
30744 else
30745 Analyze_Refinement_Clause (Clauses);
30746 end if;
30748 -- List all abstract states that were left unrefined
30750 Report_Unrefined_States (Available_States);
30752 Set_Is_Analyzed_Pragma (N);
30753 end Analyze_Refined_State_In_Decl_Part;
30755 ---------------------------------------------
30756 -- Analyze_Subprogram_Variant_In_Decl_Part --
30757 ---------------------------------------------
30759 -- WARNING: This routine manages Ghost regions. Return statements must be
30760 -- replaced by gotos which jump to the end of the routine and restore the
30761 -- Ghost mode.
30763 procedure Analyze_Subprogram_Variant_In_Decl_Part
30764 (N : Node_Id;
30765 Freeze_Id : Entity_Id := Empty)
30767 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
30768 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
30770 procedure Analyze_Variant (Variant : Node_Id);
30771 -- Verify the legality of a single contract case
30773 ---------------------
30774 -- Analyze_Variant --
30775 ---------------------
30777 procedure Analyze_Variant (Variant : Node_Id) is
30778 Direction : Node_Id;
30779 Expr : Node_Id;
30780 Errors : Nat;
30781 Extra_Direction : Node_Id;
30783 begin
30784 if Nkind (Variant) /= N_Component_Association then
30785 Error_Msg_N ("wrong syntax in subprogram variant", Variant);
30786 return;
30787 end if;
30789 Direction := First (Choices (Variant));
30790 Expr := Expression (Variant);
30792 -- Each variant must have exactly one direction
30794 Extra_Direction := Next (Direction);
30796 if Present (Extra_Direction) then
30797 Error_Msg_N
30798 ("subprogram variant case must have exactly one direction",
30799 Extra_Direction);
30800 end if;
30802 -- Check placement of OTHERS if available (SPARK RM 6.1.3(1))
30804 if Nkind (Direction) = N_Identifier then
30805 if Chars (Direction) not in Name_Decreases
30806 | Name_Increases
30807 | Name_Structural
30808 then
30809 Error_Msg_N ("wrong direction", Direction);
30810 end if;
30811 else
30812 Error_Msg_N ("wrong syntax", Direction);
30813 end if;
30815 Errors := Serious_Errors_Detected;
30817 -- Preanalyze_Assert_Expression, but without enforcing any of the two
30818 -- acceptable types.
30820 Preanalyze_Assert_Expression (Expr);
30822 -- Expression of a discrete type is allowed. Nothing more to check
30823 -- for structural variants.
30825 if Is_Discrete_Type (Etype (Expr))
30826 or else Chars (Direction) = Name_Structural
30827 then
30828 null;
30830 -- Expression of a Big_Integer type (or its ghost variant) is only
30831 -- allowed in Decreases clause.
30833 elsif
30834 Is_RTE (Base_Type (Etype (Expr)), RE_Big_Integer)
30835 or else
30836 Is_RTE (Base_Type (Etype (Expr)), RO_GH_Big_Integer)
30837 then
30838 if Chars (Direction) = Name_Increases then
30839 Error_Msg_N
30840 ("Subprogram_Variant with Big_Integer can only decrease",
30841 Expr);
30842 end if;
30844 -- Expression of other types is not allowed
30846 else
30847 Error_Msg_N ("expected a discrete or Big_Integer type", Expr);
30848 end if;
30850 -- Emit a clarification message when the variant expression
30851 -- contains at least one undefined reference, possibly due
30852 -- to contract freezing.
30854 if Errors /= Serious_Errors_Detected
30855 and then Present (Freeze_Id)
30856 and then Has_Undefined_Reference (Expr)
30857 then
30858 Contract_Freeze_Error (Spec_Id, Freeze_Id);
30859 end if;
30860 end Analyze_Variant;
30862 -- Local variables
30864 Variants : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
30866 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
30867 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
30868 -- Save the Ghost-related attributes to restore on exit
30870 Variant : Node_Id;
30871 Restore_Scope : Boolean := False;
30873 -- Start of processing for Analyze_Subprogram_Variant_In_Decl_Part
30875 begin
30876 -- Do not analyze the pragma multiple times
30878 if Is_Analyzed_Pragma (N) then
30879 return;
30880 end if;
30882 -- Set the Ghost mode in effect from the pragma. Due to the delayed
30883 -- analysis of the pragma, the Ghost mode at point of declaration and
30884 -- point of analysis may not necessarily be the same. Use the mode in
30885 -- effect at the point of declaration.
30887 Set_Ghost_Mode (N);
30889 -- Single and multiple contract cases must appear in aggregate form. If
30890 -- this is not the case, then either the parser of the analysis of the
30891 -- pragma failed to produce an aggregate, e.g. when the contract is
30892 -- "null" or a "(null record)".
30894 pragma Assert
30895 (if Nkind (Variants) = N_Aggregate
30896 then Null_Record_Present (Variants)
30897 xor (Present (Component_Associations (Variants))
30899 Present (Expressions (Variants)))
30900 else Nkind (Variants) = N_Null);
30902 -- Only "change_direction => discrete_expression" clauses are allowed
30904 if Nkind (Variants) = N_Aggregate
30905 and then Present (Component_Associations (Variants))
30906 and then No (Expressions (Variants))
30907 then
30909 -- Check that the expression is a proper aggregate (no parentheses)
30911 if Paren_Count (Variants) /= 0 then
30912 Error_Msg_F -- CODEFIX
30913 ("redundant parentheses", Variants);
30914 end if;
30916 -- Ensure that the formal parameters are visible when analyzing all
30917 -- clauses. This falls out of the general rule of aspects pertaining
30918 -- to subprogram declarations.
30920 if not In_Open_Scopes (Spec_Id) then
30921 Restore_Scope := True;
30922 Push_Scope (Spec_Id);
30924 if Is_Generic_Subprogram (Spec_Id) then
30925 Install_Generic_Formals (Spec_Id);
30926 else
30927 Install_Formals (Spec_Id);
30928 end if;
30929 end if;
30931 Variant := First (Component_Associations (Variants));
30932 while Present (Variant) loop
30933 Analyze_Variant (Variant);
30935 if Chars (First (Choices (Variant))) = Name_Structural
30936 and then List_Length (Component_Associations (Variants)) > 1
30937 then
30938 Error_Msg_N
30939 ("Structural variant shall be the only variant", Variant);
30940 end if;
30942 Next (Variant);
30943 end loop;
30945 if Restore_Scope then
30946 End_Scope;
30947 end if;
30949 -- Currently it is not possible to inline Subprogram_Variant on a
30950 -- subprogram subject to pragma Inline_Always.
30952 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
30954 -- Otherwise the pragma is illegal
30956 else
30957 Error_Msg_N ("wrong syntax for subprogram variant", N);
30958 end if;
30960 Set_Is_Analyzed_Pragma (N);
30962 Restore_Ghost_Region (Saved_GM, Saved_IGR);
30963 end Analyze_Subprogram_Variant_In_Decl_Part;
30965 ------------------------------------
30966 -- Analyze_Test_Case_In_Decl_Part --
30967 ------------------------------------
30969 procedure Analyze_Test_Case_In_Decl_Part (N : Node_Id) is
30970 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
30971 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
30973 procedure Preanalyze_Test_Case_Arg (Arg_Nam : Name_Id);
30974 -- Preanalyze one of the optional arguments "Requires" or "Ensures"
30975 -- denoted by Arg_Nam.
30977 ------------------------------
30978 -- Preanalyze_Test_Case_Arg --
30979 ------------------------------
30981 procedure Preanalyze_Test_Case_Arg (Arg_Nam : Name_Id) is
30982 Arg : Node_Id;
30984 begin
30985 -- Preanalyze the original aspect argument for a generic subprogram
30986 -- to properly capture global references.
30988 if Is_Generic_Subprogram (Spec_Id) then
30989 Arg :=
30990 Test_Case_Arg
30991 (Prag => N,
30992 Arg_Nam => Arg_Nam,
30993 From_Aspect => True);
30995 if Present (Arg) then
30996 Preanalyze_Assert_Expression
30997 (Expression (Arg), Standard_Boolean);
30998 end if;
30999 end if;
31001 Arg := Test_Case_Arg (N, Arg_Nam);
31003 if Present (Arg) then
31004 Preanalyze_Assert_Expression (Expression (Arg), Standard_Boolean);
31005 end if;
31006 end Preanalyze_Test_Case_Arg;
31008 -- Local variables
31010 Restore_Scope : Boolean := False;
31012 -- Start of processing for Analyze_Test_Case_In_Decl_Part
31014 begin
31015 -- Do not analyze the pragma multiple times
31017 if Is_Analyzed_Pragma (N) then
31018 return;
31019 end if;
31021 -- Ensure that the formal parameters are visible when analyzing all
31022 -- clauses. This falls out of the general rule of aspects pertaining
31023 -- to subprogram declarations.
31025 if not In_Open_Scopes (Spec_Id) then
31026 Restore_Scope := True;
31027 Push_Scope (Spec_Id);
31029 if Is_Generic_Subprogram (Spec_Id) then
31030 Install_Generic_Formals (Spec_Id);
31031 else
31032 Install_Formals (Spec_Id);
31033 end if;
31034 end if;
31036 Preanalyze_Test_Case_Arg (Name_Requires);
31037 Preanalyze_Test_Case_Arg (Name_Ensures);
31039 if Restore_Scope then
31040 End_Scope;
31041 end if;
31043 -- Currently it is not possible to inline pre/postconditions on a
31044 -- subprogram subject to pragma Inline_Always.
31046 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
31048 Set_Is_Analyzed_Pragma (N);
31049 end Analyze_Test_Case_In_Decl_Part;
31051 ----------------
31052 -- Appears_In --
31053 ----------------
31055 function Appears_In (List : Elist_Id; Item_Id : Entity_Id) return Boolean is
31056 Elmt : Elmt_Id;
31057 Id : Entity_Id;
31059 begin
31060 if Present (List) then
31061 Elmt := First_Elmt (List);
31062 while Present (Elmt) loop
31063 if Nkind (Node (Elmt)) = N_Defining_Identifier then
31064 Id := Node (Elmt);
31065 else
31066 Id := Entity_Of (Node (Elmt));
31067 end if;
31069 if Id = Item_Id then
31070 return True;
31071 end if;
31073 Next_Elmt (Elmt);
31074 end loop;
31075 end if;
31077 return False;
31078 end Appears_In;
31080 -----------------------------------
31081 -- Build_Pragma_Check_Equivalent --
31082 -----------------------------------
31084 function Build_Pragma_Check_Equivalent
31085 (Prag : Node_Id;
31086 Subp_Id : Entity_Id := Empty;
31087 Inher_Id : Entity_Id := Empty;
31088 Keep_Pragma_Id : Boolean := False) return Node_Id
31090 function Suppress_Reference (N : Node_Id) return Traverse_Result;
31091 -- Detect whether node N references a formal parameter subject to
31092 -- pragma Unreferenced. If this is the case, set Comes_From_Source
31093 -- to False to suppress the generation of a reference when analyzing
31094 -- N later on.
31096 ------------------------
31097 -- Suppress_Reference --
31098 ------------------------
31100 function Suppress_Reference (N : Node_Id) return Traverse_Result is
31101 Formal : Entity_Id;
31103 begin
31104 if Is_Entity_Name (N) and then Present (Entity (N)) then
31105 Formal := Entity (N);
31107 -- The formal parameter is subject to pragma Unreferenced. Prevent
31108 -- the generation of references by resetting the Comes_From_Source
31109 -- flag.
31111 if Is_Formal (Formal)
31112 and then Has_Pragma_Unreferenced (Formal)
31113 then
31114 Set_Comes_From_Source (N, False);
31115 end if;
31116 end if;
31118 return OK;
31119 end Suppress_Reference;
31121 procedure Suppress_References is
31122 new Traverse_Proc (Suppress_Reference);
31124 -- Local variables
31126 Loc : constant Source_Ptr := Sloc (Prag);
31127 Prag_Nam : constant Name_Id := Pragma_Name (Prag);
31128 Check_Prag : Node_Id;
31129 Nam : Name_Id;
31131 -- Start of processing for Build_Pragma_Check_Equivalent
31133 begin
31134 -- When the pre- or postcondition is inherited, map the formals of the
31135 -- inherited subprogram to those of the current subprogram. In addition,
31136 -- map primitive operations of the parent type into the corresponding
31137 -- primitive operations of the descendant.
31139 if Present (Inher_Id) then
31140 pragma Assert (Present (Subp_Id));
31142 Update_Primitives_Mapping (Inher_Id, Subp_Id);
31144 -- Use generic machinery to copy inherited pragma, as if it were an
31145 -- instantiation, resetting source locations appropriately, so that
31146 -- expressions inside the inherited pragma use chained locations.
31147 -- This is used in particular in GNATprove to locate precisely
31148 -- messages on a given inherited pragma.
31150 Set_Copied_Sloc_For_Inherited_Pragma
31151 (Unit_Declaration_Node (Subp_Id), Inher_Id);
31152 Check_Prag := New_Copy_Tree (Source => Prag);
31154 -- Build the inherited class-wide condition
31156 Build_Class_Wide_Expression
31157 (Pragma_Or_Expr => Check_Prag,
31158 Subp => Subp_Id,
31159 Par_Subp => Inher_Id,
31160 Adjust_Sloc => True);
31162 -- If not an inherited condition simply copy the original pragma
31164 else
31165 Check_Prag := New_Copy_Tree (Source => Prag);
31166 end if;
31168 -- Mark the pragma as being internally generated and reset the Analyzed
31169 -- flag.
31171 Set_Analyzed (Check_Prag, False);
31172 Set_Comes_From_Source (Check_Prag, False);
31174 -- The tree of the original pragma may contain references to the
31175 -- formal parameters of the related subprogram. At the same time
31176 -- the corresponding body may mark the formals as unreferenced:
31178 -- procedure Proc (Formal : ...)
31179 -- with Pre => Formal ...;
31181 -- procedure Proc (Formal : ...) is
31182 -- pragma Unreferenced (Formal);
31183 -- ...
31185 -- This creates problems because all pragma Check equivalents are
31186 -- analyzed at the end of the body declarations. Since all source
31187 -- references have already been accounted for, reset any references
31188 -- to such formals in the generated pragma Check equivalent.
31190 Suppress_References (Check_Prag);
31192 if Present (Corresponding_Aspect (Prag)) then
31193 Nam := Chars (Identifier (Corresponding_Aspect (Prag)));
31194 else
31195 Nam := Prag_Nam;
31196 end if;
31198 -- Unless Keep_Pragma_Id is True in order to keep the identifier of
31199 -- the copied pragma in the newly created pragma, convert the copy into
31200 -- pragma Check by correcting the name and adding a check_kind argument.
31202 if not Keep_Pragma_Id then
31203 Set_Class_Present (Check_Prag, False);
31205 Set_Pragma_Identifier
31206 (Check_Prag, Make_Identifier (Loc, Name_Check));
31208 Prepend_To (Pragma_Argument_Associations (Check_Prag),
31209 Make_Pragma_Argument_Association (Loc,
31210 Expression => Make_Identifier (Loc, Nam)));
31211 end if;
31213 return Check_Prag;
31214 end Build_Pragma_Check_Equivalent;
31216 -----------------------------
31217 -- Check_Applicable_Policy --
31218 -----------------------------
31220 procedure Check_Applicable_Policy (N : Node_Id) is
31221 PP : Node_Id;
31222 Policy : Name_Id;
31224 Ename : constant Name_Id := Original_Aspect_Pragma_Name (N);
31226 begin
31227 -- No effect if not valid assertion kind name
31229 if not Is_Valid_Assertion_Kind (Ename) then
31230 return;
31231 end if;
31233 -- Loop through entries in check policy list
31235 PP := Opt.Check_Policy_List;
31236 while Present (PP) loop
31237 declare
31238 PPA : constant List_Id := Pragma_Argument_Associations (PP);
31239 Pnm : constant Name_Id := Chars (Get_Pragma_Arg (First (PPA)));
31241 begin
31242 if Ename = Pnm
31243 or else Pnm = Name_Assertion
31244 or else (Pnm = Name_Statement_Assertions
31245 and then Ename in Name_Assert
31246 | Name_Assert_And_Cut
31247 | Name_Assume
31248 | Name_Loop_Invariant
31249 | Name_Loop_Variant)
31250 then
31251 Policy := Chars (Get_Pragma_Arg (Last (PPA)));
31253 case Policy is
31254 when Name_Ignore
31255 | Name_Off
31257 -- In CodePeer mode and GNATprove mode, we need to
31258 -- consider all assertions, unless they are disabled.
31259 -- Force Is_Checked on ignored assertions, in particular
31260 -- because transformations of the AST may depend on
31261 -- assertions being checked (e.g. the translation of
31262 -- attribute 'Loop_Entry).
31264 if CodePeer_Mode or GNATprove_Mode then
31265 Set_Is_Checked (N, True);
31266 Set_Is_Ignored (N, False);
31267 else
31268 Set_Is_Checked (N, False);
31269 Set_Is_Ignored (N, True);
31270 end if;
31272 when Name_Check
31273 | Name_On
31275 Set_Is_Checked (N, True);
31276 Set_Is_Ignored (N, False);
31278 when Name_Disable =>
31279 Set_Is_Ignored (N, True);
31280 Set_Is_Checked (N, False);
31281 Set_Is_Disabled (N, True);
31283 -- That should be exhaustive, the null here is a defence
31284 -- against a malformed tree from previous errors.
31286 when others =>
31287 null;
31288 end case;
31290 return;
31291 end if;
31293 PP := Next_Pragma (PP);
31294 end;
31295 end loop;
31297 -- If there are no specific entries that matched, then we let the
31298 -- setting of assertions govern. Note that this provides the needed
31299 -- compatibility with the RM for the cases of assertion, invariant,
31300 -- precondition, predicate, and postcondition. Note also that
31301 -- Assertions_Enabled is forced in CodePeer mode and GNATprove mode.
31303 if Assertions_Enabled then
31304 Set_Is_Checked (N, True);
31305 Set_Is_Ignored (N, False);
31306 else
31307 Set_Is_Checked (N, False);
31308 Set_Is_Ignored (N, True);
31309 end if;
31310 end Check_Applicable_Policy;
31312 -------------------------------
31313 -- Check_External_Properties --
31314 -------------------------------
31316 procedure Check_External_Properties
31317 (Item : Node_Id;
31318 AR : Boolean;
31319 AW : Boolean;
31320 ER : Boolean;
31321 EW : Boolean)
31323 type Properties is array (Positive range 1 .. 4) of Boolean;
31324 type Combinations is array (Positive range <>) of Properties;
31325 -- Arrays of Async_Readers, Async_Writers, Effective_Writes and
31326 -- Effective_Reads properties and their combinations, respectively.
31328 Specified : constant Properties := (AR, AW, EW, ER);
31329 -- External properties, as given by the Item pragma
31331 Allowed : constant Combinations :=
31332 (1 => (True, False, True, False),
31333 2 => (False, True, False, True),
31334 3 => (True, False, False, False),
31335 4 => (False, True, False, False),
31336 5 => (True, True, True, False),
31337 6 => (True, True, False, True),
31338 7 => (True, True, False, False),
31339 8 => (True, True, True, True));
31340 -- Allowed combinations, as listed in the SPARK RM 7.1.2(6) table
31342 begin
31343 -- Check if the specified properties match any of the allowed
31344 -- combination; if not, then emit an error.
31346 for J in Allowed'Range loop
31347 if Specified = Allowed (J) then
31348 return;
31349 end if;
31350 end loop;
31352 SPARK_Msg_N
31353 ("illegal combination of external properties (SPARK RM 7.1.2(6))",
31354 Item);
31355 end Check_External_Properties;
31357 ----------------
31358 -- Check_Kind --
31359 ----------------
31361 function Check_Kind (Nam : Name_Id) return Name_Id is
31362 PP : Node_Id;
31364 begin
31365 -- Loop through entries in check policy list
31367 PP := Opt.Check_Policy_List;
31368 while Present (PP) loop
31369 declare
31370 PPA : constant List_Id := Pragma_Argument_Associations (PP);
31371 Pnm : constant Name_Id := Chars (Get_Pragma_Arg (First (PPA)));
31373 begin
31374 if Nam = Pnm
31375 or else (Pnm = Name_Assertion
31376 and then Is_Valid_Assertion_Kind (Nam))
31377 or else (Pnm = Name_Statement_Assertions
31378 and then Nam in Name_Assert
31379 | Name_Assert_And_Cut
31380 | Name_Assume
31381 | Name_Loop_Invariant
31382 | Name_Loop_Variant)
31383 then
31384 case Chars (Get_Pragma_Arg (Last (PPA))) is
31385 when Name_Check
31386 | Name_On
31388 return Name_Check;
31390 when Name_Ignore
31391 | Name_Off
31393 return Name_Ignore;
31395 when Name_Disable =>
31396 return Name_Disable;
31398 when others =>
31399 raise Program_Error;
31400 end case;
31402 else
31403 PP := Next_Pragma (PP);
31404 end if;
31405 end;
31406 end loop;
31408 -- If there are no specific entries that matched, then we let the
31409 -- setting of assertions govern. Note that this provides the needed
31410 -- compatibility with the RM for the cases of assertion, invariant,
31411 -- precondition, predicate, and postcondition.
31413 if Assertions_Enabled then
31414 return Name_Check;
31415 else
31416 return Name_Ignore;
31417 end if;
31418 end Check_Kind;
31420 ---------------------------
31421 -- Check_Missing_Part_Of --
31422 ---------------------------
31424 procedure Check_Missing_Part_Of (Item_Id : Entity_Id) is
31425 function Has_Visible_State (Pack_Id : Entity_Id) return Boolean;
31426 -- Determine whether a package denoted by Pack_Id declares at least one
31427 -- visible state.
31429 -----------------------
31430 -- Has_Visible_State --
31431 -----------------------
31433 function Has_Visible_State (Pack_Id : Entity_Id) return Boolean is
31434 Item_Id : Entity_Id;
31436 begin
31437 -- Traverse the entity chain of the package trying to find at least
31438 -- one visible abstract state, variable or a package [instantiation]
31439 -- that declares a visible state.
31441 Item_Id := First_Entity (Pack_Id);
31442 while Present (Item_Id)
31443 and then not In_Private_Part (Item_Id)
31444 loop
31445 -- Do not consider internally generated items
31447 if not Comes_From_Source (Item_Id) then
31448 null;
31450 -- Do not consider generic formals or their corresponding actuals
31451 -- because they are not part of a visible state. Note that both
31452 -- entities are marked as hidden.
31454 elsif Is_Hidden (Item_Id) then
31455 null;
31457 -- A visible state has been found. Note that constants are not
31458 -- considered here because it is not possible to determine whether
31459 -- they depend on variable input. This check is left to the SPARK
31460 -- prover.
31462 elsif Ekind (Item_Id) in E_Abstract_State | E_Variable then
31463 return True;
31465 -- Recursively peek into nested packages and instantiations
31467 elsif Ekind (Item_Id) = E_Package
31468 and then Has_Visible_State (Item_Id)
31469 then
31470 return True;
31471 end if;
31473 Next_Entity (Item_Id);
31474 end loop;
31476 return False;
31477 end Has_Visible_State;
31479 -- Local variables
31481 Pack_Id : Entity_Id;
31482 Placement : State_Space_Kind;
31484 -- Start of processing for Check_Missing_Part_Of
31486 begin
31487 -- Do not consider abstract states, variables or package instantiations
31488 -- coming from an instance as those always inherit the Part_Of indicator
31489 -- of the instance itself.
31491 if In_Instance then
31492 return;
31494 -- Do not consider internally generated entities as these can never
31495 -- have a Part_Of indicator.
31497 elsif not Comes_From_Source (Item_Id) then
31498 return;
31500 -- Perform these checks only when SPARK_Mode is enabled as they will
31501 -- interfere with standard Ada rules and produce false positives.
31503 elsif SPARK_Mode /= On then
31504 return;
31506 -- Do not consider constants, because the compiler cannot accurately
31507 -- determine whether they have variable input (SPARK RM 7.1.1(2)) and
31508 -- act as a hidden state of a package.
31510 elsif Ekind (Item_Id) = E_Constant then
31511 return;
31512 end if;
31514 -- Find where the abstract state, variable or package instantiation
31515 -- lives with respect to the state space.
31517 Find_Placement_In_State_Space
31518 (Item_Id => Item_Id,
31519 Placement => Placement,
31520 Pack_Id => Pack_Id);
31522 -- Items that appear in a non-package construct (subprogram, block, etc)
31523 -- do not require a Part_Of indicator because they can never act as a
31524 -- hidden state.
31526 if Placement = Not_In_Package then
31527 null;
31529 -- An item declared in the body state space of a package always act as a
31530 -- constituent and does not need explicit Part_Of indicator.
31532 elsif Placement = Body_State_Space then
31533 null;
31535 -- In general an item declared in the visible state space of a package
31536 -- does not require a Part_Of indicator. The only exception is when the
31537 -- related package is a nongeneric private child unit, in which case
31538 -- Part_Of must denote a state in the parent unit or in one of its
31539 -- descendants.
31541 elsif Placement = Visible_State_Space then
31542 if Is_Child_Unit (Pack_Id)
31543 and then not Is_Generic_Unit (Pack_Id)
31544 and then Is_Private_Descendant (Pack_Id)
31545 then
31546 -- A package instantiation does not need a Part_Of indicator when
31547 -- the related generic template has no visible state.
31549 if Ekind (Item_Id) = E_Package
31550 and then Is_Generic_Instance (Item_Id)
31551 and then not Has_Visible_State (Item_Id)
31552 then
31553 null;
31555 -- All other cases require Part_Of
31557 else
31558 Error_Msg_N
31559 ("indicator Part_Of is required in this context "
31560 & "(SPARK RM 7.2.6(3))", Item_Id);
31561 Error_Msg_Name_1 := Chars (Pack_Id);
31562 Error_Msg_N
31563 ("\& is declared in the visible part of private child "
31564 & "unit %", Item_Id);
31565 end if;
31566 end if;
31568 -- When the item appears in the private state space of a package, it
31569 -- must be a part of some state declared by the said package.
31571 else pragma Assert (Placement = Private_State_Space);
31573 -- The related package does not declare a state, the item cannot act
31574 -- as a Part_Of constituent.
31576 if No (Get_Pragma (Pack_Id, Pragma_Abstract_State)) then
31577 null;
31579 -- A package instantiation does not need a Part_Of indicator when the
31580 -- related generic template has no visible state.
31582 elsif Ekind (Item_Id) = E_Package
31583 and then Is_Generic_Instance (Item_Id)
31584 and then not Has_Visible_State (Item_Id)
31585 then
31586 null;
31588 -- All other cases require Part_Of
31590 else
31591 Error_Msg_Code := GEC_Required_Part_Of;
31592 Error_Msg_N
31593 ("indicator Part_Of is required in this context '[[]']",
31594 Item_Id);
31595 Error_Msg_Name_1 := Chars (Pack_Id);
31596 Error_Msg_N
31597 ("\& is declared in the private part of package %", Item_Id);
31598 end if;
31599 end if;
31600 end Check_Missing_Part_Of;
31602 ---------------------------------------------------
31603 -- Check_Postcondition_Use_In_Inlined_Subprogram --
31604 ---------------------------------------------------
31606 procedure Check_Postcondition_Use_In_Inlined_Subprogram
31607 (Prag : Node_Id;
31608 Spec_Id : Entity_Id)
31610 begin
31611 if Warn_On_Redundant_Constructs
31612 and then Has_Pragma_Inline_Always (Spec_Id)
31613 and then Assertions_Enabled
31614 and then not Back_End_Inlining
31615 then
31616 Error_Msg_Name_1 := Original_Aspect_Pragma_Name (Prag);
31618 if From_Aspect_Specification (Prag) then
31619 Error_Msg_NE
31620 ("aspect % not enforced on inlined subprogram &?r?",
31621 Corresponding_Aspect (Prag), Spec_Id);
31622 else
31623 Error_Msg_NE
31624 ("pragma % not enforced on inlined subprogram &?r?",
31625 Prag, Spec_Id);
31626 end if;
31627 end if;
31628 end Check_Postcondition_Use_In_Inlined_Subprogram;
31630 -------------------------------------
31631 -- Check_State_And_Constituent_Use --
31632 -------------------------------------
31634 procedure Check_State_And_Constituent_Use
31635 (States : Elist_Id;
31636 Constits : Elist_Id;
31637 Context : Node_Id)
31639 Constit_Elmt : Elmt_Id;
31640 Constit_Id : Entity_Id;
31641 State_Id : Entity_Id;
31643 begin
31644 -- Nothing to do if there are no states or constituents
31646 if No (States) or else No (Constits) then
31647 return;
31648 end if;
31650 -- Inspect the list of constituents and try to determine whether its
31651 -- encapsulating state is in list States.
31653 Constit_Elmt := First_Elmt (Constits);
31654 while Present (Constit_Elmt) loop
31655 Constit_Id := Node (Constit_Elmt);
31657 -- Determine whether the constituent is part of an encapsulating
31658 -- state that appears in the same context and if this is the case,
31659 -- emit an error (SPARK RM 7.2.6(7)).
31661 State_Id := Find_Encapsulating_State (States, Constit_Id);
31663 if Present (State_Id) then
31664 Error_Msg_Name_1 := Chars (Constit_Id);
31665 SPARK_Msg_NE
31666 ("cannot mention state & and its constituent % in the same "
31667 & "context", Context, State_Id);
31668 exit;
31669 end if;
31671 Next_Elmt (Constit_Elmt);
31672 end loop;
31673 end Check_State_And_Constituent_Use;
31675 ---------------------------------------------
31676 -- Collect_Inherited_Class_Wide_Conditions --
31677 ---------------------------------------------
31679 procedure Collect_Inherited_Class_Wide_Conditions (Subp : Entity_Id) is
31680 Parent_Subp : constant Entity_Id :=
31681 Ultimate_Alias (Overridden_Operation (Subp));
31682 -- The Overridden_Operation may itself be inherited and as such have no
31683 -- explicit contract.
31685 Prags : constant Node_Id := Contract (Parent_Subp);
31686 In_Spec_Expr : Boolean := In_Spec_Expression;
31687 Installed : Boolean;
31688 Prag : Node_Id;
31689 New_Prag : Node_Id;
31691 begin
31692 Installed := False;
31694 -- Iterate over the contract of the overridden subprogram to find all
31695 -- inherited class-wide pre- and postconditions.
31697 if Present (Prags) then
31698 Prag := Pre_Post_Conditions (Prags);
31700 while Present (Prag) loop
31701 if Pragma_Name_Unmapped (Prag)
31702 in Name_Precondition | Name_Postcondition
31703 and then Class_Present (Prag)
31704 then
31705 -- The generated pragma must be analyzed in the context of
31706 -- the subprogram, to make its formals visible. In addition,
31707 -- we must inhibit freezing and full analysis because the
31708 -- controlling type of the subprogram is not frozen yet, and
31709 -- may have further primitives.
31711 if not Installed then
31712 Installed := True;
31713 Push_Scope (Subp);
31714 Install_Formals (Subp);
31715 In_Spec_Expr := In_Spec_Expression;
31716 In_Spec_Expression := True;
31717 end if;
31719 New_Prag :=
31720 Build_Pragma_Check_Equivalent
31721 (Prag, Subp, Parent_Subp, Keep_Pragma_Id => True);
31723 Insert_After (Unit_Declaration_Node (Subp), New_Prag);
31724 Preanalyze (New_Prag);
31726 -- Prevent further analysis in subsequent processing of the
31727 -- current list of declarations
31729 Set_Analyzed (New_Prag);
31730 end if;
31732 Prag := Next_Pragma (Prag);
31733 end loop;
31735 if Installed then
31736 In_Spec_Expression := In_Spec_Expr;
31737 End_Scope;
31738 end if;
31739 end if;
31740 end Collect_Inherited_Class_Wide_Conditions;
31742 ---------------------------------------
31743 -- Collect_Subprogram_Inputs_Outputs --
31744 ---------------------------------------
31746 procedure Collect_Subprogram_Inputs_Outputs
31747 (Subp_Id : Entity_Id;
31748 Synthesize : Boolean := False;
31749 Subp_Inputs : in out Elist_Id;
31750 Subp_Outputs : in out Elist_Id;
31751 Global_Seen : out Boolean)
31753 procedure Collect_Dependency_Clause (Clause : Node_Id);
31754 -- Collect all relevant items from a dependency clause
31756 procedure Collect_Global_List
31757 (List : Node_Id;
31758 Mode : Name_Id := Name_Input);
31759 -- Collect all relevant items from a global list
31761 -------------------------------
31762 -- Collect_Dependency_Clause --
31763 -------------------------------
31765 procedure Collect_Dependency_Clause (Clause : Node_Id) is
31766 procedure Collect_Dependency_Item
31767 (Item : Node_Id;
31768 Is_Input : Boolean);
31769 -- Add an item to the proper subprogram input or output collection
31771 -----------------------------
31772 -- Collect_Dependency_Item --
31773 -----------------------------
31775 procedure Collect_Dependency_Item
31776 (Item : Node_Id;
31777 Is_Input : Boolean)
31779 Extra : Node_Id;
31781 begin
31782 -- Nothing to collect when the item is null
31784 if Nkind (Item) = N_Null then
31785 null;
31787 -- Ditto for attribute 'Result
31789 elsif Is_Attribute_Result (Item) then
31790 null;
31792 -- Multiple items appear as an aggregate
31794 elsif Nkind (Item) = N_Aggregate then
31795 Extra := First (Expressions (Item));
31796 while Present (Extra) loop
31797 Collect_Dependency_Item (Extra, Is_Input);
31798 Next (Extra);
31799 end loop;
31801 -- Otherwise this is a solitary item
31803 else
31804 if Is_Input then
31805 Append_New_Elmt (Item, Subp_Inputs);
31806 else
31807 Append_New_Elmt (Item, Subp_Outputs);
31808 end if;
31809 end if;
31810 end Collect_Dependency_Item;
31812 -- Start of processing for Collect_Dependency_Clause
31814 begin
31815 if Nkind (Clause) = N_Null then
31816 null;
31818 -- A dependency clause appears as component association
31820 elsif Nkind (Clause) = N_Component_Association then
31821 Collect_Dependency_Item
31822 (Item => Expression (Clause),
31823 Is_Input => True);
31825 Collect_Dependency_Item
31826 (Item => First (Choices (Clause)),
31827 Is_Input => False);
31829 -- To accommodate partial decoration of disabled SPARK features, this
31830 -- routine may be called with illegal input. If this is the case, do
31831 -- not raise Program_Error.
31833 else
31834 null;
31835 end if;
31836 end Collect_Dependency_Clause;
31838 -------------------------
31839 -- Collect_Global_List --
31840 -------------------------
31842 procedure Collect_Global_List
31843 (List : Node_Id;
31844 Mode : Name_Id := Name_Input)
31846 procedure Collect_Global_Item (Item : Node_Id; Mode : Name_Id);
31847 -- Add an item to the proper subprogram input or output collection
31849 -------------------------
31850 -- Collect_Global_Item --
31851 -------------------------
31853 procedure Collect_Global_Item (Item : Node_Id; Mode : Name_Id) is
31854 begin
31855 if Mode in Name_In_Out | Name_Input then
31856 Append_New_Elmt (Item, Subp_Inputs);
31857 end if;
31859 if Mode in Name_In_Out | Name_Output then
31860 Append_New_Elmt (Item, Subp_Outputs);
31861 end if;
31862 end Collect_Global_Item;
31864 -- Local variables
31866 Assoc : Node_Id;
31867 Item : Node_Id;
31869 -- Start of processing for Collect_Global_List
31871 begin
31872 if Nkind (List) = N_Null then
31873 null;
31875 -- Single global item declaration
31877 elsif Nkind (List) in N_Expanded_Name
31878 | N_Identifier
31879 | N_Selected_Component
31880 then
31881 Collect_Global_Item (List, Mode);
31883 -- Simple global list or moded global list declaration
31885 elsif Nkind (List) = N_Aggregate then
31886 if Present (Expressions (List)) then
31887 Item := First (Expressions (List));
31888 while Present (Item) loop
31889 Collect_Global_Item (Item, Mode);
31890 Next (Item);
31891 end loop;
31893 else
31894 Assoc := First (Component_Associations (List));
31895 while Present (Assoc) loop
31896 Collect_Global_List
31897 (List => Expression (Assoc),
31898 Mode => Chars (First (Choices (Assoc))));
31899 Next (Assoc);
31900 end loop;
31901 end if;
31903 -- To accommodate partial decoration of disabled SPARK features, this
31904 -- routine may be called with illegal input. If this is the case, do
31905 -- not raise Program_Error.
31907 else
31908 null;
31909 end if;
31910 end Collect_Global_List;
31912 -- Local variables
31914 Clause : Node_Id;
31915 Clauses : Node_Id;
31916 Depends : Node_Id;
31917 Formal : Entity_Id;
31918 Global : Node_Id;
31919 Spec_Id : Entity_Id := Empty;
31920 Subp_Decl : Node_Id;
31921 Typ : Entity_Id;
31923 -- Start of processing for Collect_Subprogram_Inputs_Outputs
31925 begin
31926 Global_Seen := False;
31928 -- Process all formal parameters of entries, [generic] subprograms, and
31929 -- their bodies.
31931 if Ekind (Subp_Id) in E_Entry
31932 | E_Entry_Family
31933 | E_Function
31934 | E_Generic_Function
31935 | E_Generic_Procedure
31936 | E_Procedure
31937 | E_Subprogram_Body
31938 then
31939 Subp_Decl := Unit_Declaration_Node (Subp_Id);
31940 Spec_Id := Unique_Defining_Entity (Subp_Decl);
31942 -- Process all formal parameters
31944 Formal := First_Formal (Spec_Id);
31945 while Present (Formal) loop
31946 if Ekind (Formal) in E_In_Out_Parameter | E_In_Parameter then
31947 Append_New_Elmt (Formal, Subp_Inputs);
31949 -- IN parameters of procedures and protected entries can act as
31950 -- outputs when the related type is access-to-variable.
31952 if Ekind (Formal) = E_In_Parameter
31953 and then (Ekind (Spec_Id) not in E_Function
31954 | E_Generic_Function
31955 or else Is_Function_With_Side_Effects (Spec_Id))
31956 and then Is_Access_Variable (Etype (Formal))
31957 then
31958 Append_New_Elmt (Formal, Subp_Outputs);
31959 end if;
31960 end if;
31962 if Ekind (Formal) in E_In_Out_Parameter | E_Out_Parameter then
31963 Append_New_Elmt (Formal, Subp_Outputs);
31965 -- OUT parameters can act as inputs when the related type is
31966 -- tagged, unconstrained array or unconstrained record.
31968 if Ekind (Formal) = E_Out_Parameter
31969 and then Is_Unconstrained_Or_Tagged_Item (Formal)
31970 then
31971 Append_New_Elmt (Formal, Subp_Inputs);
31972 end if;
31973 end if;
31975 Next_Formal (Formal);
31976 end loop;
31978 -- Otherwise the input denotes a task type, a task body, or the
31979 -- anonymous object created for a single task type.
31981 elsif Ekind (Subp_Id) in E_Task_Type | E_Task_Body
31982 or else Is_Single_Task_Object (Subp_Id)
31983 then
31984 Subp_Decl := Declaration_Node (Subp_Id);
31985 Spec_Id := Unique_Defining_Entity (Subp_Decl);
31986 end if;
31988 -- When processing an entry, subprogram or task body, look for pragmas
31989 -- Refined_Depends and Refined_Global as they specify the inputs and
31990 -- outputs.
31992 if Is_Entry_Body (Subp_Id)
31993 or else Ekind (Subp_Id) in E_Subprogram_Body | E_Task_Body
31994 then
31995 Depends := Get_Pragma (Subp_Id, Pragma_Refined_Depends);
31996 Global := Get_Pragma (Subp_Id, Pragma_Refined_Global);
31998 -- Subprogram declaration or stand-alone body case, look for pragmas
31999 -- Depends and Global.
32001 else
32002 Depends := Get_Pragma (Spec_Id, Pragma_Depends);
32003 Global := Get_Pragma (Spec_Id, Pragma_Global);
32004 end if;
32006 -- Pragma [Refined_]Global takes precedence over [Refined_]Depends
32007 -- because it provides finer granularity of inputs and outputs.
32009 if Present (Global) then
32010 Global_Seen := True;
32011 Collect_Global_List (Expression (Get_Argument (Global, Spec_Id)));
32013 -- When the related subprogram lacks pragma [Refined_]Global, fall back
32014 -- to [Refined_]Depends if the caller requests this behavior. Synthesize
32015 -- the inputs and outputs from [Refined_]Depends.
32017 elsif Synthesize and then Present (Depends) then
32018 Clauses := Expression (Get_Argument (Depends, Spec_Id));
32020 -- Multiple dependency clauses appear as an aggregate
32022 if Nkind (Clauses) = N_Aggregate then
32023 Clause := First (Component_Associations (Clauses));
32024 while Present (Clause) loop
32025 Collect_Dependency_Clause (Clause);
32026 Next (Clause);
32027 end loop;
32029 -- Otherwise this is a single dependency clause
32031 else
32032 Collect_Dependency_Clause (Clauses);
32033 end if;
32034 end if;
32036 -- The current instance of a protected type acts as a formal parameter
32037 -- of mode IN for functions and IN OUT for entries and procedures
32038 -- (SPARK RM 6.1.4).
32040 if Ekind (Scope (Spec_Id)) = E_Protected_Type then
32041 Typ := Scope (Spec_Id);
32043 -- Use the anonymous object when the type is single protected
32045 if Is_Single_Concurrent_Type_Declaration (Declaration_Node (Typ)) then
32046 Typ := Anonymous_Object (Typ);
32047 end if;
32049 Append_New_Elmt (Typ, Subp_Inputs);
32051 if Ekind (Spec_Id) in E_Entry | E_Entry_Family | E_Procedure then
32052 Append_New_Elmt (Typ, Subp_Outputs);
32053 end if;
32055 -- The current instance of a task type acts as a formal parameter of
32056 -- mode IN OUT (SPARK RM 6.1.4).
32058 elsif Ekind (Spec_Id) = E_Task_Type then
32059 Typ := Spec_Id;
32061 -- Use the anonymous object when the type is single task
32063 if Is_Single_Concurrent_Type_Declaration (Declaration_Node (Typ)) then
32064 Typ := Anonymous_Object (Typ);
32065 end if;
32067 Append_New_Elmt (Typ, Subp_Inputs);
32068 Append_New_Elmt (Typ, Subp_Outputs);
32070 elsif Is_Single_Task_Object (Spec_Id) then
32071 Append_New_Elmt (Spec_Id, Subp_Inputs);
32072 Append_New_Elmt (Spec_Id, Subp_Outputs);
32073 end if;
32074 end Collect_Subprogram_Inputs_Outputs;
32076 ---------------------------
32077 -- Contract_Freeze_Error --
32078 ---------------------------
32080 procedure Contract_Freeze_Error
32081 (Contract_Id : Entity_Id;
32082 Freeze_Id : Entity_Id)
32084 begin
32085 Error_Msg_Name_1 := Chars (Contract_Id);
32086 Error_Msg_Sloc := Sloc (Freeze_Id);
32088 SPARK_Msg_NE
32089 ("body & declared # freezes the contract of%", Contract_Id, Freeze_Id);
32090 SPARK_Msg_N
32091 ("\all contractual items must be declared before body #", Contract_Id);
32092 end Contract_Freeze_Error;
32094 ---------------------------------
32095 -- Delay_Config_Pragma_Analyze --
32096 ---------------------------------
32098 function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
32099 begin
32100 return Pragma_Name_Unmapped (N)
32101 in Name_Interrupt_State | Name_Priority_Specific_Dispatching;
32102 end Delay_Config_Pragma_Analyze;
32104 -----------------------
32105 -- Duplication_Error --
32106 -----------------------
32108 procedure Duplication_Error (Prag : Node_Id; Prev : Node_Id) is
32109 Prag_From_Asp : constant Boolean := From_Aspect_Specification (Prag);
32110 Prev_From_Asp : constant Boolean := From_Aspect_Specification (Prev);
32112 begin
32113 Error_Msg_Sloc := Sloc (Prev);
32114 Error_Msg_Name_1 := Original_Aspect_Pragma_Name (Prag);
32116 -- Emit a precise message to distinguish between source pragmas and
32117 -- pragmas generated from aspects. The ordering of the two pragmas is
32118 -- the following:
32120 -- Prev -- ok
32121 -- Prag -- duplicate
32123 -- No error is emitted when both pragmas come from aspects because this
32124 -- is already detected by the general aspect analysis mechanism.
32126 if Prag_From_Asp and Prev_From_Asp then
32127 null;
32128 elsif Prag_From_Asp then
32129 Error_Msg_N ("aspect % duplicates pragma declared #", Prag);
32130 elsif Prev_From_Asp then
32131 Error_Msg_N ("pragma % duplicates aspect declared #", Prag);
32132 else
32133 Error_Msg_N ("pragma % duplicates pragma declared #", Prag);
32134 end if;
32135 end Duplication_Error;
32137 ------------------------------
32138 -- Find_Encapsulating_State --
32139 ------------------------------
32141 function Find_Encapsulating_State
32142 (States : Elist_Id;
32143 Constit_Id : Entity_Id) return Entity_Id
32145 State_Id : Entity_Id;
32147 begin
32148 -- Since a constituent may be part of a larger constituent set, climb
32149 -- the encapsulating state chain looking for a state that appears in
32150 -- States.
32152 State_Id := Encapsulating_State (Constit_Id);
32153 while Present (State_Id) loop
32154 if Contains (States, State_Id) then
32155 return State_Id;
32156 end if;
32158 State_Id := Encapsulating_State (State_Id);
32159 end loop;
32161 return Empty;
32162 end Find_Encapsulating_State;
32164 --------------------------
32165 -- Find_Related_Context --
32166 --------------------------
32168 function Find_Related_Context
32169 (Prag : Node_Id;
32170 Do_Checks : Boolean := False) return Node_Id
32172 Stmt : Node_Id;
32174 begin
32175 -- If the pragma comes from an aspect on a compilation unit that is a
32176 -- package instance, then return the original package instantiation
32177 -- node.
32179 if Nkind (Parent (Prag)) = N_Compilation_Unit_Aux then
32180 return
32181 Get_Unit_Instantiation_Node
32182 (Defining_Entity (Unit (Enclosing_Comp_Unit_Node (Prag))));
32183 end if;
32185 Stmt := Prev (Prag);
32186 while Present (Stmt) loop
32188 -- Skip prior pragmas, but check for duplicates
32190 if Nkind (Stmt) = N_Pragma then
32191 if Do_Checks
32192 and then Pragma_Name (Stmt) = Pragma_Name (Prag)
32193 then
32194 Duplication_Error
32195 (Prag => Prag,
32196 Prev => Stmt);
32197 end if;
32199 -- Skip internally generated code
32201 elsif not Comes_From_Source (Stmt)
32202 and then not Comes_From_Source (Original_Node (Stmt))
32203 then
32205 -- The anonymous object created for a single concurrent type is a
32206 -- suitable context.
32208 if Nkind (Stmt) = N_Object_Declaration
32209 and then Is_Single_Concurrent_Object (Defining_Entity (Stmt))
32210 then
32211 return Stmt;
32212 end if;
32214 -- Return the current source construct
32216 else
32217 return Stmt;
32218 end if;
32220 Prev (Stmt);
32221 end loop;
32223 return Empty;
32224 end Find_Related_Context;
32226 --------------------------------------
32227 -- Find_Related_Declaration_Or_Body --
32228 --------------------------------------
32230 function Find_Related_Declaration_Or_Body
32231 (Prag : Node_Id;
32232 Do_Checks : Boolean := False) return Node_Id
32234 Prag_Nam : constant Name_Id := Original_Aspect_Pragma_Name (Prag);
32236 procedure Expression_Function_Error;
32237 -- Emit an error concerning pragma Prag that illegaly applies to an
32238 -- expression function.
32240 -------------------------------
32241 -- Expression_Function_Error --
32242 -------------------------------
32244 procedure Expression_Function_Error is
32245 begin
32246 Error_Msg_Name_1 := Prag_Nam;
32248 -- Emit a precise message to distinguish between source pragmas and
32249 -- pragmas generated from aspects.
32251 if From_Aspect_Specification (Prag) then
32252 Error_Msg_N
32253 ("aspect % cannot apply to a standalone expression function",
32254 Prag);
32255 else
32256 Error_Msg_N
32257 ("pragma % cannot apply to a standalone expression function",
32258 Prag);
32259 end if;
32260 end Expression_Function_Error;
32262 -- Local variables
32264 Context : constant Node_Id := Parent (Prag);
32265 Stmt : Node_Id;
32267 Look_For_Body : constant Boolean :=
32268 Prag_Nam in Name_Refined_Depends
32269 | Name_Refined_Global
32270 | Name_Refined_Post
32271 | Name_Refined_State;
32272 -- Refinement pragmas must be associated with a subprogram body [stub]
32274 -- Start of processing for Find_Related_Declaration_Or_Body
32276 begin
32277 Stmt := Prev (Prag);
32278 while Present (Stmt) loop
32280 -- Skip prior pragmas, but check for duplicates
32282 if Nkind (Stmt) = N_Pragma then
32283 if Do_Checks
32284 and then Original_Aspect_Pragma_Name (Stmt) = Prag_Nam
32285 then
32286 Duplication_Error
32287 (Prag => Prag,
32288 Prev => Stmt);
32289 end if;
32291 -- Emit an error when a refinement pragma appears on an expression
32292 -- function without a completion.
32294 elsif Do_Checks
32295 and then Look_For_Body
32296 and then Nkind (Stmt) = N_Subprogram_Declaration
32297 and then Nkind (Original_Node (Stmt)) = N_Expression_Function
32298 and then not Has_Completion (Defining_Entity (Stmt))
32299 then
32300 Expression_Function_Error;
32301 return Empty;
32303 -- The refinement pragma applies to a subprogram body stub
32305 elsif Look_For_Body
32306 and then Nkind (Stmt) = N_Subprogram_Body_Stub
32307 then
32308 return Stmt;
32310 -- Skip internally generated code
32312 elsif not Comes_From_Source (Stmt) then
32314 -- The anonymous object created for a single concurrent type is a
32315 -- suitable context.
32317 if Nkind (Stmt) = N_Object_Declaration
32318 and then Is_Single_Concurrent_Object (Defining_Entity (Stmt))
32319 then
32320 return Stmt;
32322 elsif Nkind (Stmt) = N_Subprogram_Declaration then
32324 -- The subprogram declaration is an internally generated spec
32325 -- for an expression function.
32327 if Nkind (Original_Node (Stmt)) = N_Expression_Function then
32328 return Stmt;
32330 -- The subprogram declaration is an internally generated spec
32331 -- for a stand-alone subprogram body declared inside a
32332 -- protected body.
32334 elsif Present (Corresponding_Body (Stmt))
32335 and then Comes_From_Source (Corresponding_Body (Stmt))
32336 and then Is_Protected_Type (Current_Scope)
32337 then
32338 return Stmt;
32340 -- The subprogram is actually an instance housed within an
32341 -- anonymous wrapper package.
32343 elsif Present (Generic_Parent (Specification (Stmt))) then
32344 return Stmt;
32346 -- Ada 2022: contract on formal subprogram or on generated
32347 -- Access_Subprogram_Wrapper, which appears after the related
32348 -- Access_Subprogram declaration.
32350 elsif Is_Generic_Actual_Subprogram (Defining_Entity (Stmt))
32351 and then Ada_Version >= Ada_2022
32352 then
32353 return Stmt;
32355 elsif Is_Access_Subprogram_Wrapper (Defining_Entity (Stmt))
32356 and then Ada_Version >= Ada_2022
32357 then
32358 return Stmt;
32359 end if;
32360 end if;
32362 -- Return the current construct which is either a subprogram body,
32363 -- a subprogram declaration or is illegal.
32365 else
32366 return Stmt;
32367 end if;
32369 Prev (Stmt);
32370 end loop;
32372 -- If we fall through, then the pragma was either the first declaration
32373 -- or it was preceded by other pragmas and no source constructs.
32375 -- The pragma is associated with a library-level subprogram
32377 if Nkind (Context) = N_Compilation_Unit_Aux then
32378 return Unit (Parent (Context));
32380 -- The pragma appears inside the declarations of an entry body
32382 elsif Nkind (Context) = N_Entry_Body then
32383 return Context;
32385 -- The pragma appears inside the statements of a subprogram body at
32386 -- some nested level.
32388 elsif Is_Statement (Context)
32389 and then Present (Enclosing_HSS (Context))
32390 then
32391 return Parent (Enclosing_HSS (Context));
32393 -- The pragma appears directly in the statements of a subprogram body
32395 elsif Nkind (Context) = N_Handled_Sequence_Of_Statements then
32396 return Parent (Context);
32398 -- The pragma appears inside the declarative part of a package body
32400 elsif Nkind (Context) = N_Package_Body then
32401 return Context;
32403 -- The pragma appears inside the declarative part of a subprogram body
32405 elsif Nkind (Context) = N_Subprogram_Body then
32406 return Context;
32408 -- The pragma appears inside the declarative part of a task body
32410 elsif Nkind (Context) = N_Task_Body then
32411 return Context;
32413 -- The pragma appears inside the visible part of a package specification
32415 elsif Nkind (Context) = N_Package_Specification then
32416 return Parent (Context);
32418 -- The pragma is a byproduct of aspect expansion, return the related
32419 -- context of the original aspect. This case has a lower priority as
32420 -- the above circuitry pinpoints precisely the related context.
32422 elsif Present (Corresponding_Aspect (Prag)) then
32423 return Parent (Corresponding_Aspect (Prag));
32425 -- No candidate subprogram [body] found
32427 else
32428 return Empty;
32429 end if;
32430 end Find_Related_Declaration_Or_Body;
32432 ----------------------------------
32433 -- Find_Related_Package_Or_Body --
32434 ----------------------------------
32436 function Find_Related_Package_Or_Body
32437 (Prag : Node_Id;
32438 Do_Checks : Boolean := False) return Node_Id
32440 Context : constant Node_Id := Parent (Prag);
32441 Prag_Nam : constant Name_Id := Pragma_Name (Prag);
32442 Stmt : Node_Id;
32444 begin
32445 Stmt := Prev (Prag);
32446 while Present (Stmt) loop
32448 -- Skip prior pragmas, but check for duplicates
32450 if Nkind (Stmt) = N_Pragma then
32451 if Do_Checks and then Pragma_Name (Stmt) = Prag_Nam then
32452 Duplication_Error
32453 (Prag => Prag,
32454 Prev => Stmt);
32455 end if;
32457 -- Skip internally generated code
32459 elsif not Comes_From_Source (Stmt) then
32460 if Nkind (Stmt) = N_Subprogram_Declaration then
32462 -- The subprogram declaration is an internally generated spec
32463 -- for an expression function.
32465 if Nkind (Original_Node (Stmt)) = N_Expression_Function then
32466 return Stmt;
32468 -- The subprogram is actually an instance housed within an
32469 -- anonymous wrapper package.
32471 elsif Present (Generic_Parent (Specification (Stmt))) then
32472 return Stmt;
32473 end if;
32474 end if;
32476 -- Return the current source construct which is illegal
32478 else
32479 return Stmt;
32480 end if;
32482 Prev (Stmt);
32483 end loop;
32485 -- If we fall through, then the pragma was either the first declaration
32486 -- or it was preceded by other pragmas and no source constructs.
32488 -- The pragma is associated with a package. The immediate context in
32489 -- this case is the specification of the package.
32491 if Nkind (Context) = N_Package_Specification then
32492 return Parent (Context);
32494 -- The pragma appears in the declarations of a package body
32496 elsif Nkind (Context) = N_Package_Body then
32497 return Context;
32499 -- The pragma appears in the statements of a package body
32501 elsif Nkind (Context) = N_Handled_Sequence_Of_Statements
32502 and then Nkind (Parent (Context)) = N_Package_Body
32503 then
32504 return Parent (Context);
32506 -- The pragma is a byproduct of aspect expansion, return the related
32507 -- context of the original aspect. This case has a lower priority as
32508 -- the above circuitry pinpoints precisely the related context.
32510 elsif Present (Corresponding_Aspect (Prag)) then
32511 return Parent (Corresponding_Aspect (Prag));
32513 -- No candidate package [body] found
32515 else
32516 return Empty;
32517 end if;
32518 end Find_Related_Package_Or_Body;
32520 ------------------
32521 -- Get_Argument --
32522 ------------------
32524 function Get_Argument
32525 (Prag : Node_Id;
32526 Context_Id : Entity_Id := Empty) return Node_Id
32528 Args : constant List_Id := Pragma_Argument_Associations (Prag);
32530 begin
32531 -- Use the expression of the original aspect when analyzing the template
32532 -- of a generic unit. In both cases the aspect's tree must be decorated
32533 -- to save the global references in the generic context.
32535 if From_Aspect_Specification (Prag)
32536 and then Present (Context_Id)
32537 and then
32538 Is_Generic_Declaration_Or_Body (Unit_Declaration_Node (Context_Id))
32539 then
32540 return Corresponding_Aspect (Prag);
32542 -- Otherwise use the expression of the pragma
32544 elsif Present (Args) then
32545 return First (Args);
32547 else
32548 return Empty;
32549 end if;
32550 end Get_Argument;
32552 -------------------------
32553 -- Get_Base_Subprogram --
32554 -------------------------
32556 function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
32557 begin
32558 -- Follow subprogram renaming chain
32560 if Is_Subprogram (Def_Id)
32561 and then Parent_Kind (Declaration_Node (Def_Id)) =
32562 N_Subprogram_Renaming_Declaration
32563 and then Present (Alias (Def_Id))
32564 then
32565 return Alias (Def_Id);
32566 else
32567 return Def_Id;
32568 end if;
32569 end Get_Base_Subprogram;
32571 -------------------------
32572 -- Get_SPARK_Mode_Type --
32573 -------------------------
32575 function Get_SPARK_Mode_Type (N : Name_Id) return SPARK_Mode_Type is
32576 begin
32577 case N is
32578 when Name_Auto =>
32579 return None;
32580 when Name_On =>
32581 return On;
32582 when Name_Off =>
32583 return Off;
32585 -- Any other argument is illegal. Assume that no SPARK mode applies
32586 -- to avoid potential cascaded errors.
32588 when others =>
32589 return None;
32590 end case;
32591 end Get_SPARK_Mode_Type;
32593 ------------------------------------
32594 -- Get_SPARK_Mode_From_Annotation --
32595 ------------------------------------
32597 function Get_SPARK_Mode_From_Annotation
32598 (N : Node_Id) return SPARK_Mode_Type
32600 Mode : Node_Id;
32602 begin
32603 if Nkind (N) = N_Aspect_Specification then
32604 Mode := Expression (N);
32606 else pragma Assert (Nkind (N) = N_Pragma);
32607 Mode := First (Pragma_Argument_Associations (N));
32609 if Present (Mode) then
32610 Mode := Get_Pragma_Arg (Mode);
32611 end if;
32612 end if;
32614 -- Aspect or pragma SPARK_Mode specifies an explicit mode
32616 if Present (Mode) then
32617 if Nkind (Mode) = N_Identifier then
32618 return Get_SPARK_Mode_Type (Chars (Mode));
32620 -- In case of a malformed aspect or pragma, return the default None
32622 else
32623 return None;
32624 end if;
32626 -- Otherwise the lack of an expression defaults SPARK_Mode to On
32628 else
32629 return On;
32630 end if;
32631 end Get_SPARK_Mode_From_Annotation;
32633 ---------------------------
32634 -- Has_Extra_Parentheses --
32635 ---------------------------
32637 function Has_Extra_Parentheses (Clause : Node_Id) return Boolean is
32638 Expr : Node_Id;
32640 begin
32641 -- The aggregate should not have an expression list because a clause
32642 -- is always interpreted as a component association. The only way an
32643 -- expression list can sneak in is by adding extra parentheses around
32644 -- the individual clauses:
32646 -- Depends (Output => Input) -- proper form
32647 -- Depends ((Output => Input)) -- extra parentheses
32649 -- Since the extra parentheses are not allowed by the syntax of the
32650 -- pragma, flag them now to avoid emitting misleading errors down the
32651 -- line.
32653 if Nkind (Clause) = N_Aggregate
32654 and then Present (Expressions (Clause))
32655 then
32656 Expr := First (Expressions (Clause));
32657 while Present (Expr) loop
32659 -- A dependency clause surrounded by extra parentheses appears
32660 -- as an aggregate of component associations with an optional
32661 -- Paren_Count set.
32663 if Nkind (Expr) = N_Aggregate
32664 and then Present (Component_Associations (Expr))
32665 then
32666 SPARK_Msg_N
32667 ("dependency clause contains extra parentheses", Expr);
32669 -- Otherwise the expression is a malformed construct
32671 else
32672 SPARK_Msg_N ("malformed dependency clause", Expr);
32673 end if;
32675 Next (Expr);
32676 end loop;
32678 return True;
32679 end if;
32681 return False;
32682 end Has_Extra_Parentheses;
32684 ----------------
32685 -- Initialize --
32686 ----------------
32688 procedure Initialize is
32689 begin
32690 Externals.Init;
32691 Compile_Time_Warnings_Errors.Init;
32692 end Initialize;
32694 --------
32695 -- ip --
32696 --------
32698 procedure ip is
32699 begin
32700 Dummy := Dummy + 1;
32701 end ip;
32703 -----------------------------
32704 -- Is_Config_Static_String --
32705 -----------------------------
32707 function Is_Config_Static_String (Arg : Node_Id) return Boolean is
32709 function Add_Config_Static_String (Arg : Node_Id) return Boolean;
32710 -- This is an internal recursive function that is just like the outer
32711 -- function except that it adds the string to the name buffer rather
32712 -- than placing the string in the name buffer.
32714 ------------------------------
32715 -- Add_Config_Static_String --
32716 ------------------------------
32718 function Add_Config_Static_String (Arg : Node_Id) return Boolean is
32719 N : Node_Id;
32720 C : Char_Code;
32722 begin
32723 N := Arg;
32725 if Nkind (N) = N_Op_Concat then
32726 if Add_Config_Static_String (Left_Opnd (N)) then
32727 N := Right_Opnd (N);
32728 else
32729 return False;
32730 end if;
32731 end if;
32733 if Nkind (N) /= N_String_Literal then
32734 Error_Msg_N ("string literal expected for pragma argument", N);
32735 return False;
32737 else
32738 for J in 1 .. String_Length (Strval (N)) loop
32739 C := Get_String_Char (Strval (N), J);
32741 if not In_Character_Range (C) then
32742 Error_Msg
32743 ("string literal contains invalid wide character",
32744 Sloc (N) + 1 + Source_Ptr (J));
32745 return False;
32746 end if;
32748 Add_Char_To_Name_Buffer (Get_Character (C));
32749 end loop;
32750 end if;
32752 return True;
32753 end Add_Config_Static_String;
32755 -- Start of processing for Is_Config_Static_String
32757 begin
32758 Name_Len := 0;
32760 return Add_Config_Static_String (Arg);
32761 end Is_Config_Static_String;
32763 -------------------------------
32764 -- Is_Elaboration_SPARK_Mode --
32765 -------------------------------
32767 function Is_Elaboration_SPARK_Mode (N : Node_Id) return Boolean is
32768 begin
32769 pragma Assert
32770 (Nkind (N) = N_Pragma
32771 and then Pragma_Name (N) = Name_SPARK_Mode
32772 and then Is_List_Member (N));
32774 -- Pragma SPARK_Mode affects the elaboration of a package body when it
32775 -- appears in the statement part of the body.
32777 return
32778 Present (Parent (N))
32779 and then Nkind (Parent (N)) = N_Handled_Sequence_Of_Statements
32780 and then List_Containing (N) = Statements (Parent (N))
32781 and then Present (Parent (Parent (N)))
32782 and then Nkind (Parent (Parent (N))) = N_Package_Body;
32783 end Is_Elaboration_SPARK_Mode;
32785 -----------------------
32786 -- Is_Enabled_Pragma --
32787 -----------------------
32789 function Is_Enabled_Pragma (Prag : Node_Id) return Boolean is
32790 Arg : Node_Id;
32792 begin
32793 if Present (Prag) then
32794 Arg := First (Pragma_Argument_Associations (Prag));
32796 if Present (Arg) then
32797 return Is_True (Expr_Value (Get_Pragma_Arg (Arg)));
32799 -- The lack of a Boolean argument automatically enables the pragma
32801 else
32802 return True;
32803 end if;
32805 -- The pragma is missing, therefore it is not enabled
32807 else
32808 return False;
32809 end if;
32810 end Is_Enabled_Pragma;
32812 -----------------------------------------
32813 -- Is_Non_Significant_Pragma_Reference --
32814 -----------------------------------------
32816 -- This function makes use of the following static table which indicates
32817 -- whether appearance of some name in a given pragma is to be considered
32818 -- as a reference for the purposes of warnings about unreferenced objects.
32820 -- -1 indicates that appearance in any argument is significant
32821 -- 0 indicates that appearance in any argument is not significant
32822 -- +n indicates that appearance as argument n is significant, but all
32823 -- other arguments are not significant
32824 -- 9n arguments from n on are significant, before n insignificant
32826 Sig_Flags : constant array (Pragma_Id) of Int :=
32827 (Pragma_Abort_Defer => -1,
32828 Pragma_Abstract_State => -1,
32829 Pragma_Ada_83 => -1,
32830 Pragma_Ada_95 => -1,
32831 Pragma_Ada_05 => -1,
32832 Pragma_Ada_2005 => -1,
32833 Pragma_Ada_12 => -1,
32834 Pragma_Ada_2012 => -1,
32835 Pragma_Ada_2022 => -1,
32836 Pragma_Aggregate_Individually_Assign => 0,
32837 Pragma_All_Calls_Remote => -1,
32838 Pragma_Allow_Integer_Address => -1,
32839 Pragma_Always_Terminates => -1,
32840 Pragma_Annotate => 93,
32841 Pragma_Assert => -1,
32842 Pragma_Assert_And_Cut => -1,
32843 Pragma_Assertion_Policy => 0,
32844 Pragma_Assume => -1,
32845 Pragma_Assume_No_Invalid_Values => 0,
32846 Pragma_Async_Readers => 0,
32847 Pragma_Async_Writers => 0,
32848 Pragma_Asynchronous => 0,
32849 Pragma_Atomic => 0,
32850 Pragma_Atomic_Components => 0,
32851 Pragma_Attach_Handler => -1,
32852 Pragma_Attribute_Definition => 92,
32853 Pragma_Check => -1,
32854 Pragma_Check_Float_Overflow => 0,
32855 Pragma_Check_Name => 0,
32856 Pragma_Check_Policy => 0,
32857 Pragma_CPP_Class => 0,
32858 Pragma_CPP_Constructor => 0,
32859 Pragma_CPP_Virtual => 0,
32860 Pragma_CPP_Vtable => 0,
32861 Pragma_CPU => -1,
32862 Pragma_C_Pass_By_Copy => 0,
32863 Pragma_Comment => -1,
32864 Pragma_Common_Object => 0,
32865 Pragma_CUDA_Device => -1,
32866 Pragma_CUDA_Execute => -1,
32867 Pragma_CUDA_Global => -1,
32868 Pragma_Compile_Time_Error => -1,
32869 Pragma_Compile_Time_Warning => -1,
32870 Pragma_Complete_Representation => 0,
32871 Pragma_Complex_Representation => 0,
32872 Pragma_Component_Alignment => 0,
32873 Pragma_Constant_After_Elaboration => 0,
32874 Pragma_Contract_Cases => -1,
32875 Pragma_Controlled => 0,
32876 Pragma_Convention => 0,
32877 Pragma_Convention_Identifier => 0,
32878 Pragma_Deadline_Floor => -1,
32879 Pragma_Debug => -1,
32880 Pragma_Debug_Policy => 0,
32881 Pragma_Default_Initial_Condition => -1,
32882 Pragma_Default_Scalar_Storage_Order => 0,
32883 Pragma_Default_Storage_Pool => 0,
32884 Pragma_Depends => -1,
32885 Pragma_Detect_Blocking => 0,
32886 Pragma_Disable_Atomic_Synchronization => 0,
32887 Pragma_Discard_Names => 0,
32888 Pragma_Dispatching_Domain => -1,
32889 Pragma_Effective_Reads => 0,
32890 Pragma_Effective_Writes => 0,
32891 Pragma_Elaborate => 0,
32892 Pragma_Elaborate_All => 0,
32893 Pragma_Elaborate_Body => 0,
32894 Pragma_Elaboration_Checks => 0,
32895 Pragma_Eliminate => 0,
32896 Pragma_Enable_Atomic_Synchronization => 0,
32897 Pragma_Exceptional_Cases => -1,
32898 Pragma_Export => -1,
32899 Pragma_Export_Function => -1,
32900 Pragma_Export_Object => -1,
32901 Pragma_Export_Procedure => -1,
32902 Pragma_Export_Valued_Procedure => -1,
32903 Pragma_Extend_System => -1,
32904 Pragma_Extensions_Allowed => 0,
32905 Pragma_Extensions_Visible => 0,
32906 Pragma_External => -1,
32907 Pragma_External_Name_Casing => 0,
32908 Pragma_Fast_Math => 0,
32909 Pragma_Favor_Top_Level => 0,
32910 Pragma_Finalize_Storage_Only => 0,
32911 Pragma_First_Controlling_Parameter => 0,
32912 Pragma_Ghost => 0,
32913 Pragma_Global => -1,
32914 Pragma_GNAT_Annotate => 93,
32915 Pragma_Ident => -1,
32916 Pragma_Ignore_Pragma => 0,
32917 Pragma_Implementation_Defined => -1,
32918 Pragma_Implemented => -1,
32919 Pragma_Implicit_Packing => 0,
32920 Pragma_Import => 93,
32921 Pragma_Import_Function => 0,
32922 Pragma_Import_Object => 0,
32923 Pragma_Import_Procedure => 0,
32924 Pragma_Import_Valued_Procedure => 0,
32925 Pragma_Independent => 0,
32926 Pragma_Independent_Components => 0,
32927 Pragma_Initial_Condition => -1,
32928 Pragma_Initialize_Scalars => 0,
32929 Pragma_Initializes => -1,
32930 Pragma_Inline => 0,
32931 Pragma_Inline_Always => 0,
32932 Pragma_Inline_Generic => 0,
32933 Pragma_Inspection_Point => -1,
32934 Pragma_Interface => 92,
32935 Pragma_Interface_Name => 0,
32936 Pragma_Interrupt_Handler => -1,
32937 Pragma_Interrupt_Priority => -1,
32938 Pragma_Interrupt_State => -1,
32939 Pragma_Invariant => -1,
32940 Pragma_Keep_Names => 0,
32941 Pragma_License => 0,
32942 Pragma_Link_With => -1,
32943 Pragma_Linker_Alias => -1,
32944 Pragma_Linker_Constructor => -1,
32945 Pragma_Linker_Destructor => -1,
32946 Pragma_Linker_Options => -1,
32947 Pragma_Linker_Section => -1,
32948 Pragma_List => 0,
32949 Pragma_Lock_Free => 0,
32950 Pragma_Locking_Policy => 0,
32951 Pragma_Loop_Invariant => -1,
32952 Pragma_Loop_Optimize => 0,
32953 Pragma_Loop_Variant => -1,
32954 Pragma_Machine_Attribute => -1,
32955 Pragma_Main => -1,
32956 Pragma_Main_Storage => -1,
32957 Pragma_Max_Entry_Queue_Length => 0,
32958 Pragma_Max_Queue_Length => 0,
32959 Pragma_Memory_Size => 0,
32960 Pragma_No_Body => 0,
32961 Pragma_No_Caching => 0,
32962 Pragma_No_Component_Reordering => -1,
32963 Pragma_No_Elaboration_Code_All => 0,
32964 Pragma_No_Heap_Finalization => 0,
32965 Pragma_No_Inline => 0,
32966 Pragma_No_Raise => 0,
32967 Pragma_No_Return => 0,
32968 Pragma_No_Run_Time => -1,
32969 Pragma_Interrupts_System_By_Default => 0,
32970 Pragma_No_Strict_Aliasing => -1,
32971 Pragma_No_Tagged_Streams => 0,
32972 Pragma_Normalize_Scalars => 0,
32973 Pragma_Obsolescent => 0,
32974 Pragma_Optimize => 0,
32975 Pragma_Optimize_Alignment => 0,
32976 Pragma_Ordered => 0,
32977 Pragma_Overflow_Mode => 0,
32978 Pragma_Overriding_Renamings => 0,
32979 Pragma_Pack => 0,
32980 Pragma_Page => 0,
32981 Pragma_Part_Of => 0,
32982 Pragma_Partition_Elaboration_Policy => 0,
32983 Pragma_Passive => 0,
32984 Pragma_Persistent_BSS => 0,
32985 Pragma_Post => -1,
32986 Pragma_Postcondition => -1,
32987 Pragma_Post_Class => -1,
32988 Pragma_Pre => -1,
32989 Pragma_Precondition => -1,
32990 Pragma_Predicate => -1,
32991 Pragma_Predicate_Failure => -1,
32992 Pragma_Preelaborable_Initialization => -1,
32993 Pragma_Preelaborate => 0,
32994 Pragma_Prefix_Exception_Messages => 0,
32995 Pragma_Pre_Class => -1,
32996 Pragma_Priority => -1,
32997 Pragma_Priority_Specific_Dispatching => 0,
32998 Pragma_Profile => 0,
32999 Pragma_Profile_Warnings => 0,
33000 Pragma_Propagate_Exceptions => 0,
33001 Pragma_Provide_Shift_Operators => 0,
33002 Pragma_Psect_Object => 0,
33003 Pragma_Pure => 0,
33004 Pragma_Pure_Function => 0,
33005 Pragma_Queuing_Policy => 0,
33006 Pragma_Rational => 0,
33007 Pragma_Ravenscar => 0,
33008 Pragma_Refined_Depends => -1,
33009 Pragma_Refined_Global => -1,
33010 Pragma_Refined_Post => -1,
33011 Pragma_Refined_State => 0,
33012 Pragma_Relative_Deadline => 0,
33013 Pragma_Remote_Access_Type => -1,
33014 Pragma_Remote_Call_Interface => -1,
33015 Pragma_Remote_Types => -1,
33016 Pragma_Rename_Pragma => 0,
33017 Pragma_Restricted_Run_Time => 0,
33018 Pragma_Restriction_Warnings => 0,
33019 Pragma_Restrictions => 0,
33020 Pragma_Reviewable => -1,
33021 Pragma_Side_Effects => 0,
33022 Pragma_Secondary_Stack_Size => -1,
33023 Pragma_Share_Generic => 0,
33024 Pragma_Shared => 0,
33025 Pragma_Shared_Passive => 0,
33026 Pragma_Short_Circuit_And_Or => 0,
33027 Pragma_Short_Descriptors => 0,
33028 Pragma_Simple_Storage_Pool_Type => 0,
33029 Pragma_Source_File_Name => 0,
33030 Pragma_Source_File_Name_Project => 0,
33031 Pragma_Source_Reference => 0,
33032 Pragma_SPARK_Mode => 0,
33033 Pragma_Static_Elaboration_Desired => 0,
33034 Pragma_Storage_Size => -1,
33035 Pragma_Storage_Unit => 0,
33036 Pragma_Stream_Convert => 0,
33037 Pragma_Style_Checks => 0,
33038 Pragma_Subprogram_Variant => -1,
33039 Pragma_Subtitle => 0,
33040 Pragma_Suppress => 0,
33041 Pragma_Suppress_All => 0,
33042 Pragma_Suppress_Debug_Info => 0,
33043 Pragma_Suppress_Exception_Locations => 0,
33044 Pragma_Suppress_Initialization => 0,
33045 Pragma_System_Name => 0,
33046 Pragma_Task_Dispatching_Policy => 0,
33047 Pragma_Task_Info => -1,
33048 Pragma_Task_Name => -1,
33049 Pragma_Task_Storage => -1,
33050 Pragma_Test_Case => -1,
33051 Pragma_Thread_Local_Storage => -1,
33052 Pragma_Time_Slice => -1,
33053 Pragma_Title => 0,
33054 Pragma_Type_Invariant => -1,
33055 Pragma_Type_Invariant_Class => -1,
33056 Pragma_Unchecked_Union => 0,
33057 Pragma_Unevaluated_Use_Of_Old => 0,
33058 Pragma_Unimplemented_Unit => 0,
33059 Pragma_Universal_Aliasing => 0,
33060 Pragma_Unmodified => 0,
33061 Pragma_Unreferenced => 0,
33062 Pragma_Unreferenced_Objects => 0,
33063 Pragma_Unreserve_All_Interrupts => 0,
33064 Pragma_Unsuppress => 0,
33065 Pragma_Unused => 0,
33066 Pragma_Use_VADS_Size => 0,
33067 Pragma_User_Aspect_Definition => 0,
33068 Pragma_Validity_Checks => 0,
33069 Pragma_Volatile => 0,
33070 Pragma_Volatile_Components => 0,
33071 Pragma_Volatile_Full_Access => 0,
33072 Pragma_Volatile_Function => 0,
33073 Pragma_Warning_As_Error => 0,
33074 Pragma_Warnings => 0,
33075 Pragma_Weak_External => 0,
33076 Pragma_Wide_Character_Encoding => 0,
33077 Unknown_Pragma => 0);
33079 function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
33080 Id : Pragma_Id;
33081 P : Node_Id;
33082 C : Int;
33083 AN : Nat;
33085 function Arg_No return Nat;
33086 -- Returns an integer showing what argument we are in. A value of
33087 -- zero means we are not in any of the arguments.
33089 ------------
33090 -- Arg_No --
33091 ------------
33093 function Arg_No return Nat is
33094 A : Node_Id;
33095 N : Nat;
33097 begin
33098 A := First (Pragma_Argument_Associations (Parent (P)));
33099 N := 1;
33100 loop
33101 if No (A) then
33102 return 0;
33103 elsif A = P then
33104 return N;
33105 end if;
33107 Next (A);
33108 N := N + 1;
33109 end loop;
33110 end Arg_No;
33112 -- Start of processing for Non_Significant_Pragma_Reference
33114 begin
33115 -- Reference might appear either directly as expression of a pragma
33116 -- argument association, e.g. pragma Export (...), or within an
33117 -- aggregate with component associations, e.g. pragma Refined_State
33118 -- ((... => ...)).
33120 P := Parent (N);
33121 loop
33122 case Nkind (P) is
33123 when N_Pragma_Argument_Association =>
33124 exit;
33125 when N_Aggregate | N_Component_Association =>
33126 P := Parent (P);
33127 when others =>
33128 return False;
33129 end case;
33130 end loop;
33132 AN := Arg_No;
33134 if AN = 0 then
33135 return False;
33136 end if;
33138 Id := Get_Pragma_Id (Parent (P));
33139 C := Sig_Flags (Id);
33141 case C is
33142 when -1 =>
33143 return False;
33145 when 0 =>
33146 return True;
33148 when 92 .. 99 =>
33149 return AN < (C - 90);
33151 when others =>
33152 return AN /= C;
33153 end case;
33154 end Is_Non_Significant_Pragma_Reference;
33156 ------------------------------
33157 -- Is_Pragma_String_Literal --
33158 ------------------------------
33160 -- This function returns true if the corresponding pragma argument is a
33161 -- static string expression. These are the only cases in which string
33162 -- literals can appear as pragma arguments. We also allow a string literal
33163 -- as the first argument to pragma Assert (although it will of course
33164 -- always generate a type error).
33166 function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
33167 Pragn : constant Node_Id := Parent (Par);
33168 Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
33169 Pname : constant Name_Id := Pragma_Name (Pragn);
33170 Argn : Natural;
33171 N : Node_Id;
33173 begin
33174 Argn := 1;
33175 N := First (Assoc);
33176 loop
33177 exit when N = Par;
33178 Argn := Argn + 1;
33179 Next (N);
33180 end loop;
33182 if Pname = Name_Assert then
33183 return True;
33185 elsif Pname = Name_Export then
33186 return Argn > 2;
33188 elsif Pname = Name_Ident then
33189 return Argn = 1;
33191 elsif Pname = Name_Import then
33192 return Argn > 2;
33194 elsif Pname = Name_Interface_Name then
33195 return Argn > 1;
33197 elsif Pname = Name_Linker_Alias then
33198 return Argn = 2;
33200 elsif Pname = Name_Linker_Section then
33201 return Argn = 2;
33203 elsif Pname = Name_Machine_Attribute then
33204 return Argn = 2;
33206 elsif Pname = Name_Source_File_Name then
33207 return True;
33209 elsif Pname = Name_Source_Reference then
33210 return Argn = 2;
33212 elsif Pname = Name_Title then
33213 return True;
33215 elsif Pname = Name_Subtitle then
33216 return True;
33218 else
33219 return False;
33220 end if;
33221 end Is_Pragma_String_Literal;
33223 ---------------------------
33224 -- Is_Private_SPARK_Mode --
33225 ---------------------------
33227 function Is_Private_SPARK_Mode (N : Node_Id) return Boolean is
33228 begin
33229 pragma Assert
33230 (Nkind (N) = N_Pragma
33231 and then Pragma_Name (N) = Name_SPARK_Mode
33232 and then Is_List_Member (N));
33234 -- For pragma SPARK_Mode to be private, it has to appear in the private
33235 -- declarations of a package.
33237 return
33238 Present (Parent (N))
33239 and then Nkind (Parent (N)) = N_Package_Specification
33240 and then List_Containing (N) = Private_Declarations (Parent (N));
33241 end Is_Private_SPARK_Mode;
33243 -----------------------------
33244 -- Is_Valid_Assertion_Kind --
33245 -----------------------------
33247 function Is_Valid_Assertion_Kind (Nam : Name_Id) return Boolean is
33248 begin
33249 case Nam is
33250 when
33251 -- RM defined
33253 Name_Assert
33254 | Name_Static_Predicate
33255 | Name_Dynamic_Predicate
33256 | Name_Pre
33257 | Name_uPre
33258 | Name_Post
33259 | Name_uPost
33260 | Name_Type_Invariant
33261 | Name_uType_Invariant
33263 -- Impl defined
33265 | Name_Assert_And_Cut
33266 | Name_Assume
33267 | Name_Contract_Cases
33268 | Name_Debug
33269 | Name_Default_Initial_Condition
33270 | Name_Ghost
33271 | Name_Ghost_Predicate
33272 | Name_Initial_Condition
33273 | Name_Invariant
33274 | Name_uInvariant
33275 | Name_Loop_Invariant
33276 | Name_Loop_Variant
33277 | Name_Postcondition
33278 | Name_Precondition
33279 | Name_Predicate
33280 | Name_Refined_Post
33281 | Name_Statement_Assertions
33282 | Name_Subprogram_Variant
33284 return True;
33286 when others =>
33287 return False;
33288 end case;
33289 end Is_Valid_Assertion_Kind;
33291 --------------------------------------
33292 -- Process_Compilation_Unit_Pragmas --
33293 --------------------------------------
33295 procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
33296 begin
33297 -- A special check for pragma Suppress_All, a very strange DEC pragma,
33298 -- strange because it comes at the end of the unit. Rational has the
33299 -- same name for a pragma, but treats it as a program unit pragma, In
33300 -- GNAT we just decide to allow it anywhere at all. If it appeared then
33301 -- the flag Has_Pragma_Suppress_All was set on the compilation unit
33302 -- node, and we insert a pragma Suppress (All_Checks) at the start of
33303 -- the context clause to ensure the correct processing.
33305 if Has_Pragma_Suppress_All (N) then
33306 Prepend_To (Context_Items (N),
33307 Make_Pragma (Sloc (N),
33308 Chars => Name_Suppress,
33309 Pragma_Argument_Associations => New_List (
33310 Make_Pragma_Argument_Association (Sloc (N),
33311 Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
33312 end if;
33314 -- Nothing else to do at the current time
33316 end Process_Compilation_Unit_Pragmas;
33318 --------------------------------------------
33319 -- Validate_Compile_Time_Warning_Or_Error --
33320 --------------------------------------------
33322 procedure Validate_Compile_Time_Warning_Or_Error
33323 (N : Node_Id;
33324 Eloc : Source_Ptr)
33326 Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
33327 Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
33328 Arg2 : constant Node_Id := Next (Arg1);
33330 Pname : constant Name_Id := Pragma_Name_Unmapped (N);
33331 Prag_Id : constant Pragma_Id := Get_Pragma_Id (Pname);
33333 begin
33334 Analyze_And_Resolve (Arg1x, Standard_Boolean);
33336 if Compile_Time_Known_Value (Arg1x) then
33337 if Is_True (Expr_Value (Arg1x)) then
33339 -- We have already verified that the second argument is a static
33340 -- string expression. Its string value must be retrieved
33341 -- explicitly if it is a declared constant, otherwise it has
33342 -- been constant-folded previously.
33344 declare
33345 Cent : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
33346 Str : constant String_Id :=
33347 Strval (Expr_Value_S (Get_Pragma_Arg (Arg2)));
33348 Str_Len : constant Nat := String_Length (Str);
33350 Force : constant Boolean :=
33351 Prag_Id = Pragma_Compile_Time_Warning
33352 and then Is_Spec_Name (Unit_Name (Current_Sem_Unit))
33353 and then (Ekind (Cent) /= E_Package
33354 or else not In_Private_Part (Cent));
33355 -- Set True if this is the warning case, and we are in the
33356 -- visible part of a package spec, or in a subprogram spec,
33357 -- in which case we want to force the client to see the
33358 -- warning, even though it is not in the main unit.
33360 C : Character;
33361 CC : Char_Code;
33362 Cont : Boolean;
33363 Ptr : Nat;
33365 begin
33366 -- Loop through segments of message separated by line feeds.
33367 -- We output these segments as separate messages with
33368 -- continuation marks for all but the first.
33370 Cont := False;
33371 Ptr := 1;
33372 loop
33373 Error_Msg_Strlen := 0;
33375 -- Loop to copy characters from argument to error message
33376 -- string buffer.
33378 loop
33379 exit when Ptr > Str_Len;
33380 CC := Get_String_Char (Str, Ptr);
33381 Ptr := Ptr + 1;
33383 -- Ignore wide chars ??? else store character
33385 if In_Character_Range (CC) then
33386 C := Get_Character (CC);
33387 exit when C = ASCII.LF;
33388 Error_Msg_Strlen := Error_Msg_Strlen + 1;
33389 Error_Msg_String (Error_Msg_Strlen) := C;
33390 end if;
33391 end loop;
33393 -- Here with one line ready to go
33395 Error_Msg_Warn := Prag_Id = Pragma_Compile_Time_Warning;
33397 -- If this is a warning in a spec, then we want clients
33398 -- to see the warning, so mark the message with the
33399 -- special sequence !! to force the warning. In the case
33400 -- of a package spec, we do not force this if we are in
33401 -- the private part of the spec.
33403 if Force then
33404 if Cont = False then
33405 Error_Msg
33406 ("<<~!!", Eloc, N, Is_Compile_Time_Pragma => True);
33407 Cont := True;
33408 else
33409 Error_Msg
33410 ("\<<~!!", Eloc, N, Is_Compile_Time_Pragma => True);
33411 end if;
33413 -- Error, rather than warning, or in a body, so we do not
33414 -- need to force visibility for client (error will be
33415 -- output in any case, and this is the situation in which
33416 -- we do not want a client to get a warning, since the
33417 -- warning is in the body or the spec private part).
33419 else
33420 if Cont = False then
33421 Error_Msg
33422 ("<<~", Eloc, N, Is_Compile_Time_Pragma => True);
33423 Cont := True;
33424 else
33425 Error_Msg
33426 ("\<<~", Eloc, N, Is_Compile_Time_Pragma => True);
33427 end if;
33428 end if;
33430 exit when Ptr > Str_Len;
33431 end loop;
33432 end;
33433 end if;
33435 -- Arg1x is not known at compile time, so possibly issue an error
33436 -- or warning. This can happen only if the pragma's processing
33437 -- was deferred until after the back end is run (see
33438 -- Process_Compile_Time_Warning_Or_Error). Note that the warning
33439 -- control switch applies to only the warning case.
33441 elsif Prag_Id = Pragma_Compile_Time_Error then
33442 Error_Msg_N ("condition is not known at compile time", Arg1x);
33444 elsif Warn_On_Unknown_Compile_Time_Warning then
33445 Error_Msg_N ("?_c?condition is not known at compile time", Arg1x);
33446 end if;
33447 end Validate_Compile_Time_Warning_Or_Error;
33449 ------------------------------------
33450 -- Record_Possible_Body_Reference --
33451 ------------------------------------
33453 procedure Record_Possible_Body_Reference
33454 (State_Id : Entity_Id;
33455 Ref : Node_Id)
33457 Context : Node_Id;
33458 Spec_Id : Entity_Id;
33460 begin
33461 -- Ensure that we are dealing with a reference to a state
33463 pragma Assert (Ekind (State_Id) = E_Abstract_State);
33465 -- Climb the tree starting from the reference looking for a package body
33466 -- whose spec declares the referenced state. This criteria automatically
33467 -- excludes references in package specs which are legal. Note that it is
33468 -- not wise to emit an error now as the package body may lack pragma
33469 -- Refined_State or the referenced state may not be mentioned in the
33470 -- refinement. This approach avoids the generation of misleading errors.
33472 Context := Ref;
33473 while Present (Context) loop
33474 if Nkind (Context) = N_Package_Body then
33475 Spec_Id := Corresponding_Spec (Context);
33477 if Contains (Abstract_States (Spec_Id), State_Id) then
33478 if No (Body_References (State_Id)) then
33479 Set_Body_References (State_Id, New_Elmt_List);
33480 end if;
33482 Append_Elmt (Ref, To => Body_References (State_Id));
33483 exit;
33484 end if;
33485 end if;
33487 Context := Parent (Context);
33488 end loop;
33489 end Record_Possible_Body_Reference;
33491 ------------------------------------------
33492 -- Relocate_Pragmas_To_Anonymous_Object --
33493 ------------------------------------------
33495 procedure Relocate_Pragmas_To_Anonymous_Object
33496 (Typ_Decl : Node_Id;
33497 Obj_Decl : Node_Id)
33499 Decl : Node_Id;
33500 Def : Node_Id;
33501 Next_Decl : Node_Id;
33503 begin
33504 if Nkind (Typ_Decl) = N_Protected_Type_Declaration then
33505 Def := Protected_Definition (Typ_Decl);
33506 else
33507 pragma Assert (Nkind (Typ_Decl) = N_Task_Type_Declaration);
33508 Def := Task_Definition (Typ_Decl);
33509 end if;
33511 -- The concurrent definition has a visible declaration list. Inspect it
33512 -- and relocate all canidate pragmas.
33514 if Present (Def) and then Present (Visible_Declarations (Def)) then
33515 Decl := First (Visible_Declarations (Def));
33516 while Present (Decl) loop
33518 -- Preserve the following declaration for iteration purposes due
33519 -- to possible relocation of a pragma.
33521 Next_Decl := Next (Decl);
33523 if Nkind (Decl) = N_Pragma
33524 and then Pragma_On_Anonymous_Object_OK (Get_Pragma_Id (Decl))
33525 then
33526 Remove (Decl);
33527 Insert_After (Obj_Decl, Decl);
33529 -- Skip internally generated code
33531 elsif not Comes_From_Source (Decl) then
33532 null;
33534 -- No candidate pragmas are available for relocation
33536 else
33537 exit;
33538 end if;
33540 Decl := Next_Decl;
33541 end loop;
33542 end if;
33543 end Relocate_Pragmas_To_Anonymous_Object;
33545 ------------------------------
33546 -- Relocate_Pragmas_To_Body --
33547 ------------------------------
33549 procedure Relocate_Pragmas_To_Body
33550 (Subp_Body : Node_Id;
33551 Target_Body : Node_Id := Empty)
33553 procedure Relocate_Pragma (Prag : Node_Id);
33554 -- Remove a single pragma from its current list and add it to the
33555 -- declarations of the proper body (either Subp_Body or Target_Body).
33557 ---------------------
33558 -- Relocate_Pragma --
33559 ---------------------
33561 procedure Relocate_Pragma (Prag : Node_Id) is
33562 Decls : List_Id;
33563 Target : Node_Id;
33565 begin
33566 -- When subprogram stubs or expression functions are involves, the
33567 -- destination declaration list belongs to the proper body.
33569 if Present (Target_Body) then
33570 Target := Target_Body;
33571 else
33572 Target := Subp_Body;
33573 end if;
33575 Decls := Declarations (Target);
33577 if No (Decls) then
33578 Decls := New_List;
33579 Set_Declarations (Target, Decls);
33580 end if;
33582 -- Unhook the pragma from its current list
33584 Remove (Prag);
33585 Prepend (Prag, Decls);
33586 end Relocate_Pragma;
33588 -- Local variables
33590 Body_Id : constant Entity_Id :=
33591 Defining_Unit_Name (Specification (Subp_Body));
33592 Next_Stmt : Node_Id;
33593 Stmt : Node_Id;
33595 -- Start of processing for Relocate_Pragmas_To_Body
33597 begin
33598 -- Do not process a body that comes from a separate unit as no construct
33599 -- can possibly follow it.
33601 if not Is_List_Member (Subp_Body) then
33602 return;
33604 -- Do not relocate pragmas that follow a stub if the stub does not have
33605 -- a proper body.
33607 elsif Nkind (Subp_Body) = N_Subprogram_Body_Stub
33608 and then No (Target_Body)
33609 then
33610 return;
33612 -- Do not process internally generated routine _Wrapped_Statements
33614 elsif Ekind (Body_Id) = E_Procedure
33615 and then Chars (Body_Id) = Name_uWrapped_Statements
33616 then
33617 return;
33618 end if;
33620 -- Look at what is following the body. We are interested in certain kind
33621 -- of pragmas (either from source or byproducts of expansion) that can
33622 -- apply to a body [stub].
33624 Stmt := Next (Subp_Body);
33625 while Present (Stmt) loop
33627 -- Preserve the following statement for iteration purposes due to a
33628 -- possible relocation of a pragma.
33630 Next_Stmt := Next (Stmt);
33632 -- Move a candidate pragma following the body to the declarations of
33633 -- the body.
33635 if Nkind (Stmt) = N_Pragma
33636 and then Pragma_On_Body_Or_Stub_OK (Get_Pragma_Id (Stmt))
33637 then
33639 -- If a source pragma Warnings follows the body, it applies to
33640 -- following statements and does not belong in the body.
33642 if Get_Pragma_Id (Stmt) = Pragma_Warnings
33643 and then Comes_From_Source (Stmt)
33644 then
33645 null;
33646 else
33647 Relocate_Pragma (Stmt);
33648 end if;
33650 -- Skip internally generated code
33652 elsif not Comes_From_Source (Stmt) then
33653 null;
33655 -- No candidate pragmas are available for relocation
33657 else
33658 exit;
33659 end if;
33661 Stmt := Next_Stmt;
33662 end loop;
33663 end Relocate_Pragmas_To_Body;
33665 -------------------
33666 -- Resolve_State --
33667 -------------------
33669 procedure Resolve_State (N : Node_Id) is
33670 Func : Entity_Id;
33671 State : Entity_Id;
33673 begin
33674 if Is_Entity_Name (N) and then Present (Entity (N)) then
33675 Func := Entity (N);
33677 -- Handle overloading of state names by functions. Traverse the
33678 -- homonym chain looking for an abstract state.
33680 if Ekind (Func) = E_Function and then Has_Homonym (Func) then
33681 pragma Assert (Is_Overloaded (N));
33683 State := Homonym (Func);
33684 while Present (State) loop
33685 if Ekind (State) = E_Abstract_State then
33687 -- Resolve the overloading by setting the proper entity of
33688 -- the reference to that of the state.
33690 Set_Etype (N, Standard_Void_Type);
33691 Set_Entity (N, State);
33692 Set_Is_Overloaded (N, False);
33694 Generate_Reference (State, N);
33695 return;
33696 end if;
33698 State := Homonym (State);
33699 end loop;
33701 -- A function can never act as a state. If the homonym chain does
33702 -- not contain a corresponding state, then something went wrong in
33703 -- the overloading mechanism.
33705 raise Program_Error;
33706 end if;
33707 end if;
33708 end Resolve_State;
33710 ----------------------------
33711 -- Rewrite_Assertion_Kind --
33712 ----------------------------
33714 procedure Rewrite_Assertion_Kind
33715 (N : Node_Id;
33716 From_Policy : Boolean := False)
33718 Nam : Name_Id;
33720 begin
33721 Nam := No_Name;
33722 if Nkind (N) = N_Attribute_Reference
33723 and then Attribute_Name (N) = Name_Class
33724 and then Nkind (Prefix (N)) = N_Identifier
33725 then
33726 case Chars (Prefix (N)) is
33727 when Name_Pre =>
33728 Nam := Name_uPre;
33730 when Name_Post =>
33731 Nam := Name_uPost;
33733 when Name_Type_Invariant =>
33734 Nam := Name_uType_Invariant;
33736 when Name_Invariant =>
33737 Nam := Name_uInvariant;
33739 when others =>
33740 return;
33741 end case;
33743 -- Recommend standard use of aspect names Pre/Post
33745 elsif Nkind (N) = N_Identifier
33746 and then From_Policy
33747 and then Serious_Errors_Detected = 0
33748 then
33749 if Chars (N) = Name_Precondition
33750 or else Chars (N) = Name_Postcondition
33751 then
33752 Error_Msg_N ("Check_Policy is a non-standard pragma??", N);
33753 Error_Msg_N
33754 ("\use Assertion_Policy and aspect names Pre/Post for "
33755 & "Ada2012 conformance??", N);
33756 end if;
33758 return;
33759 end if;
33761 if Nam /= No_Name then
33762 Rewrite (N, Make_Identifier (Sloc (N), Chars => Nam));
33763 end if;
33764 end Rewrite_Assertion_Kind;
33766 --------
33767 -- rv --
33768 --------
33770 procedure rv is
33771 begin
33772 Dummy := Dummy + 1;
33773 end rv;
33775 --------------------------------
33776 -- Set_Encoded_Interface_Name --
33777 --------------------------------
33779 procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
33780 Str : constant String_Id := Strval (S);
33781 Len : constant Nat := String_Length (Str);
33782 CC : Char_Code;
33783 C : Character;
33784 J : Pos;
33786 Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
33788 procedure Encode;
33789 -- Stores encoded value of character code CC. The encoding we use an
33790 -- underscore followed by four lower case hex digits.
33792 ------------
33793 -- Encode --
33794 ------------
33796 procedure Encode is
33797 begin
33798 Store_String_Char (Get_Char_Code ('_'));
33799 Store_String_Char
33800 (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
33801 Store_String_Char
33802 (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
33803 Store_String_Char
33804 (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
33805 Store_String_Char
33806 (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
33807 end Encode;
33809 -- Start of processing for Set_Encoded_Interface_Name
33811 begin
33812 -- If first character is asterisk, this is a link name, and we leave it
33813 -- completely unmodified. We also ignore null strings (the latter case
33814 -- happens only in error cases).
33816 if Len = 0
33817 or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
33818 then
33819 Set_Interface_Name (E, S);
33821 else
33822 J := 1;
33823 loop
33824 CC := Get_String_Char (Str, J);
33826 exit when not In_Character_Range (CC);
33828 C := Get_Character (CC);
33830 exit when C /= '_' and then C /= '$'
33831 and then C not in '0' .. '9'
33832 and then C not in 'a' .. 'z'
33833 and then C not in 'A' .. 'Z';
33835 if J = Len then
33836 Set_Interface_Name (E, S);
33837 return;
33839 else
33840 J := J + 1;
33841 end if;
33842 end loop;
33844 -- Here we need to encode. The encoding we use as follows:
33845 -- three underscores + four hex digits (lower case)
33847 Start_String;
33849 for J in 1 .. String_Length (Str) loop
33850 CC := Get_String_Char (Str, J);
33852 if not In_Character_Range (CC) then
33853 Encode;
33854 else
33855 C := Get_Character (CC);
33857 if C = '_' or else C = '$'
33858 or else C in '0' .. '9'
33859 or else C in 'a' .. 'z'
33860 or else C in 'A' .. 'Z'
33861 then
33862 Store_String_Char (CC);
33863 else
33864 Encode;
33865 end if;
33866 end if;
33867 end loop;
33869 Set_Interface_Name (E,
33870 Make_String_Literal (Sloc (S),
33871 Strval => End_String));
33872 end if;
33873 end Set_Encoded_Interface_Name;
33875 ------------------------
33876 -- Set_Elab_Unit_Name --
33877 ------------------------
33879 procedure Set_Elab_Unit_Name (N : Node_Id; With_Item : Node_Id) is
33880 Pref : Node_Id;
33881 Scop : Entity_Id;
33883 begin
33884 if Nkind (N) = N_Identifier
33885 and then Nkind (With_Item) = N_Identifier
33886 then
33887 Set_Entity (N, Entity (With_Item));
33889 elsif Nkind (N) = N_Selected_Component then
33890 Change_Selected_Component_To_Expanded_Name (N);
33891 Set_Entity (N, Entity (With_Item));
33892 Set_Entity (Selector_Name (N), Entity (N));
33894 Pref := Prefix (N);
33895 Scop := Scope (Entity (N));
33896 while Nkind (Pref) = N_Selected_Component loop
33897 Change_Selected_Component_To_Expanded_Name (Pref);
33898 Set_Entity (Selector_Name (Pref), Scop);
33899 Set_Entity (Pref, Scop);
33900 Pref := Prefix (Pref);
33901 Scop := Scope (Scop);
33902 end loop;
33904 Set_Entity (Pref, Scop);
33905 end if;
33907 Generate_Reference (Entity (With_Item), N, Set_Ref => False);
33908 end Set_Elab_Unit_Name;
33910 -----------------------
33911 -- Set_Overflow_Mode --
33912 -----------------------
33914 procedure Set_Overflow_Mode (N : Node_Id) is
33916 function Get_Overflow_Mode (Arg : Node_Id) return Overflow_Mode_Type;
33917 -- Function to process one pragma argument, Arg
33919 -----------------------
33920 -- Get_Overflow_Mode --
33921 -----------------------
33923 function Get_Overflow_Mode (Arg : Node_Id) return Overflow_Mode_Type is
33924 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
33926 begin
33927 if Chars (Argx) = Name_Strict then
33928 return Strict;
33930 elsif Chars (Argx) = Name_Minimized then
33931 return Minimized;
33933 elsif Chars (Argx) = Name_Eliminated then
33934 return Eliminated;
33936 else
33937 raise Program_Error;
33938 end if;
33939 end Get_Overflow_Mode;
33941 -- Local variables
33943 Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
33944 Arg2 : constant Node_Id := Next (Arg1);
33946 -- Start of processing for Set_Overflow_Mode
33948 begin
33949 -- Process first argument
33951 Scope_Suppress.Overflow_Mode_General :=
33952 Get_Overflow_Mode (Arg1);
33954 -- Case of only one argument
33956 if No (Arg2) then
33957 Scope_Suppress.Overflow_Mode_Assertions :=
33958 Scope_Suppress.Overflow_Mode_General;
33960 -- Case of two arguments present
33962 else
33963 Scope_Suppress.Overflow_Mode_Assertions :=
33964 Get_Overflow_Mode (Arg2);
33965 end if;
33966 end Set_Overflow_Mode;
33968 -------------------
33969 -- Test_Case_Arg --
33970 -------------------
33972 function Test_Case_Arg
33973 (Prag : Node_Id;
33974 Arg_Nam : Name_Id;
33975 From_Aspect : Boolean := False) return Node_Id
33977 Aspect : constant Node_Id := Corresponding_Aspect (Prag);
33978 Arg : Node_Id;
33979 Args : Node_Id;
33981 begin
33982 pragma Assert
33983 (Arg_Nam in Name_Ensures | Name_Mode | Name_Name | Name_Requires);
33985 -- The caller requests the aspect argument
33987 if From_Aspect then
33988 if Present (Aspect)
33989 and then Nkind (Expression (Aspect)) = N_Aggregate
33990 then
33991 Args := Expression (Aspect);
33993 -- "Name" and "Mode" may appear without an identifier as a
33994 -- positional association.
33996 if Present (Expressions (Args)) then
33997 Arg := First (Expressions (Args));
33999 if Present (Arg) and then Arg_Nam = Name_Name then
34000 return Arg;
34001 end if;
34003 -- Skip "Name"
34005 Arg := Next (Arg);
34007 if Present (Arg) and then Arg_Nam = Name_Mode then
34008 return Arg;
34009 end if;
34010 end if;
34012 -- Some or all arguments may appear as component associatons
34014 if Present (Component_Associations (Args)) then
34015 Arg := First (Component_Associations (Args));
34016 while Present (Arg) loop
34017 if Chars (First (Choices (Arg))) = Arg_Nam then
34018 return Arg;
34019 end if;
34021 Next (Arg);
34022 end loop;
34023 end if;
34024 end if;
34026 -- Otherwise retrieve the argument directly from the pragma
34028 else
34029 Arg := First (Pragma_Argument_Associations (Prag));
34031 if Present (Arg) and then Arg_Nam = Name_Name then
34032 return Arg;
34033 end if;
34035 -- Skip argument "Name"
34037 Arg := Next (Arg);
34039 if Present (Arg) and then Arg_Nam = Name_Mode then
34040 return Arg;
34041 end if;
34043 -- Skip argument "Mode"
34045 Arg := Next (Arg);
34047 -- Arguments "Requires" and "Ensures" are optional and may not be
34048 -- present at all.
34050 while Present (Arg) loop
34051 if Chars (Arg) = Arg_Nam then
34052 return Arg;
34053 end if;
34055 Next (Arg);
34056 end loop;
34057 end if;
34059 return Empty;
34060 end Test_Case_Arg;
34062 --------------------------------------------
34063 -- Defer_Compile_Time_Warning_Error_To_BE --
34064 --------------------------------------------
34066 procedure Defer_Compile_Time_Warning_Error_To_BE (N : Node_Id) is
34067 Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
34068 begin
34069 Compile_Time_Warnings_Errors.Append
34070 (New_Val => CTWE_Entry'(Eloc => Sloc (Arg1),
34071 Scope => Current_Scope,
34072 Prag => N));
34074 -- If the Boolean expression contains T'Size, and we're not in the main
34075 -- unit being compiled, then we need to copy the pragma into the main
34076 -- unit, because otherwise T'Size might never be computed, leaving it
34077 -- as 0.
34079 if not In_Extended_Main_Code_Unit (N) then
34080 -- We've created an Itype for the string in this pragma and
34081 -- may have made other Itypes. When we copy the entire tree
34082 -- of this pragma, we'll make a second copy of them in its
34083 -- unit, which will mess up the numbering of the remaining
34084 -- internal names.
34086 declare
34087 Saved_Current_Sem_Unit : constant Unit_Number_Type :=
34088 Current_Sem_Unit;
34089 New_N : Node_Id;
34091 begin
34092 Current_Sem_Unit := Main_Unit;
34093 New_N := New_Copy_Tree (N);
34094 Current_Sem_Unit := Saved_Current_Sem_Unit;
34095 Insert_Library_Level_Action (New_N);
34096 end;
34097 end if;
34098 end Defer_Compile_Time_Warning_Error_To_BE;
34100 ------------------------------------------
34101 -- Validate_Compile_Time_Warning_Errors --
34102 ------------------------------------------
34104 procedure Validate_Compile_Time_Warning_Errors is
34105 procedure Set_Scope (S : Entity_Id);
34106 -- Install all enclosing scopes of S along with S itself
34108 procedure Unset_Scope (S : Entity_Id);
34109 -- Uninstall all enclosing scopes of S along with S itself
34111 ---------------
34112 -- Set_Scope --
34113 ---------------
34115 procedure Set_Scope (S : Entity_Id) is
34116 begin
34117 if S /= Standard_Standard then
34118 Set_Scope (Scope (S));
34119 end if;
34121 Push_Scope (S);
34122 end Set_Scope;
34124 -----------------
34125 -- Unset_Scope --
34126 -----------------
34128 procedure Unset_Scope (S : Entity_Id) is
34129 begin
34130 if S /= Standard_Standard then
34131 Unset_Scope (Scope (S));
34132 end if;
34134 Pop_Scope;
34135 end Unset_Scope;
34137 -- Start of processing for Validate_Compile_Time_Warning_Errors
34139 begin
34140 -- These error/warning messages were deferred because they could not be
34141 -- evaluated in the front-end and they needed additional information
34142 -- from the back-end. There is no reason to run these checks again if
34143 -- the back-end was not activated by this point.
34145 if not Generating_Code then
34146 return;
34147 end if;
34149 Expander_Mode_Save_And_Set (False);
34150 In_Compile_Time_Warning_Or_Error := True;
34152 for N in Compile_Time_Warnings_Errors.First ..
34153 Compile_Time_Warnings_Errors.Last
34154 loop
34155 declare
34156 T : CTWE_Entry renames Compile_Time_Warnings_Errors.Table (N);
34158 begin
34159 Set_Scope (T.Scope);
34160 Reset_Analyzed_Flags (T.Prag);
34161 Validate_Compile_Time_Warning_Or_Error (T.Prag, T.Eloc);
34162 Unset_Scope (T.Scope);
34163 end;
34164 end loop;
34166 In_Compile_Time_Warning_Or_Error := False;
34167 Expander_Mode_Restore;
34168 end Validate_Compile_Time_Warning_Errors;
34170 end Sem_Prag;