MATCH: Improve `A CMP 0 ? A : -A` set of patterns to use bitwise_equal_p.
[official-gcc.git] / gcc / ada / sem_prag.adb
blob6de87fbaba9611e9db71996416c91f74a94980de
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-2023, 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_Part_Of
190 (Indic : Node_Id;
191 Item_Id : Entity_Id;
192 Encap : Node_Id;
193 Encap_Id : out Entity_Id;
194 Legal : out Boolean);
195 -- Subsidiary to Analyze_Part_Of_In_Decl_Part, Analyze_Part_Of_Option and
196 -- Analyze_Pragma. Perform full analysis of indicator Part_Of. Indic is the
197 -- Part_Of indicator. Item_Id is the entity of an abstract state, object or
198 -- package instantiation. Encap denotes the encapsulating state or single
199 -- concurrent type. Encap_Id is the entity of Encap. Flag Legal is set when
200 -- the indicator is legal.
202 function Appears_In (List : Elist_Id; Item_Id : Entity_Id) return Boolean;
203 -- Subsidiary to analysis of pragmas Depends, Global and Refined_Depends.
204 -- Query whether a particular item appears in a mixed list of nodes and
205 -- entities. It is assumed that all nodes in the list have entities.
207 procedure Check_Postcondition_Use_In_Inlined_Subprogram
208 (Prag : Node_Id;
209 Spec_Id : Entity_Id);
210 -- Subsidiary to the analysis of pragmas Contract_Cases, Postcondition,
211 -- Precondition, Refined_Post, Subprogram_Variant, and Test_Case. Emit a
212 -- warning when pragma Prag is associated with subprogram Spec_Id subject
213 -- to Inline_Always, assertions are enabled and inling is done in the
214 -- frontend.
216 procedure Check_State_And_Constituent_Use
217 (States : Elist_Id;
218 Constits : Elist_Id;
219 Context : Node_Id);
220 -- Subsidiary to the analysis of pragmas [Refined_]Depends, [Refined_]
221 -- Global and Initializes. Determine whether a state from list States and a
222 -- corresponding constituent from list Constits (if any) appear in the same
223 -- context denoted by Context. If this is the case, emit an error.
225 procedure Contract_Freeze_Error
226 (Contract_Id : Entity_Id;
227 Freeze_Id : Entity_Id);
228 -- Subsidiary to the analysis of pragmas Contract_Cases, Exceptional_Cases,
229 -- Part_Of, Post, Pre and Subprogram_Variant. Emit a freezing-related error
230 -- message where Freeze_Id is the entity of a body which caused contract
231 -- freezing and Contract_Id denotes the entity of the affected contstruct.
233 procedure Duplication_Error (Prag : Node_Id; Prev : Node_Id);
234 -- Subsidiary to all Find_Related_xxx routines. Emit an error on pragma
235 -- Prag that duplicates previous pragma Prev.
237 function Find_Encapsulating_State
238 (States : Elist_Id;
239 Constit_Id : Entity_Id) return Entity_Id;
240 -- Given the entity of a constituent Constit_Id, find the corresponding
241 -- encapsulating state which appears in States. The routine returns Empty
242 -- if no such state is found.
244 function Find_Related_Context
245 (Prag : Node_Id;
246 Do_Checks : Boolean := False) return Node_Id;
247 -- Subsidiary to the analysis of pragmas
248 -- Async_Readers
249 -- Async_Writers
250 -- Constant_After_Elaboration
251 -- Effective_Reads
252 -- Effective_Writers
253 -- No_Caching
254 -- Part_Of
255 -- Find the first source declaration or statement found while traversing
256 -- the previous node chain starting from pragma Prag. If flag Do_Checks is
257 -- set, the routine reports duplicate pragmas. The routine returns Empty
258 -- when reaching the start of the node chain.
260 function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id;
261 -- If Def_Id refers to a renamed subprogram, then the base subprogram (the
262 -- original one, following the renaming chain) is returned. Otherwise the
263 -- entity is returned unchanged. Should be in Einfo???
265 function Get_SPARK_Mode_Type (N : Name_Id) return SPARK_Mode_Type;
266 -- Subsidiary to the analysis of pragma SPARK_Mode as well as subprogram
267 -- Get_SPARK_Mode_From_Annotation. Convert a name into a corresponding
268 -- value of type SPARK_Mode_Type.
270 function Has_Extra_Parentheses (Clause : Node_Id) return Boolean;
271 -- Subsidiary to the analysis of pragmas Depends and Refined_Depends.
272 -- Determine whether dependency clause Clause is surrounded by extra
273 -- parentheses. If this is the case, issue an error message.
275 function Is_Unconstrained_Or_Tagged_Item (Item : Entity_Id) return Boolean;
276 -- Subsidiary to Collect_Subprogram_Inputs_Outputs and the analysis of
277 -- pragma Depends. Determine whether the type of dependency item Item is
278 -- tagged, unconstrained array, unconstrained record or a record with at
279 -- least one unconstrained component.
281 procedure Record_Possible_Body_Reference
282 (State_Id : Entity_Id;
283 Ref : Node_Id);
284 -- Subsidiary to the analysis of pragmas [Refined_]Depends and [Refined_]
285 -- Global. Given an abstract state denoted by State_Id and a reference Ref
286 -- to it, determine whether the reference appears in a package body that
287 -- will eventually refine the state. If this is the case, record the
288 -- reference for future checks (see Analyze_Refined_State_In_Decls).
290 procedure Resolve_State (N : Node_Id);
291 -- Handle the overloading of state names by functions. When N denotes a
292 -- function, this routine finds the corresponding state and sets the entity
293 -- of N to that of the state.
295 procedure Rewrite_Assertion_Kind
296 (N : Node_Id;
297 From_Policy : Boolean := False);
298 -- If N is Pre'Class, Post'Class, Invariant'Class, or Type_Invariant'Class,
299 -- then it is rewritten as an identifier with the corresponding special
300 -- name _Pre, _Post, _Invariant, or _Type_Invariant. Used by pragmas Check
301 -- and Check_Policy. If the names are Precondition or Postcondition, this
302 -- combination is deprecated in favor of Assertion_Policy and Ada2012
303 -- Aspect names. The parameter From_Policy indicates that the pragma
304 -- is the old non-standard Check_Policy and not a rewritten pragma.
306 procedure Set_Elab_Unit_Name (N : Node_Id; With_Item : Node_Id);
307 -- Place semantic information on the argument of an Elaborate/Elaborate_All
308 -- pragma. Entity name for unit and its parents is taken from item in
309 -- previous with_clause that mentions the unit.
311 procedure Validate_Compile_Time_Warning_Or_Error
312 (N : Node_Id;
313 Eloc : Source_Ptr);
314 -- Common processing for Compile_Time_Error and Compile_Time_Warning of
315 -- pragma N. Called when the pragma is processed as part of its regular
316 -- analysis but also called after calling the back end to validate these
317 -- pragmas for size and alignment appropriateness.
319 procedure Defer_Compile_Time_Warning_Error_To_BE (N : Node_Id);
320 -- N is a pragma Compile_Time_Error or Compile_Warning_Error whose boolean
321 -- expression is not known at compile time during the front end. This
322 -- procedure makes an entry in a table. The actual checking is performed by
323 -- Validate_Compile_Time_Warning_Errors, which is invoked after calling the
324 -- back end.
326 Dummy : Integer := 0;
327 pragma Volatile (Dummy);
328 -- Dummy volatile integer used in bodies of ip/rv to prevent optimization
330 procedure ip;
331 pragma No_Inline (ip);
332 -- A dummy procedure called when pragma Inspection_Point is analyzed. This
333 -- is just to help debugging the front end. If a pragma Inspection_Point
334 -- is added to a source program, then breaking on ip will get you to that
335 -- point in the program.
337 procedure rv;
338 pragma No_Inline (rv);
339 -- This is a dummy function called by the processing for pragma Reviewable.
340 -- It is there for assisting front end debugging. By placing a Reviewable
341 -- pragma in the source program, a breakpoint on rv catches this place in
342 -- the source, allowing convenient stepping to the point of interest.
344 ------------------------------------------------------
345 -- Table for Defer_Compile_Time_Warning_Error_To_BE --
346 ------------------------------------------------------
348 -- The following table collects pragmas Compile_Time_Error and Compile_
349 -- Time_Warning for validation. Entries are made by calls to subprogram
350 -- Defer_Compile_Time_Warning_Error_To_BE, and the call to the procedure
351 -- Validate_Compile_Time_Warning_Errors does the actual error checking
352 -- and posting of warning and error messages. The reason for this delayed
353 -- processing is to take advantage of back-annotations of attributes size
354 -- and alignment values performed by the back end.
356 -- Note: the reason we store a Source_Ptr value instead of a Node_Id is
357 -- that by the time Validate_Compile_Time_Warning_Errors is called, Sprint
358 -- will already have modified all Sloc values if the -gnatD option is set.
360 type CTWE_Entry is record
361 Eloc : Source_Ptr;
362 -- Source location used in warnings and error messages
364 Prag : Node_Id;
365 -- Pragma Compile_Time_Error or Compile_Time_Warning
367 Scope : Node_Id;
368 -- The scope which encloses the pragma
369 end record;
371 package Compile_Time_Warnings_Errors is new Table.Table (
372 Table_Component_Type => CTWE_Entry,
373 Table_Index_Type => Int,
374 Table_Low_Bound => 1,
375 Table_Initial => 50,
376 Table_Increment => 200,
377 Table_Name => "Compile_Time_Warnings_Errors");
379 -------------------------------
380 -- Adjust_External_Name_Case --
381 -------------------------------
383 function Adjust_External_Name_Case (N : Node_Id) return Node_Id is
384 CC : Char_Code;
386 begin
387 -- Adjust case of literal if required
389 if Opt.External_Name_Exp_Casing = As_Is then
390 return N;
392 else
393 -- Copy existing string
395 Start_String;
397 -- Set proper casing
399 for J in 1 .. String_Length (Strval (N)) loop
400 CC := Get_String_Char (Strval (N), J);
402 if Opt.External_Name_Exp_Casing = Uppercase
403 and then CC in Get_Char_Code ('a') .. Get_Char_Code ('z')
404 then
405 Store_String_Char (CC - 32);
407 elsif Opt.External_Name_Exp_Casing = Lowercase
408 and then CC in Get_Char_Code ('A') .. Get_Char_Code ('Z')
409 then
410 Store_String_Char (CC + 32);
412 else
413 Store_String_Char (CC);
414 end if;
415 end loop;
417 return
418 Make_String_Literal (Sloc (N),
419 Strval => End_String);
420 end if;
421 end Adjust_External_Name_Case;
423 --------------------------------------------
424 -- Analyze_Always_Terminates_In_Decl_Part --
425 --------------------------------------------
427 procedure Analyze_Always_Terminates_In_Decl_Part
428 (N : Node_Id;
429 Freeze_Id : Entity_Id := Empty)
431 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
432 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
433 Arg1 : constant Node_Id :=
434 First (Pragma_Argument_Associations (N));
436 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
437 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
438 -- Save the Ghost-related attributes to restore on exit
440 Errors : Nat;
441 Restore_Scope : Boolean := False;
443 begin
444 -- Do not analyze the pragma multiple times
446 if Is_Analyzed_Pragma (N) then
447 return;
448 end if;
450 if Present (Arg1) then
452 -- Set the Ghost mode in effect from the pragma. Due to the delayed
453 -- analysis of the pragma, the Ghost mode at point of declaration and
454 -- point of analysis may not necessarily be the same. Use the mode in
455 -- effect at the point of declaration.
457 Set_Ghost_Mode (N);
459 -- Ensure that the subprogram and its formals are visible when
460 -- analyzing the expression of the pragma.
462 if not In_Open_Scopes (Spec_Id) then
463 Restore_Scope := True;
465 if Is_Generic_Subprogram (Spec_Id) then
466 Push_Scope (Spec_Id);
467 Install_Generic_Formals (Spec_Id);
468 else
469 Push_Scope (Spec_Id);
470 Install_Formals (Spec_Id);
471 end if;
472 end if;
474 Errors := Serious_Errors_Detected;
475 Preanalyze_Assert_Expression (Expression (Arg1), Standard_Boolean);
477 -- Emit a clarification message when the expression contains at least
478 -- one undefined reference, possibly due to contract freezing.
480 if Errors /= Serious_Errors_Detected
481 and then Present (Freeze_Id)
482 and then Has_Undefined_Reference (Expression (Arg1))
483 then
484 Contract_Freeze_Error (Spec_Id, Freeze_Id);
485 end if;
487 if Restore_Scope then
488 End_Scope;
489 end if;
491 Restore_Ghost_Region (Saved_GM, Saved_IGR);
492 end if;
494 Set_Is_Analyzed_Pragma (N);
496 end Analyze_Always_Terminates_In_Decl_Part;
498 -----------------------------------------
499 -- Analyze_Contract_Cases_In_Decl_Part --
500 -----------------------------------------
502 -- WARNING: This routine manages Ghost regions. Return statements must be
503 -- replaced by gotos which jump to the end of the routine and restore the
504 -- Ghost mode.
506 procedure Analyze_Contract_Cases_In_Decl_Part
507 (N : Node_Id;
508 Freeze_Id : Entity_Id := Empty)
510 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
511 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
513 Others_Seen : Boolean := False;
514 -- This flag is set when an "others" choice is encountered. It is used
515 -- to detect multiple illegal occurrences of "others".
517 procedure Analyze_Contract_Case (CCase : Node_Id);
518 -- Verify the legality of a single contract case
520 ---------------------------
521 -- Analyze_Contract_Case --
522 ---------------------------
524 procedure Analyze_Contract_Case (CCase : Node_Id) is
525 Case_Guard : Node_Id;
526 Conseq : Node_Id;
527 Errors : Nat;
528 Extra_Guard : Node_Id;
530 begin
531 if Nkind (CCase) = N_Component_Association then
532 Case_Guard := First (Choices (CCase));
533 Conseq := Expression (CCase);
535 -- Each contract case must have exactly one case guard
537 Extra_Guard := Next (Case_Guard);
539 if Present (Extra_Guard) then
540 Error_Msg_N
541 ("contract case must have exactly one case guard",
542 Extra_Guard);
543 end if;
545 -- Check placement of OTHERS if available (SPARK RM 6.1.3(1))
547 if Nkind (Case_Guard) = N_Others_Choice then
548 if Others_Seen then
549 Error_Msg_N
550 ("only one OTHERS choice allowed in contract cases",
551 Case_Guard);
552 else
553 Others_Seen := True;
554 end if;
556 elsif Others_Seen then
557 Error_Msg_N
558 ("OTHERS must be the last choice in contract cases", N);
559 end if;
561 -- Preanalyze the case guard and consequence
563 if Nkind (Case_Guard) /= N_Others_Choice then
564 Errors := Serious_Errors_Detected;
565 Preanalyze_Assert_Expression (Case_Guard, Standard_Boolean);
567 -- Emit a clarification message when the case guard contains
568 -- at least one undefined reference, possibly due to contract
569 -- freezing.
571 if Errors /= Serious_Errors_Detected
572 and then Present (Freeze_Id)
573 and then Has_Undefined_Reference (Case_Guard)
574 then
575 Contract_Freeze_Error (Spec_Id, Freeze_Id);
576 end if;
577 end if;
579 Errors := Serious_Errors_Detected;
580 Preanalyze_Assert_Expression (Conseq, Standard_Boolean);
582 -- Emit a clarification message when the consequence contains
583 -- at least one undefined reference, possibly due to contract
584 -- freezing.
586 if Errors /= Serious_Errors_Detected
587 and then Present (Freeze_Id)
588 and then Has_Undefined_Reference (Conseq)
589 then
590 Contract_Freeze_Error (Spec_Id, Freeze_Id);
591 end if;
593 -- The contract case is malformed
595 else
596 Error_Msg_N ("wrong syntax in contract case", CCase);
597 end if;
598 end Analyze_Contract_Case;
600 -- Local variables
602 CCases : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
604 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
605 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
606 -- Save the Ghost-related attributes to restore on exit
608 CCase : Node_Id;
609 Restore_Scope : Boolean := False;
611 -- Start of processing for Analyze_Contract_Cases_In_Decl_Part
613 begin
614 -- Do not analyze the pragma multiple times
616 if Is_Analyzed_Pragma (N) then
617 return;
618 end if;
620 -- Set the Ghost mode in effect from the pragma. Due to the delayed
621 -- analysis of the pragma, the Ghost mode at point of declaration and
622 -- point of analysis may not necessarily be the same. Use the mode in
623 -- effect at the point of declaration.
625 Set_Ghost_Mode (N);
627 -- Single and multiple contract cases must appear in aggregate form. If
628 -- this is not the case, then either the parser or the analysis of the
629 -- pragma failed to produce an aggregate, e.g. when the contract is
630 -- "null" or a "(null record)".
632 pragma Assert
633 (if Nkind (CCases) = N_Aggregate
634 then Null_Record_Present (CCases)
635 xor (Present (Component_Associations (CCases))
637 Present (Expressions (CCases)))
638 else Nkind (CCases) = N_Null);
640 -- Only CASE_GUARD => CONSEQUENCE clauses are allowed
642 if Nkind (CCases) = N_Aggregate
643 and then Present (Component_Associations (CCases))
644 and then No (Expressions (CCases))
645 then
647 -- Check that the expression is a proper aggregate (no parentheses)
649 if Paren_Count (CCases) /= 0 then
650 Error_Msg_F -- CODEFIX
651 ("redundant parentheses", CCases);
652 end if;
654 -- Ensure that the formal parameters are visible when analyzing all
655 -- clauses. This falls out of the general rule of aspects pertaining
656 -- to subprogram declarations.
658 if not In_Open_Scopes (Spec_Id) then
659 Restore_Scope := True;
660 Push_Scope (Spec_Id);
662 if Is_Generic_Subprogram (Spec_Id) then
663 Install_Generic_Formals (Spec_Id);
664 else
665 Install_Formals (Spec_Id);
666 end if;
667 end if;
669 CCase := First (Component_Associations (CCases));
670 while Present (CCase) loop
671 Analyze_Contract_Case (CCase);
672 Next (CCase);
673 end loop;
675 if Restore_Scope then
676 End_Scope;
677 end if;
679 -- Currently it is not possible to inline pre/postconditions on a
680 -- subprogram subject to pragma Inline_Always.
682 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
684 -- Otherwise the pragma is illegal
686 else
687 Error_Msg_N ("wrong syntax for contract cases", N);
688 end if;
690 Set_Is_Analyzed_Pragma (N);
692 Restore_Ghost_Region (Saved_GM, Saved_IGR);
693 end Analyze_Contract_Cases_In_Decl_Part;
695 ----------------------------------
696 -- Analyze_Depends_In_Decl_Part --
697 ----------------------------------
699 procedure Analyze_Depends_In_Decl_Part (N : Node_Id) is
700 Loc : constant Source_Ptr := Sloc (N);
701 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
702 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
704 All_Inputs_Seen : Elist_Id := No_Elist;
705 -- A list containing the entities of all the inputs processed so far.
706 -- The list is populated with unique entities because the same input
707 -- may appear in multiple input lists.
709 All_Outputs_Seen : Elist_Id := No_Elist;
710 -- A list containing the entities of all the outputs processed so far.
711 -- The list is populated with unique entities because output items are
712 -- unique in a dependence relation.
714 Constits_Seen : Elist_Id := No_Elist;
715 -- A list containing the entities of all constituents processed so far.
716 -- It aids in detecting illegal usage of a state and a corresponding
717 -- constituent in pragma [Refinde_]Depends.
719 Global_Seen : Boolean := False;
720 -- A flag set when pragma Global has been processed
722 Null_Output_Seen : Boolean := False;
723 -- A flag used to track the legality of a null output
725 Result_Seen : Boolean := False;
726 -- A flag set when Spec_Id'Result is processed
728 States_Seen : Elist_Id := No_Elist;
729 -- A list containing the entities of all states processed so far. It
730 -- helps in detecting illegal usage of a state and a corresponding
731 -- constituent in pragma [Refined_]Depends.
733 Subp_Inputs : Elist_Id := No_Elist;
734 Subp_Outputs : Elist_Id := No_Elist;
735 -- Two lists containing the full set of inputs and output of the related
736 -- subprograms. Note that these lists contain both nodes and entities.
738 Task_Input_Seen : Boolean := False;
739 Task_Output_Seen : Boolean := False;
740 -- Flags used to track the implicit dependence of a task unit on itself
742 procedure Add_Item_To_Name_Buffer (Item_Id : Entity_Id);
743 -- Subsidiary routine to Check_Role and Check_Usage. Add the item kind
744 -- to the name buffer. The individual kinds are as follows:
745 -- E_Abstract_State - "state"
746 -- E_Constant - "constant"
747 -- E_Generic_In_Out_Parameter - "generic parameter"
748 -- E_Generic_In_Parameter - "generic parameter"
749 -- E_In_Parameter - "parameter"
750 -- E_In_Out_Parameter - "parameter"
751 -- E_Loop_Parameter - "loop parameter"
752 -- E_Out_Parameter - "parameter"
753 -- E_Protected_Type - "current instance of protected type"
754 -- E_Task_Type - "current instance of task type"
755 -- E_Variable - "global"
757 procedure Analyze_Dependency_Clause
758 (Clause : Node_Id;
759 Is_Last : Boolean);
760 -- Verify the legality of a single dependency clause. Flag Is_Last
761 -- denotes whether Clause is the last clause in the relation.
763 procedure Check_Function_Return;
764 -- Verify that Funtion'Result appears as one of the outputs
765 -- (SPARK RM 6.1.5(10)).
767 procedure Check_Role
768 (Item : Node_Id;
769 Item_Id : Entity_Id;
770 Is_Input : Boolean;
771 Self_Ref : Boolean);
772 -- Ensure that an item fulfills its designated input and/or output role
773 -- as specified by pragma Global (if any) or the enclosing context. If
774 -- this is not the case, emit an error. Item and Item_Id denote the
775 -- attributes of an item. Flag Is_Input should be set when item comes
776 -- from an input list. Flag Self_Ref should be set when the item is an
777 -- output and the dependency clause has operator "+".
779 procedure Check_Usage
780 (Subp_Items : Elist_Id;
781 Used_Items : Elist_Id;
782 Is_Input : Boolean);
783 -- Verify that all items from Subp_Items appear in Used_Items. Emit an
784 -- error if this is not the case.
786 procedure Normalize_Clause (Clause : Node_Id);
787 -- Remove a self-dependency "+" from the input list of a clause
789 -----------------------------
790 -- Add_Item_To_Name_Buffer --
791 -----------------------------
793 procedure Add_Item_To_Name_Buffer (Item_Id : Entity_Id) is
794 begin
795 if Ekind (Item_Id) = E_Abstract_State then
796 Add_Str_To_Name_Buffer ("state");
798 elsif Ekind (Item_Id) = E_Constant then
799 Add_Str_To_Name_Buffer ("constant");
801 elsif Is_Formal_Object (Item_Id) then
802 Add_Str_To_Name_Buffer ("generic parameter");
804 elsif Is_Formal (Item_Id) then
805 Add_Str_To_Name_Buffer ("parameter");
807 elsif Ekind (Item_Id) = E_Loop_Parameter then
808 Add_Str_To_Name_Buffer ("loop parameter");
810 elsif Ekind (Item_Id) = E_Protected_Type
811 or else Is_Single_Protected_Object (Item_Id)
812 then
813 Add_Str_To_Name_Buffer ("current instance of protected type");
815 elsif Ekind (Item_Id) = E_Task_Type
816 or else Is_Single_Task_Object (Item_Id)
817 then
818 Add_Str_To_Name_Buffer ("current instance of task type");
820 elsif Ekind (Item_Id) = E_Variable then
821 Add_Str_To_Name_Buffer ("global");
823 -- The routine should not be called with non-SPARK items
825 else
826 raise Program_Error;
827 end if;
828 end Add_Item_To_Name_Buffer;
830 -------------------------------
831 -- Analyze_Dependency_Clause --
832 -------------------------------
834 procedure Analyze_Dependency_Clause
835 (Clause : Node_Id;
836 Is_Last : Boolean)
838 procedure Analyze_Input_List (Inputs : Node_Id);
839 -- Verify the legality of a single input list
841 procedure Analyze_Input_Output
842 (Item : Node_Id;
843 Is_Input : Boolean;
844 Self_Ref : Boolean;
845 Top_Level : Boolean;
846 Seen : in out Elist_Id;
847 Null_Seen : in out Boolean;
848 Non_Null_Seen : in out Boolean);
849 -- Verify the legality of a single input or output item. Flag
850 -- Is_Input should be set whenever Item is an input, False when it
851 -- denotes an output. Flag Self_Ref should be set when the item is an
852 -- output and the dependency clause has a "+". Flag Top_Level should
853 -- be set whenever Item appears immediately within an input or output
854 -- list. Seen is a collection of all abstract states, objects and
855 -- formals processed so far. Flag Null_Seen denotes whether a null
856 -- input or output has been encountered. Flag Non_Null_Seen denotes
857 -- whether a non-null input or output has been encountered.
859 ------------------------
860 -- Analyze_Input_List --
861 ------------------------
863 procedure Analyze_Input_List (Inputs : Node_Id) is
864 Inputs_Seen : Elist_Id := No_Elist;
865 -- A list containing the entities of all inputs that appear in the
866 -- current input list.
868 Non_Null_Input_Seen : Boolean := False;
869 Null_Input_Seen : Boolean := False;
870 -- Flags used to check the legality of an input list
872 Input : Node_Id;
874 begin
875 -- Multiple inputs appear as an aggregate
877 if Nkind (Inputs) = N_Aggregate then
878 if Present (Component_Associations (Inputs)) then
879 SPARK_Msg_N
880 ("nested dependency relations not allowed", Inputs);
882 elsif Present (Expressions (Inputs)) then
883 Input := First (Expressions (Inputs));
884 while Present (Input) loop
885 Analyze_Input_Output
886 (Item => Input,
887 Is_Input => True,
888 Self_Ref => False,
889 Top_Level => False,
890 Seen => Inputs_Seen,
891 Null_Seen => Null_Input_Seen,
892 Non_Null_Seen => Non_Null_Input_Seen);
894 Next (Input);
895 end loop;
897 -- Syntax error, always report
899 else
900 Error_Msg_N ("malformed input dependency list", Inputs);
901 end if;
903 -- Process a solitary input
905 else
906 Analyze_Input_Output
907 (Item => Inputs,
908 Is_Input => True,
909 Self_Ref => False,
910 Top_Level => False,
911 Seen => Inputs_Seen,
912 Null_Seen => Null_Input_Seen,
913 Non_Null_Seen => Non_Null_Input_Seen);
914 end if;
916 -- Detect an illegal dependency clause of the form
918 -- (null =>[+] null)
920 if Null_Output_Seen and then Null_Input_Seen then
921 SPARK_Msg_N
922 ("null dependency clause cannot have a null input list",
923 Inputs);
924 end if;
925 end Analyze_Input_List;
927 --------------------------
928 -- Analyze_Input_Output --
929 --------------------------
931 procedure Analyze_Input_Output
932 (Item : Node_Id;
933 Is_Input : Boolean;
934 Self_Ref : Boolean;
935 Top_Level : Boolean;
936 Seen : in out Elist_Id;
937 Null_Seen : in out Boolean;
938 Non_Null_Seen : in out Boolean)
940 procedure Current_Task_Instance_Seen;
941 -- Set the appropriate global flag when the current instance of a
942 -- task unit is encountered.
944 --------------------------------
945 -- Current_Task_Instance_Seen --
946 --------------------------------
948 procedure Current_Task_Instance_Seen is
949 begin
950 if Is_Input then
951 Task_Input_Seen := True;
952 else
953 Task_Output_Seen := True;
954 end if;
955 end Current_Task_Instance_Seen;
957 -- Local variables
959 Is_Output : constant Boolean := not Is_Input;
960 Grouped : Node_Id;
961 Item_Id : Entity_Id;
963 -- Start of processing for Analyze_Input_Output
965 begin
966 -- Multiple input or output items appear as an aggregate
968 if Nkind (Item) = N_Aggregate then
969 if not Top_Level then
970 SPARK_Msg_N ("nested grouping of items not allowed", Item);
972 elsif Present (Component_Associations (Item)) then
973 SPARK_Msg_N
974 ("nested dependency relations not allowed", Item);
976 -- Recursively analyze the grouped items
978 elsif Present (Expressions (Item)) then
979 Grouped := First (Expressions (Item));
980 while Present (Grouped) loop
981 Analyze_Input_Output
982 (Item => Grouped,
983 Is_Input => Is_Input,
984 Self_Ref => Self_Ref,
985 Top_Level => False,
986 Seen => Seen,
987 Null_Seen => Null_Seen,
988 Non_Null_Seen => Non_Null_Seen);
990 Next (Grouped);
991 end loop;
993 -- Syntax error, always report
995 else
996 Error_Msg_N ("malformed dependency list", Item);
997 end if;
999 -- Process attribute 'Result in the context of a dependency clause
1001 elsif Is_Attribute_Result (Item) then
1002 Non_Null_Seen := True;
1004 Analyze (Item);
1006 -- Attribute 'Result is allowed to appear on the output side of
1007 -- a dependency clause (SPARK RM 6.1.5(6)).
1009 if Is_Input then
1010 SPARK_Msg_N ("function result cannot act as input", Item);
1012 elsif Null_Seen then
1013 SPARK_Msg_N
1014 ("cannot mix null and non-null dependency items", Item);
1016 else
1017 Result_Seen := True;
1018 end if;
1020 -- Detect multiple uses of null in a single dependency list or
1021 -- throughout the whole relation. Verify the placement of a null
1022 -- output list relative to the other clauses (SPARK RM 6.1.5(12)).
1024 elsif Nkind (Item) = N_Null then
1025 if Null_Seen then
1026 SPARK_Msg_N
1027 ("multiple null dependency relations not allowed", Item);
1029 elsif Non_Null_Seen then
1030 SPARK_Msg_N
1031 ("cannot mix null and non-null dependency items", Item);
1033 else
1034 Null_Seen := True;
1036 if Is_Output then
1037 if not Is_Last then
1038 SPARK_Msg_N
1039 ("null output list must be the last clause in a "
1040 & "dependency relation", Item);
1042 -- Catch a useless dependence of the form:
1043 -- null =>+ ...
1045 elsif Self_Ref then
1046 SPARK_Msg_N
1047 ("useless dependence, null depends on itself", Item);
1048 end if;
1049 end if;
1050 end if;
1052 -- Default case
1054 else
1055 Non_Null_Seen := True;
1057 if Null_Seen then
1058 SPARK_Msg_N ("cannot mix null and non-null items", Item);
1059 end if;
1061 Analyze (Item);
1062 Resolve_State (Item);
1064 -- Find the entity of the item. If this is a renaming, climb
1065 -- the renaming chain to reach the root object. Renamings of
1066 -- non-entire objects do not yield an entity (Empty).
1068 Item_Id := Entity_Of (Item);
1070 if Present (Item_Id) then
1072 -- Constants
1074 if Ekind (Item_Id) in E_Constant | E_Loop_Parameter
1075 or else
1077 -- Current instances of concurrent types
1079 Ekind (Item_Id) in E_Protected_Type | E_Task_Type
1080 or else
1082 -- Formal parameters
1084 Ekind (Item_Id) in E_Generic_In_Out_Parameter
1085 | E_Generic_In_Parameter
1086 | E_In_Parameter
1087 | E_In_Out_Parameter
1088 | E_Out_Parameter
1089 or else
1091 -- States, variables
1093 Ekind (Item_Id) in E_Abstract_State | E_Variable
1094 then
1095 -- A [generic] function is not allowed to have Output
1096 -- items in its dependency relations. Note that "null"
1097 -- and attribute 'Result are still valid items.
1099 if Ekind (Spec_Id) in E_Function | E_Generic_Function
1100 and then not Is_Input
1101 then
1102 SPARK_Msg_N
1103 ("output item is not applicable to function", Item);
1104 end if;
1106 -- The item denotes a concurrent type. Note that single
1107 -- protected/task types are not considered here because
1108 -- they behave as objects in the context of pragma
1109 -- [Refined_]Depends.
1111 if Ekind (Item_Id) in E_Protected_Type | E_Task_Type then
1113 -- This use is legal as long as the concurrent type is
1114 -- the current instance of an enclosing type.
1116 if Is_CCT_Instance (Item_Id, Spec_Id) then
1118 -- The dependence of a task unit on itself is
1119 -- implicit and may or may not be explicitly
1120 -- specified (SPARK RM 6.1.4).
1122 if Ekind (Item_Id) = E_Task_Type then
1123 Current_Task_Instance_Seen;
1124 end if;
1126 -- Otherwise this is not the current instance
1128 else
1129 SPARK_Msg_N
1130 ("invalid use of subtype mark in dependency "
1131 & "relation", Item);
1132 end if;
1134 -- The dependency of a task unit on itself is implicit
1135 -- and may or may not be explicitly specified
1136 -- (SPARK RM 6.1.4).
1138 elsif Is_Single_Task_Object (Item_Id)
1139 and then Is_CCT_Instance (Etype (Item_Id), Spec_Id)
1140 then
1141 Current_Task_Instance_Seen;
1142 end if;
1144 -- Ensure that the item fulfills its role as input and/or
1145 -- output as specified by pragma Global or the enclosing
1146 -- context.
1148 Check_Role (Item, Item_Id, Is_Input, Self_Ref);
1150 -- Detect multiple uses of the same state, variable or
1151 -- formal parameter. If this is not the case, add the
1152 -- item to the list of processed relations.
1154 if Contains (Seen, Item_Id) then
1155 SPARK_Msg_NE
1156 ("duplicate use of item &", Item, Item_Id);
1157 else
1158 Append_New_Elmt (Item_Id, Seen);
1159 end if;
1161 -- Detect illegal use of an input related to a null
1162 -- output. Such input items cannot appear in other
1163 -- input lists (SPARK RM 6.1.5(13)).
1165 if Is_Input
1166 and then Null_Output_Seen
1167 and then Contains (All_Inputs_Seen, Item_Id)
1168 then
1169 SPARK_Msg_N
1170 ("input of a null output list cannot appear in "
1171 & "multiple input lists", Item);
1172 end if;
1174 -- Add an input or a self-referential output to the list
1175 -- of all processed inputs.
1177 if Is_Input or else Self_Ref then
1178 Append_New_Elmt (Item_Id, All_Inputs_Seen);
1179 end if;
1181 -- State related checks (SPARK RM 6.1.5(3))
1183 if Ekind (Item_Id) = E_Abstract_State then
1185 -- Package and subprogram bodies are instantiated
1186 -- individually in a separate compiler pass. Due to
1187 -- this mode of instantiation, the refinement of a
1188 -- state may no longer be visible when a subprogram
1189 -- body contract is instantiated. Since the generic
1190 -- template is legal, do not perform this check in
1191 -- the instance to circumvent this oddity.
1193 if In_Instance then
1194 null;
1196 -- An abstract state with visible refinement cannot
1197 -- appear in pragma [Refined_]Depends as its place
1198 -- must be taken by some of its constituents
1199 -- (SPARK RM 6.1.4(7)).
1201 elsif Has_Visible_Refinement (Item_Id) then
1202 SPARK_Msg_NE
1203 ("cannot mention state & in dependence relation",
1204 Item, Item_Id);
1205 SPARK_Msg_N ("\use its constituents instead", Item);
1206 return;
1208 -- If the reference to the abstract state appears in
1209 -- an enclosing package body that will eventually
1210 -- refine the state, record the reference for future
1211 -- checks.
1213 else
1214 Record_Possible_Body_Reference
1215 (State_Id => Item_Id,
1216 Ref => Item);
1217 end if;
1219 elsif Ekind (Item_Id) in E_Constant | E_Variable
1220 and then Present (Ultimate_Overlaid_Entity (Item_Id))
1221 then
1222 SPARK_Msg_NE
1223 ("overlaying object & cannot appear in Depends",
1224 Item, Item_Id);
1225 SPARK_Msg_NE
1226 ("\use the overlaid object & instead",
1227 Item, Ultimate_Overlaid_Entity (Item_Id));
1228 return;
1229 end if;
1231 -- When the item renames an entire object, replace the
1232 -- item with a reference to the object.
1234 if Entity (Item) /= Item_Id then
1235 Rewrite (Item,
1236 New_Occurrence_Of (Item_Id, Sloc (Item)));
1237 Analyze (Item);
1238 end if;
1240 -- Add the entity of the current item to the list of
1241 -- processed items.
1243 if Ekind (Item_Id) = E_Abstract_State then
1244 Append_New_Elmt (Item_Id, States_Seen);
1246 -- The variable may eventually become a constituent of a
1247 -- single protected/task type. Record the reference now
1248 -- and verify its legality when analyzing the contract of
1249 -- the variable (SPARK RM 9.3).
1251 elsif Ekind (Item_Id) = E_Variable then
1252 Record_Possible_Part_Of_Reference
1253 (Var_Id => Item_Id,
1254 Ref => Item);
1255 end if;
1257 if Ekind (Item_Id) in E_Abstract_State
1258 | E_Constant
1259 | E_Variable
1260 and then Present (Encapsulating_State (Item_Id))
1261 then
1262 Append_New_Elmt (Item_Id, Constits_Seen);
1263 end if;
1265 -- All other input/output items are illegal
1266 -- (SPARK RM 6.1.5(1)).
1268 else
1269 SPARK_Msg_N
1270 ("item must denote parameter, variable, state or "
1271 & "current instance of concurrent type", Item);
1272 end if;
1274 -- All other input/output items are illegal
1275 -- (SPARK RM 6.1.5(1)). This is a syntax error, always report.
1277 else
1278 Error_Msg_N
1279 ("item must denote parameter, variable, state or current "
1280 & "instance of concurrent type", Item);
1281 end if;
1282 end if;
1283 end Analyze_Input_Output;
1285 -- Local variables
1287 Inputs : Node_Id;
1288 Output : Node_Id;
1289 Self_Ref : Boolean;
1291 Non_Null_Output_Seen : Boolean := False;
1292 -- Flag used to check the legality of an output list
1294 -- Start of processing for Analyze_Dependency_Clause
1296 begin
1297 Inputs := Expression (Clause);
1298 Self_Ref := False;
1300 -- An input list with a self-dependency appears as operator "+" where
1301 -- the actuals inputs are the right operand.
1303 if Nkind (Inputs) = N_Op_Plus then
1304 Inputs := Right_Opnd (Inputs);
1305 Self_Ref := True;
1306 end if;
1308 -- Process the output_list of a dependency_clause
1310 Output := First (Choices (Clause));
1311 while Present (Output) loop
1312 Analyze_Input_Output
1313 (Item => Output,
1314 Is_Input => False,
1315 Self_Ref => Self_Ref,
1316 Top_Level => True,
1317 Seen => All_Outputs_Seen,
1318 Null_Seen => Null_Output_Seen,
1319 Non_Null_Seen => Non_Null_Output_Seen);
1321 Next (Output);
1322 end loop;
1324 -- Process the input_list of a dependency_clause
1326 Analyze_Input_List (Inputs);
1327 end Analyze_Dependency_Clause;
1329 ---------------------------
1330 -- Check_Function_Return --
1331 ---------------------------
1333 procedure Check_Function_Return is
1334 begin
1335 if Ekind (Spec_Id) in E_Function | E_Generic_Function
1336 and then not Result_Seen
1337 then
1338 SPARK_Msg_NE
1339 ("result of & must appear in exactly one output list",
1340 N, Spec_Id);
1341 end if;
1342 end Check_Function_Return;
1344 ----------------
1345 -- Check_Role --
1346 ----------------
1348 procedure Check_Role
1349 (Item : Node_Id;
1350 Item_Id : Entity_Id;
1351 Is_Input : Boolean;
1352 Self_Ref : Boolean)
1354 procedure Find_Role
1355 (Item_Is_Input : out Boolean;
1356 Item_Is_Output : out Boolean);
1357 -- Find the input/output role of Item_Id. Flags Item_Is_Input and
1358 -- Item_Is_Output are set depending on the role.
1360 procedure Role_Error
1361 (Item_Is_Input : Boolean;
1362 Item_Is_Output : Boolean);
1363 -- Emit an error message concerning the incorrect use of Item in
1364 -- pragma [Refined_]Depends. Flags Item_Is_Input and Item_Is_Output
1365 -- denote whether the item is an input and/or an output.
1367 ---------------
1368 -- Find_Role --
1369 ---------------
1371 procedure Find_Role
1372 (Item_Is_Input : out Boolean;
1373 Item_Is_Output : out Boolean)
1375 -- A constant or an IN parameter of a procedure or a protected
1376 -- entry, if it is of an access-to-variable type, should be
1377 -- handled like a variable, as the underlying memory pointed-to
1378 -- can be modified. Use Adjusted_Kind to do this adjustment.
1380 Adjusted_Kind : Entity_Kind := Ekind (Item_Id);
1382 begin
1383 if (Ekind (Item_Id) in E_Constant | E_Generic_In_Parameter
1384 or else
1385 (Ekind (Item_Id) = E_In_Parameter
1386 and then Ekind (Scope (Item_Id))
1387 not in E_Function | E_Generic_Function))
1388 and then Is_Access_Variable (Etype (Item_Id))
1389 and then Ekind (Spec_Id) not in E_Function
1390 | E_Generic_Function
1391 then
1392 Adjusted_Kind := E_Variable;
1393 end if;
1395 case Adjusted_Kind is
1397 -- Abstract states
1399 when E_Abstract_State =>
1401 -- When pragma Global is present it determines the mode of
1402 -- the abstract state.
1404 if Global_Seen then
1405 Item_Is_Input := Appears_In (Subp_Inputs, Item_Id);
1406 Item_Is_Output := Appears_In (Subp_Outputs, Item_Id);
1408 -- Otherwise the state has a default IN OUT mode, because it
1409 -- behaves as a variable.
1411 else
1412 Item_Is_Input := True;
1413 Item_Is_Output := True;
1414 end if;
1416 -- Constants and IN parameters
1418 when E_Constant
1419 | E_Generic_In_Parameter
1420 | E_In_Parameter
1421 | E_Loop_Parameter
1423 -- When pragma Global is present it determines the mode
1424 -- of constant objects as inputs (and such objects cannot
1425 -- appear as outputs in the Global contract).
1427 if Global_Seen then
1428 Item_Is_Input := Appears_In (Subp_Inputs, Item_Id);
1429 else
1430 Item_Is_Input := True;
1431 end if;
1433 Item_Is_Output := False;
1435 -- Variables and IN OUT parameters, as well as constants and
1436 -- IN parameters of access type which are handled like
1437 -- variables.
1439 when E_Generic_In_Out_Parameter
1440 | E_In_Out_Parameter
1441 | E_Out_Parameter
1442 | E_Variable
1444 -- An OUT parameter of the related subprogram; it cannot
1445 -- appear in Global.
1447 if Adjusted_Kind = E_Out_Parameter
1448 and then Scope (Item_Id) = Spec_Id
1449 then
1451 -- The parameter has mode IN if its type is unconstrained
1452 -- or tagged because array bounds, discriminants or tags
1453 -- can be read.
1455 Item_Is_Input :=
1456 Is_Unconstrained_Or_Tagged_Item (Item_Id);
1458 Item_Is_Output := True;
1460 -- A parameter of an enclosing subprogram; it can appear
1461 -- in Global and behaves as a read-write variable.
1463 else
1464 -- When pragma Global is present it determines the mode
1465 -- of the object.
1467 if Global_Seen then
1469 -- A variable has mode IN when its type is
1470 -- unconstrained or tagged because array bounds,
1471 -- discriminants, or tags can be read.
1473 Item_Is_Input :=
1474 Appears_In (Subp_Inputs, Item_Id)
1475 or else Is_Unconstrained_Or_Tagged_Item (Item_Id);
1477 Item_Is_Output := Appears_In (Subp_Outputs, Item_Id);
1479 -- Otherwise the variable has a default IN OUT mode
1481 else
1482 Item_Is_Input := True;
1483 Item_Is_Output := True;
1484 end if;
1485 end if;
1487 -- Protected types
1489 when E_Protected_Type =>
1490 if Global_Seen then
1492 -- A variable has mode IN when its type is unconstrained
1493 -- or tagged because array bounds, discriminants or tags
1494 -- can be read.
1496 Item_Is_Input :=
1497 Appears_In (Subp_Inputs, Item_Id)
1498 or else Is_Unconstrained_Or_Tagged_Item (Item_Id);
1500 Item_Is_Output := Appears_In (Subp_Outputs, Item_Id);
1502 else
1503 -- A protected type acts as a formal parameter of mode IN
1504 -- when it applies to a protected function.
1506 if Ekind (Spec_Id) = E_Function then
1507 Item_Is_Input := True;
1508 Item_Is_Output := False;
1510 -- Otherwise the protected type acts as a formal of mode
1511 -- IN OUT.
1513 else
1514 Item_Is_Input := True;
1515 Item_Is_Output := True;
1516 end if;
1517 end if;
1519 -- Task types
1521 when E_Task_Type =>
1523 -- When pragma Global is present it determines the mode of
1524 -- the object.
1526 if Global_Seen then
1527 Item_Is_Input :=
1528 Appears_In (Subp_Inputs, Item_Id)
1529 or else Is_Unconstrained_Or_Tagged_Item (Item_Id);
1531 Item_Is_Output := Appears_In (Subp_Outputs, Item_Id);
1533 -- Otherwise task types act as IN OUT parameters
1535 else
1536 Item_Is_Input := True;
1537 Item_Is_Output := True;
1538 end if;
1540 when others =>
1541 raise Program_Error;
1542 end case;
1543 end Find_Role;
1545 ----------------
1546 -- Role_Error --
1547 ----------------
1549 procedure Role_Error
1550 (Item_Is_Input : Boolean;
1551 Item_Is_Output : Boolean)
1553 begin
1554 Name_Len := 0;
1556 -- When the item is not part of the input and the output set of
1557 -- the related subprogram, then it appears as extra in pragma
1558 -- [Refined_]Depends.
1560 if not Item_Is_Input and then not Item_Is_Output then
1561 Add_Item_To_Name_Buffer (Item_Id);
1562 Add_Str_To_Name_Buffer
1563 (" & cannot appear in dependence relation");
1565 SPARK_Msg_NE (To_String (Global_Name_Buffer), Item, Item_Id);
1567 Error_Msg_Name_1 := Chars (Spec_Id);
1568 SPARK_Msg_NE
1569 (Fix_Msg (Spec_Id, "\& is not part of the input or output "
1570 & "set of subprogram %"), Item, Item_Id);
1572 -- The mode of the item and its role in pragma [Refined_]Depends
1573 -- are in conflict. Construct a detailed message explaining the
1574 -- illegality (SPARK RM 6.1.5(5-6)).
1576 else
1577 if Item_Is_Input then
1578 Add_Str_To_Name_Buffer ("read-only");
1579 else
1580 Add_Str_To_Name_Buffer ("write-only");
1581 end if;
1583 Add_Char_To_Name_Buffer (' ');
1584 Add_Item_To_Name_Buffer (Item_Id);
1585 Add_Str_To_Name_Buffer (" & cannot appear as ");
1587 if Item_Is_Input then
1588 Add_Str_To_Name_Buffer ("output");
1589 else
1590 Add_Str_To_Name_Buffer ("input");
1591 end if;
1593 Add_Str_To_Name_Buffer (" in dependence relation");
1595 SPARK_Msg_NE (To_String (Global_Name_Buffer), Item, Item_Id);
1596 end if;
1597 end Role_Error;
1599 -- Local variables
1601 Item_Is_Input : Boolean;
1602 Item_Is_Output : Boolean;
1604 -- Start of processing for Check_Role
1606 begin
1607 Find_Role (Item_Is_Input, Item_Is_Output);
1609 -- Input item
1611 if Is_Input then
1612 if not Item_Is_Input then
1613 Role_Error (Item_Is_Input, Item_Is_Output);
1614 end if;
1616 -- Self-referential item
1618 elsif Self_Ref then
1619 if not Item_Is_Input or else not Item_Is_Output then
1620 Role_Error (Item_Is_Input, Item_Is_Output);
1621 end if;
1623 -- Output item
1625 elsif not Item_Is_Output then
1626 Role_Error (Item_Is_Input, Item_Is_Output);
1627 end if;
1628 end Check_Role;
1630 -----------------
1631 -- Check_Usage --
1632 -----------------
1634 procedure Check_Usage
1635 (Subp_Items : Elist_Id;
1636 Used_Items : Elist_Id;
1637 Is_Input : Boolean)
1639 procedure Usage_Error (Item_Id : Entity_Id);
1640 -- Emit an error concerning the illegal usage of an item
1642 -----------------
1643 -- Usage_Error --
1644 -----------------
1646 procedure Usage_Error (Item_Id : Entity_Id) is
1647 begin
1648 -- Input case
1650 if Is_Input then
1652 -- Unconstrained and tagged items are not part of the explicit
1653 -- input set of the related subprogram, they do not have to be
1654 -- present in a dependence relation and should not be flagged
1655 -- (SPARK RM 6.1.5(5)).
1657 if not Is_Unconstrained_Or_Tagged_Item (Item_Id) then
1658 Name_Len := 0;
1660 Add_Item_To_Name_Buffer (Item_Id);
1661 Add_Str_To_Name_Buffer
1662 (" & is missing from input dependence list");
1664 SPARK_Msg_NE (To_String (Global_Name_Buffer), N, Item_Id);
1665 SPARK_Msg_NE
1666 ("\add `null ='> &` dependency to ignore this input",
1667 N, Item_Id);
1668 end if;
1670 -- Output case (SPARK RM 6.1.5(10))
1672 else
1673 Name_Len := 0;
1675 Add_Item_To_Name_Buffer (Item_Id);
1676 Add_Str_To_Name_Buffer
1677 (" & is missing from output dependence list");
1679 SPARK_Msg_NE (To_String (Global_Name_Buffer), N, Item_Id);
1680 end if;
1681 end Usage_Error;
1683 -- Local variables
1685 Elmt : Elmt_Id;
1686 Item : Node_Id;
1687 Item_Id : Entity_Id;
1689 -- Start of processing for Check_Usage
1691 begin
1692 if No (Subp_Items) then
1693 return;
1694 end if;
1696 -- Each input or output of the subprogram must appear in a dependency
1697 -- relation.
1699 Elmt := First_Elmt (Subp_Items);
1700 while Present (Elmt) loop
1701 Item := Node (Elmt);
1703 if Nkind (Item) = N_Defining_Identifier then
1704 Item_Id := Item;
1705 else
1706 Item_Id := Entity_Of (Item);
1707 end if;
1709 -- The item does not appear in a dependency
1711 if Present (Item_Id)
1712 and then not Contains (Used_Items, Item_Id)
1713 then
1714 if Is_Formal (Item_Id) then
1715 Usage_Error (Item_Id);
1717 -- The current instance of a protected type behaves as a formal
1718 -- parameter (SPARK RM 6.1.4).
1720 elsif Ekind (Item_Id) = E_Protected_Type
1721 or else Is_Single_Protected_Object (Item_Id)
1722 then
1723 Usage_Error (Item_Id);
1725 -- The current instance of a task type behaves as a formal
1726 -- parameter (SPARK RM 6.1.4).
1728 elsif Ekind (Item_Id) = E_Task_Type
1729 or else Is_Single_Task_Object (Item_Id)
1730 then
1731 -- The dependence of a task unit on itself is implicit and
1732 -- may or may not be explicitly specified (SPARK RM 6.1.4).
1733 -- Emit an error if only one input/output is present.
1735 if Task_Input_Seen /= Task_Output_Seen then
1736 Usage_Error (Item_Id);
1737 end if;
1739 -- States and global objects are not used properly only when
1740 -- the subprogram is subject to pragma Global.
1742 elsif Global_Seen
1743 and then Ekind (Item_Id) in E_Abstract_State
1744 | E_Constant
1745 | E_Loop_Parameter
1746 | E_Protected_Type
1747 | E_Task_Type
1748 | E_Variable
1749 | Formal_Kind
1750 then
1751 Usage_Error (Item_Id);
1752 end if;
1753 end if;
1755 Next_Elmt (Elmt);
1756 end loop;
1757 end Check_Usage;
1759 ----------------------
1760 -- Normalize_Clause --
1761 ----------------------
1763 procedure Normalize_Clause (Clause : Node_Id) is
1764 procedure Create_Or_Modify_Clause
1765 (Output : Node_Id;
1766 Outputs : Node_Id;
1767 Inputs : Node_Id;
1768 After : Node_Id;
1769 In_Place : Boolean;
1770 Multiple : Boolean);
1771 -- Create a brand new clause to represent the self-reference or
1772 -- modify the input and/or output lists of an existing clause. Output
1773 -- denotes a self-referencial output. Outputs is the output list of a
1774 -- clause. Inputs is the input list of a clause. After denotes the
1775 -- clause after which the new clause is to be inserted. Flag In_Place
1776 -- should be set when normalizing the last output of an output list.
1777 -- Flag Multiple should be set when Output comes from a list with
1778 -- multiple items.
1780 -----------------------------
1781 -- Create_Or_Modify_Clause --
1782 -----------------------------
1784 procedure Create_Or_Modify_Clause
1785 (Output : Node_Id;
1786 Outputs : Node_Id;
1787 Inputs : Node_Id;
1788 After : Node_Id;
1789 In_Place : Boolean;
1790 Multiple : Boolean)
1792 procedure Propagate_Output
1793 (Output : Node_Id;
1794 Inputs : Node_Id);
1795 -- Handle the various cases of output propagation to the input
1796 -- list. Output denotes a self-referencial output item. Inputs
1797 -- is the input list of a clause.
1799 ----------------------
1800 -- Propagate_Output --
1801 ----------------------
1803 procedure Propagate_Output
1804 (Output : Node_Id;
1805 Inputs : Node_Id)
1807 function In_Input_List
1808 (Item : Entity_Id;
1809 Inputs : List_Id) return Boolean;
1810 -- Determine whether a particulat item appears in the input
1811 -- list of a clause.
1813 -------------------
1814 -- In_Input_List --
1815 -------------------
1817 function In_Input_List
1818 (Item : Entity_Id;
1819 Inputs : List_Id) return Boolean
1821 Elmt : Node_Id;
1823 begin
1824 Elmt := First (Inputs);
1825 while Present (Elmt) loop
1826 if Entity_Of (Elmt) = Item then
1827 return True;
1828 end if;
1830 Next (Elmt);
1831 end loop;
1833 return False;
1834 end In_Input_List;
1836 -- Local variables
1838 Output_Id : constant Entity_Id := Entity_Of (Output);
1839 Grouped : List_Id;
1841 -- Start of processing for Propagate_Output
1843 begin
1844 -- The clause is of the form:
1846 -- (Output =>+ null)
1848 -- Remove null input and replace it with a copy of the output:
1850 -- (Output => Output)
1852 if Nkind (Inputs) = N_Null then
1853 Rewrite (Inputs, New_Copy_Tree (Output));
1855 -- The clause is of the form:
1857 -- (Output =>+ (Input1, ..., InputN))
1859 -- Determine whether the output is not already mentioned in the
1860 -- input list and if not, add it to the list of inputs:
1862 -- (Output => (Output, Input1, ..., InputN))
1864 elsif Nkind (Inputs) = N_Aggregate then
1865 Grouped := Expressions (Inputs);
1867 if not In_Input_List
1868 (Item => Output_Id,
1869 Inputs => Grouped)
1870 then
1871 Prepend_To (Grouped, New_Copy_Tree (Output));
1872 end if;
1874 -- The clause is of the form:
1876 -- (Output =>+ Input)
1878 -- If the input does not mention the output, group the two
1879 -- together:
1881 -- (Output => (Output, Input))
1883 elsif Entity_Of (Inputs) /= Output_Id then
1884 Rewrite (Inputs,
1885 Make_Aggregate (Loc,
1886 Expressions => New_List (
1887 New_Copy_Tree (Output),
1888 New_Copy_Tree (Inputs))));
1889 end if;
1890 end Propagate_Output;
1892 -- Local variables
1894 Loc : constant Source_Ptr := Sloc (Clause);
1895 New_Clause : Node_Id;
1897 -- Start of processing for Create_Or_Modify_Clause
1899 begin
1900 -- A null output depending on itself does not require any
1901 -- normalization.
1903 if Nkind (Output) = N_Null then
1904 return;
1906 -- A function result cannot depend on itself because it cannot
1907 -- appear in the input list of a relation (SPARK RM 6.1.5(10)).
1909 elsif Is_Attribute_Result (Output) then
1910 SPARK_Msg_N ("function result cannot depend on itself", Output);
1911 return;
1912 end if;
1914 -- When performing the transformation in place, simply add the
1915 -- output to the list of inputs (if not already there). This
1916 -- case arises when dealing with the last output of an output
1917 -- list. Perform the normalization in place to avoid generating
1918 -- a malformed tree.
1920 if In_Place then
1921 Propagate_Output (Output, Inputs);
1923 -- A list with multiple outputs is slowly trimmed until only
1924 -- one element remains. When this happens, replace aggregate
1925 -- with the element itself.
1927 if Multiple then
1928 Remove (Output);
1929 Rewrite (Outputs, Output);
1930 end if;
1932 -- Default case
1934 else
1935 -- Unchain the output from its output list as it will appear in
1936 -- a new clause. Note that we cannot simply rewrite the output
1937 -- as null because this will violate the semantics of pragma
1938 -- Depends.
1940 Remove (Output);
1942 -- Generate a new clause of the form:
1943 -- (Output => Inputs)
1945 New_Clause :=
1946 Make_Component_Association (Loc,
1947 Choices => New_List (Output),
1948 Expression => New_Copy_Tree (Inputs));
1950 -- The new clause contains replicated content that has already
1951 -- been analyzed. There is not need to reanalyze or renormalize
1952 -- it again.
1954 Set_Analyzed (New_Clause);
1956 Propagate_Output
1957 (Output => First (Choices (New_Clause)),
1958 Inputs => Expression (New_Clause));
1960 Insert_After (After, New_Clause);
1961 end if;
1962 end Create_Or_Modify_Clause;
1964 -- Local variables
1966 Outputs : constant Node_Id := First (Choices (Clause));
1967 Inputs : Node_Id;
1968 Last_Output : Node_Id;
1969 Next_Output : Node_Id;
1970 Output : Node_Id;
1972 -- Start of processing for Normalize_Clause
1974 begin
1975 -- A self-dependency appears as operator "+". Remove the "+" from the
1976 -- tree by moving the real inputs to their proper place.
1978 if Nkind (Expression (Clause)) = N_Op_Plus then
1979 Rewrite (Expression (Clause), Right_Opnd (Expression (Clause)));
1980 Inputs := Expression (Clause);
1982 -- Multiple outputs appear as an aggregate
1984 if Nkind (Outputs) = N_Aggregate then
1985 Last_Output := Last (Expressions (Outputs));
1987 Output := First (Expressions (Outputs));
1988 while Present (Output) loop
1990 -- Normalization may remove an output from its list,
1991 -- preserve the subsequent output now.
1993 Next_Output := Next (Output);
1995 Create_Or_Modify_Clause
1996 (Output => Output,
1997 Outputs => Outputs,
1998 Inputs => Inputs,
1999 After => Clause,
2000 In_Place => Output = Last_Output,
2001 Multiple => True);
2003 Output := Next_Output;
2004 end loop;
2006 -- Solitary output
2008 else
2009 Create_Or_Modify_Clause
2010 (Output => Outputs,
2011 Outputs => Empty,
2012 Inputs => Inputs,
2013 After => Empty,
2014 In_Place => True,
2015 Multiple => False);
2016 end if;
2017 end if;
2018 end Normalize_Clause;
2020 -- Local variables
2022 Deps : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
2023 Subp_Id : constant Entity_Id := Defining_Entity (Subp_Decl);
2025 Clause : Node_Id;
2026 Errors : Nat;
2027 Last_Clause : Node_Id;
2028 Restore_Scope : Boolean := False;
2030 -- Start of processing for Analyze_Depends_In_Decl_Part
2032 begin
2033 -- Do not analyze the pragma multiple times
2035 if Is_Analyzed_Pragma (N) then
2036 return;
2037 end if;
2039 -- Empty dependency list
2041 if Nkind (Deps) = N_Null then
2043 -- Gather all states, objects and formal parameters that the
2044 -- subprogram may depend on. These items are obtained from the
2045 -- parameter profile or pragma [Refined_]Global (if available).
2047 Collect_Subprogram_Inputs_Outputs
2048 (Subp_Id => Subp_Id,
2049 Subp_Inputs => Subp_Inputs,
2050 Subp_Outputs => Subp_Outputs,
2051 Global_Seen => Global_Seen);
2053 -- Verify that every input or output of the subprogram appear in a
2054 -- dependency.
2056 Check_Usage (Subp_Inputs, All_Inputs_Seen, True);
2057 Check_Usage (Subp_Outputs, All_Outputs_Seen, False);
2058 Check_Function_Return;
2060 -- Dependency clauses appear as component associations of an aggregate
2062 elsif Nkind (Deps) = N_Aggregate then
2064 -- Do not attempt to perform analysis of a syntactically illegal
2065 -- clause as this will lead to misleading errors.
2067 if Has_Extra_Parentheses (Deps) then
2068 goto Leave;
2069 end if;
2071 if Present (Component_Associations (Deps)) then
2072 Last_Clause := Last (Component_Associations (Deps));
2074 -- Gather all states, objects and formal parameters that the
2075 -- subprogram may depend on. These items are obtained from the
2076 -- parameter profile or pragma [Refined_]Global (if available).
2078 Collect_Subprogram_Inputs_Outputs
2079 (Subp_Id => Subp_Id,
2080 Subp_Inputs => Subp_Inputs,
2081 Subp_Outputs => Subp_Outputs,
2082 Global_Seen => Global_Seen);
2084 -- When pragma [Refined_]Depends appears on a single concurrent
2085 -- type, it is relocated to the anonymous object.
2087 if Is_Single_Concurrent_Object (Spec_Id) then
2088 null;
2090 -- Ensure that the formal parameters are visible when analyzing
2091 -- all clauses. This falls out of the general rule of aspects
2092 -- pertaining to subprogram declarations.
2094 elsif not In_Open_Scopes (Spec_Id) then
2095 Restore_Scope := True;
2096 Push_Scope (Spec_Id);
2098 if Ekind (Spec_Id) = E_Task_Type then
2100 -- Task discriminants cannot appear in the [Refined_]Depends
2101 -- contract, but must be present for the analysis so that we
2102 -- can reject them with an informative error message.
2104 if Has_Discriminants (Spec_Id) then
2105 Install_Discriminants (Spec_Id);
2106 end if;
2108 elsif Is_Generic_Subprogram (Spec_Id) then
2109 Install_Generic_Formals (Spec_Id);
2111 else
2112 Install_Formals (Spec_Id);
2113 end if;
2114 end if;
2116 Clause := First (Component_Associations (Deps));
2117 while Present (Clause) loop
2118 Errors := Serious_Errors_Detected;
2120 -- The normalization mechanism may create extra clauses that
2121 -- contain replicated input and output names. There is no need
2122 -- to reanalyze them.
2124 if not Analyzed (Clause) then
2125 Set_Analyzed (Clause);
2127 Analyze_Dependency_Clause
2128 (Clause => Clause,
2129 Is_Last => Clause = Last_Clause);
2130 end if;
2132 -- Do not normalize a clause if errors were detected (count
2133 -- of Serious_Errors has increased) because the inputs and/or
2134 -- outputs may denote illegal items.
2136 if Serious_Errors_Detected = Errors then
2137 Normalize_Clause (Clause);
2138 end if;
2140 Next (Clause);
2141 end loop;
2143 if Restore_Scope then
2144 End_Scope;
2145 end if;
2147 -- Verify that every input or output of the subprogram appear in a
2148 -- dependency.
2150 Check_Usage (Subp_Inputs, All_Inputs_Seen, True);
2151 Check_Usage (Subp_Outputs, All_Outputs_Seen, False);
2152 Check_Function_Return;
2154 -- The dependency list is malformed. This is a syntax error, always
2155 -- report.
2157 else
2158 Error_Msg_N ("malformed dependency relation", Deps);
2159 goto Leave;
2160 end if;
2162 -- The top level dependency relation is malformed. This is a syntax
2163 -- error, always report.
2165 else
2166 Error_Msg_N ("malformed dependency relation", Deps);
2167 goto Leave;
2168 end if;
2170 -- Ensure that a state and a corresponding constituent do not appear
2171 -- together in pragma [Refined_]Depends.
2173 Check_State_And_Constituent_Use
2174 (States => States_Seen,
2175 Constits => Constits_Seen,
2176 Context => N);
2178 <<Leave>>
2179 Set_Is_Analyzed_Pragma (N);
2180 end Analyze_Depends_In_Decl_Part;
2182 --------------------------------------------
2183 -- Analyze_Exceptional_Cases_In_Decl_Part --
2184 --------------------------------------------
2186 -- WARNING: This routine manages Ghost regions. Return statements must be
2187 -- replaced by gotos which jump to the end of the routine and restore the
2188 -- Ghost mode.
2190 procedure Analyze_Exceptional_Cases_In_Decl_Part
2191 (N : Node_Id;
2192 Freeze_Id : Entity_Id := Empty)
2194 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
2195 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
2197 procedure Analyze_Exceptional_Contract (Exceptional_Contract : Node_Id);
2198 -- Verify the legality of a single exceptional contract
2200 procedure Check_Duplication (Id : Node_Id; Contracts : List_Id);
2201 -- Iterate through the identifiers in each contract to find duplicates
2203 ----------------------------------
2204 -- Analyze_Exceptional_Contract --
2205 ----------------------------------
2207 procedure Analyze_Exceptional_Contract (Exceptional_Contract : Node_Id)
2209 Exception_Choice : Node_Id;
2210 Consequence : Node_Id;
2211 Errors : Nat;
2213 begin
2214 if Nkind (Exceptional_Contract) /= N_Component_Association then
2215 Error_Msg_N
2216 ("wrong syntax in exceptional contract", Exceptional_Contract);
2217 return;
2218 end if;
2220 Exception_Choice := First (Choices (Exceptional_Contract));
2221 Consequence := Expression (Exceptional_Contract);
2223 while Present (Exception_Choice) loop
2224 if Nkind (Exception_Choice) = N_Others_Choice then
2225 if Present (Next (Exception_Choice))
2226 or else Present (Next (Exceptional_Contract))
2227 or else Present (Prev (Exception_Choice))
2228 then
2229 Error_Msg_N
2230 ("OTHERS must appear alone and last", Exception_Choice);
2231 end if;
2233 else
2234 Analyze (Exception_Choice);
2236 if Is_Entity_Name (Exception_Choice)
2237 and then Ekind (Entity (Exception_Choice)) = E_Exception
2238 then
2239 if Present (Renamed_Entity (Entity (Exception_Choice)))
2240 and then Entity (Exception_Choice) = Standard_Numeric_Error
2241 then
2242 Check_Restriction
2243 (No_Obsolescent_Features, Exception_Choice);
2245 if Warn_On_Obsolescent_Feature then
2246 Error_Msg_N
2247 ("Numeric_Error is an obsolescent feature " &
2248 "(RM J.6(1))?j?",
2249 Exception_Choice);
2250 Error_Msg_N
2251 ("\use Constraint_Error instead?j?",
2252 Exception_Choice);
2253 end if;
2254 end if;
2256 Check_Duplication
2257 (Exception_Choice, List_Containing (Exceptional_Contract));
2259 -- Check for exception declared within generic formal
2260 -- package (which is illegal, see RM 11.2(8)).
2262 declare
2263 Ent : Entity_Id := Entity (Exception_Choice);
2264 Scop : Entity_Id;
2266 begin
2267 if Present (Renamed_Entity (Ent)) then
2268 Ent := Renamed_Entity (Ent);
2269 end if;
2271 Scop := Scope (Ent);
2272 while Scop /= Standard_Standard
2273 and then Ekind (Scop) = E_Package
2274 loop
2275 if Nkind (Declaration_Node (Scop)) =
2276 N_Package_Specification
2277 and then
2278 Nkind (Original_Node (Parent
2279 (Declaration_Node (Scop)))) =
2280 N_Formal_Package_Declaration
2281 then
2282 Error_Msg_NE
2283 ("exception& is declared in generic formal "
2284 & "package", Exception_Choice, Ent);
2285 Error_Msg_N
2286 ("\and therefore cannot appear in contract "
2287 & "(RM 11.2(8))", Exception_Choice);
2288 exit;
2290 -- If the exception is declared in an inner instance,
2291 -- nothing else to check.
2293 elsif Is_Generic_Instance (Scop) then
2294 exit;
2295 end if;
2297 Scop := Scope (Scop);
2298 end loop;
2299 end;
2300 else
2301 Error_Msg_N ("exception name expected", Exception_Choice);
2302 end if;
2303 end if;
2305 Next (Exception_Choice);
2306 end loop;
2308 -- Now analyze the expressions of this contract
2310 Errors := Serious_Errors_Detected;
2312 -- Preanalyze_Assert_Expression, but without enforcing any of the two
2313 -- acceptable types.
2315 Preanalyze_Assert_Expression (Consequence, Any_Boolean);
2317 -- Emit a clarification message when the consequence contains at
2318 -- least one undefined reference, possibly due to contract freezing.
2320 if Errors /= Serious_Errors_Detected
2321 and then Present (Freeze_Id)
2322 and then Has_Undefined_Reference (Consequence)
2323 then
2324 Contract_Freeze_Error (Spec_Id, Freeze_Id);
2325 end if;
2326 end Analyze_Exceptional_Contract;
2328 -----------------------
2329 -- Check_Duplication --
2330 -----------------------
2332 procedure Check_Duplication (Id : Node_Id; Contracts : List_Id) is
2333 Contract : Node_Id;
2334 Id1 : Node_Id;
2335 Id_Entity : Entity_Id := Entity (Id);
2337 begin
2338 if Present (Renamed_Entity (Id_Entity)) then
2339 Id_Entity := Renamed_Entity (Id_Entity);
2340 end if;
2342 Contract := First (Contracts);
2343 while Present (Contract) loop
2344 Id1 := First (Choices (Contract));
2345 while Present (Id1) loop
2347 -- Only check against the exception choices which precede
2348 -- Id in the contract, since the ones that follow Id have not
2349 -- been analyzed yet and will be checked in a subsequent call.
2351 if Id = Id1 then
2352 return;
2354 -- Duplication both simple and via a renaming across different
2355 -- exceptional contracts is illegal.
2357 elsif Nkind (Id1) /= N_Others_Choice
2358 and then
2359 (Id_Entity = Entity (Id1)
2360 or else Id_Entity = Renamed_Entity (Entity (Id1)))
2361 and then Contract /= Parent (Id)
2362 then
2363 Error_Msg_Sloc := Sloc (Id1);
2364 Error_Msg_NE ("exception choice duplicates &#", Id, Id1);
2365 end if;
2367 Next (Id1);
2368 end loop;
2370 Next (Contract);
2371 end loop;
2372 end Check_Duplication;
2374 -- Local variables
2376 Exceptional_Contracts : constant Node_Id :=
2377 Expression (Get_Argument (N, Spec_Id));
2379 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
2380 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
2381 -- Save the Ghost-related attributes to restore on exit
2383 Exceptional_Contract : Node_Id;
2384 Restore_Scope : Boolean := False;
2386 -- Start of processing for Analyze_Subprogram_Variant_In_Decl_Part
2388 begin
2389 -- Do not analyze the pragma multiple times
2391 if Is_Analyzed_Pragma (N) then
2392 return;
2393 end if;
2395 -- Set the Ghost mode in effect from the pragma. Due to the delayed
2396 -- analysis of the pragma, the Ghost mode at point of declaration and
2397 -- point of analysis may not necessarily be the same. Use the mode in
2398 -- effect at the point of declaration.
2400 Set_Ghost_Mode (N);
2402 -- Single and multiple contracts must appear in aggregate form. If this
2403 -- is not the case, then either the parser of the analysis of the pragma
2404 -- failed to produce an aggregate, e.g. when the contract is "null" or a
2405 -- "(null record)".
2407 pragma Assert
2408 (if Nkind (Exceptional_Contracts) = N_Aggregate
2409 then Null_Record_Present (Exceptional_Contracts)
2410 xor (Present (Component_Associations (Exceptional_Contracts))
2412 Present (Expressions (Exceptional_Contracts)))
2413 else Nkind (Exceptional_Contracts) = N_Null);
2415 -- Only clauses of the following form are allowed:
2417 -- exceptional_contract ::=
2418 -- [choice_parameter_specification:]
2419 -- exception_choice {'|' exception_choice} => consequence
2421 -- where
2423 -- consequence ::= Boolean_expression
2425 if Nkind (Exceptional_Contracts) = N_Aggregate
2426 and then Present (Component_Associations (Exceptional_Contracts))
2427 and then No (Expressions (Exceptional_Contracts))
2428 then
2430 -- Check that the expression is a proper aggregate (no parentheses)
2432 if Paren_Count (Exceptional_Contracts) /= 0 then
2433 Error_Msg_F -- CODEFIX
2434 ("redundant parentheses", Exceptional_Contracts);
2435 end if;
2437 -- Ensure that the formal parameters are visible when analyzing all
2438 -- clauses. This falls out of the general rule of aspects pertaining
2439 -- to subprogram declarations.
2441 if not In_Open_Scopes (Spec_Id) then
2442 Restore_Scope := True;
2443 Push_Scope (Spec_Id);
2445 if Is_Generic_Subprogram (Spec_Id) then
2446 Install_Generic_Formals (Spec_Id);
2447 else
2448 Install_Formals (Spec_Id);
2449 end if;
2450 end if;
2452 Exceptional_Contract :=
2453 First (Component_Associations (Exceptional_Contracts));
2454 while Present (Exceptional_Contract) loop
2455 Analyze_Exceptional_Contract (Exceptional_Contract);
2456 Next (Exceptional_Contract);
2457 end loop;
2459 if Restore_Scope then
2460 End_Scope;
2461 end if;
2463 -- Otherwise the pragma is illegal
2465 else
2466 Error_Msg_N ("wrong syntax for exceptional cases", N);
2467 end if;
2469 Set_Is_Analyzed_Pragma (N);
2471 Restore_Ghost_Region (Saved_GM, Saved_IGR);
2472 end Analyze_Exceptional_Cases_In_Decl_Part;
2474 --------------------------------------------
2475 -- Analyze_External_Property_In_Decl_Part --
2476 --------------------------------------------
2478 procedure Analyze_External_Property_In_Decl_Part
2479 (N : Node_Id;
2480 Expr_Val : out Boolean)
2482 Prag_Id : constant Pragma_Id := Get_Pragma_Id (Pragma_Name (N));
2483 Arg1 : constant Node_Id :=
2484 First (Pragma_Argument_Associations (N));
2485 Obj_Decl : constant Node_Id := Find_Related_Context (N);
2486 Obj_Id : constant Entity_Id := Defining_Entity (Obj_Decl);
2487 Obj_Typ : Entity_Id;
2488 Expr : Node_Id;
2490 begin
2491 if Is_Type (Obj_Id) then
2492 Obj_Typ := Obj_Id;
2493 else
2494 Obj_Typ := Etype (Obj_Id);
2495 end if;
2497 -- Ensure that the Boolean expression (if present) is static. A missing
2498 -- argument defaults the value to True (SPARK RM 7.1.2(5)).
2500 Expr_Val := True;
2502 if Present (Arg1) then
2503 Expr := Get_Pragma_Arg (Arg1);
2505 if Is_OK_Static_Expression (Expr) then
2506 Expr_Val := Is_True (Expr_Value (Expr));
2507 end if;
2508 end if;
2510 -- The output parameter was set to the argument specified by the pragma.
2511 -- Do not analyze the pragma multiple times.
2513 if Is_Analyzed_Pragma (N) then
2514 return;
2515 end if;
2517 Error_Msg_Name_1 := Pragma_Name (N);
2519 -- An external property pragma must apply to an effectively volatile
2520 -- object other than a formal subprogram parameter (SPARK RM 7.1.3(2)).
2521 -- The check is performed at the end of the declarative region due to a
2522 -- possible out-of-order arrangement of pragmas:
2524 -- Obj : ...;
2525 -- pragma Async_Readers (Obj);
2526 -- pragma Volatile (Obj);
2528 if Prag_Id /= Pragma_No_Caching
2529 and then not Is_Effectively_Volatile (Obj_Id)
2530 then
2531 if No_Caching_Enabled (Obj_Id) then
2532 if Expr_Val then -- Confirming value of False is allowed
2533 SPARK_Msg_N
2534 ("illegal combination of external property % and property "
2535 & """No_Caching"" (SPARK RM 7.1.2(6))", N);
2536 end if;
2537 else
2538 SPARK_Msg_N
2539 ("external property % must apply to a volatile type or object",
2541 end if;
2543 -- Pragma No_Caching should only apply to volatile types or variables of
2544 -- a non-effectively volatile type (SPARK RM 7.1.2).
2546 elsif Prag_Id = Pragma_No_Caching then
2547 if Is_Effectively_Volatile (Obj_Typ) then
2548 SPARK_Msg_N ("property % must not apply to a type or object of "
2549 & "an effectively volatile type", N);
2550 elsif not Is_Volatile (Obj_Id) then
2551 SPARK_Msg_N
2552 ("property % must apply to a volatile type or object", N);
2553 end if;
2554 end if;
2556 Set_Is_Analyzed_Pragma (N);
2557 end Analyze_External_Property_In_Decl_Part;
2559 ---------------------------------
2560 -- Analyze_Global_In_Decl_Part --
2561 ---------------------------------
2563 procedure Analyze_Global_In_Decl_Part (N : Node_Id) is
2564 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
2565 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
2566 Subp_Id : constant Entity_Id := Defining_Entity (Subp_Decl);
2568 Constits_Seen : Elist_Id := No_Elist;
2569 -- A list containing the entities of all constituents processed so far.
2570 -- It aids in detecting illegal usage of a state and a corresponding
2571 -- constituent in pragma [Refinde_]Global.
2573 Seen : Elist_Id := No_Elist;
2574 -- A list containing the entities of all the items processed so far. It
2575 -- plays a role in detecting distinct entities.
2577 States_Seen : Elist_Id := No_Elist;
2578 -- A list containing the entities of all states processed so far. It
2579 -- helps in detecting illegal usage of a state and a corresponding
2580 -- constituent in pragma [Refined_]Global.
2582 In_Out_Seen : Boolean := False;
2583 Input_Seen : Boolean := False;
2584 Output_Seen : Boolean := False;
2585 Proof_Seen : Boolean := False;
2586 -- Flags used to verify the consistency of modes
2588 procedure Analyze_Global_List
2589 (List : Node_Id;
2590 Global_Mode : Name_Id := Name_Input);
2591 -- Verify the legality of a single global list declaration. Global_Mode
2592 -- denotes the current mode in effect.
2594 -------------------------
2595 -- Analyze_Global_List --
2596 -------------------------
2598 procedure Analyze_Global_List
2599 (List : Node_Id;
2600 Global_Mode : Name_Id := Name_Input)
2602 procedure Analyze_Global_Item
2603 (Item : Node_Id;
2604 Global_Mode : Name_Id);
2605 -- Verify the legality of a single global item declaration denoted by
2606 -- Item. Global_Mode denotes the current mode in effect.
2608 procedure Check_Duplicate_Mode
2609 (Mode : Node_Id;
2610 Status : in out Boolean);
2611 -- Flag Status denotes whether a particular mode has been seen while
2612 -- processing a global list. This routine verifies that Mode is not a
2613 -- duplicate mode and sets the flag Status (SPARK RM 6.1.4(9)).
2615 procedure Check_Mode_Restriction_In_Enclosing_Context
2616 (Item : Node_Id;
2617 Item_Id : Entity_Id);
2618 -- Verify that an item of mode In_Out or Output does not appear as
2619 -- an input in the Global aspect of an enclosing subprogram or task
2620 -- unit. If this is the case, emit an error. Item and Item_Id are
2621 -- respectively the item and its entity.
2623 procedure Check_Mode_Restriction_In_Function (Mode : Node_Id);
2624 -- Mode denotes either In_Out or Output. Depending on the kind of the
2625 -- related subprogram, emit an error if those two modes apply to a
2626 -- function (SPARK RM 6.1.4(10)).
2628 -------------------------
2629 -- Analyze_Global_Item --
2630 -------------------------
2632 procedure Analyze_Global_Item
2633 (Item : Node_Id;
2634 Global_Mode : Name_Id)
2636 Item_Id : Entity_Id;
2638 begin
2639 -- Detect one of the following cases
2641 -- with Global => (null, Name)
2642 -- with Global => (Name_1, null, Name_2)
2643 -- with Global => (Name, null)
2645 if Nkind (Item) = N_Null then
2646 SPARK_Msg_N ("cannot mix null and non-null global items", Item);
2647 return;
2648 end if;
2650 Analyze (Item);
2651 Resolve_State (Item);
2653 -- Find the entity of the item. If this is a renaming, climb the
2654 -- renaming chain to reach the root object. Renamings of non-
2655 -- entire objects do not yield an entity (Empty).
2657 Item_Id := Entity_Of (Item);
2659 if Present (Item_Id) then
2661 -- A global item may denote a formal parameter of an enclosing
2662 -- subprogram (SPARK RM 6.1.4(6)). Do this check first to
2663 -- provide a better error diagnostic.
2665 if Is_Formal (Item_Id) then
2666 if Scope (Item_Id) = Spec_Id then
2667 SPARK_Msg_NE
2668 (Fix_Msg (Spec_Id, "global item cannot reference "
2669 & "parameter of subprogram &"), Item, Spec_Id);
2670 return;
2671 end if;
2673 -- A global item may denote a concurrent type as long as it is
2674 -- the current instance of an enclosing protected or task type
2675 -- (SPARK RM 6.1.4).
2677 elsif Ekind (Item_Id) in E_Protected_Type | E_Task_Type then
2678 if Is_CCT_Instance (Item_Id, Spec_Id) then
2680 -- Pragma [Refined_]Global associated with a protected
2681 -- subprogram cannot mention the current instance of a
2682 -- protected type because the instance behaves as a
2683 -- formal parameter.
2685 if Ekind (Item_Id) = E_Protected_Type then
2686 if Scope (Spec_Id) = Item_Id then
2687 Error_Msg_Name_1 := Chars (Item_Id);
2688 SPARK_Msg_NE
2689 (Fix_Msg (Spec_Id, "global item of subprogram & "
2690 & "cannot reference current instance of "
2691 & "protected type %"), Item, Spec_Id);
2692 return;
2693 end if;
2695 -- Pragma [Refined_]Global associated with a task type
2696 -- cannot mention the current instance of a task type
2697 -- because the instance behaves as a formal parameter.
2699 else pragma Assert (Ekind (Item_Id) = E_Task_Type);
2700 if Spec_Id = Item_Id then
2701 Error_Msg_Name_1 := Chars (Item_Id);
2702 SPARK_Msg_NE
2703 (Fix_Msg (Spec_Id, "global item of subprogram & "
2704 & "cannot reference current instance of task "
2705 & "type %"), Item, Spec_Id);
2706 return;
2707 end if;
2708 end if;
2710 -- Otherwise the global item denotes a subtype mark that is
2711 -- not a current instance.
2713 else
2714 SPARK_Msg_N
2715 ("invalid use of subtype mark in global list", Item);
2716 return;
2717 end if;
2719 -- A global item may denote the anonymous object created for a
2720 -- single protected/task type as long as the current instance
2721 -- is the same single type (SPARK RM 6.1.4).
2723 elsif Is_Single_Concurrent_Object (Item_Id)
2724 and then Is_CCT_Instance (Etype (Item_Id), Spec_Id)
2725 then
2726 -- Pragma [Refined_]Global associated with a protected
2727 -- subprogram cannot mention the current instance of a
2728 -- protected type because the instance behaves as a formal
2729 -- parameter.
2731 if Is_Single_Protected_Object (Item_Id) then
2732 if Scope (Spec_Id) = Etype (Item_Id) then
2733 Error_Msg_Name_1 := Chars (Item_Id);
2734 SPARK_Msg_NE
2735 (Fix_Msg (Spec_Id, "global item of subprogram & "
2736 & "cannot reference current instance of protected "
2737 & "type %"), Item, Spec_Id);
2738 return;
2739 end if;
2741 -- Pragma [Refined_]Global associated with a task type
2742 -- cannot mention the current instance of a task type
2743 -- because the instance behaves as a formal parameter.
2745 else pragma Assert (Is_Single_Task_Object (Item_Id));
2746 if Spec_Id = Item_Id then
2747 Error_Msg_Name_1 := Chars (Item_Id);
2748 SPARK_Msg_NE
2749 (Fix_Msg (Spec_Id, "global item of subprogram & "
2750 & "cannot reference current instance of task "
2751 & "type %"), Item, Spec_Id);
2752 return;
2753 end if;
2754 end if;
2756 -- A formal object may act as a global item inside a generic
2758 elsif Is_Formal_Object (Item_Id) then
2759 null;
2761 elsif Ekind (Item_Id) in E_Constant | E_Variable
2762 and then Present (Ultimate_Overlaid_Entity (Item_Id))
2763 then
2764 SPARK_Msg_NE
2765 ("overlaying object & cannot appear in Global",
2766 Item, Item_Id);
2767 SPARK_Msg_NE
2768 ("\use the overlaid object & instead",
2769 Item, Ultimate_Overlaid_Entity (Item_Id));
2770 return;
2772 -- The only legal references are those to abstract states,
2773 -- objects and various kinds of constants (SPARK RM 6.1.4(4)).
2775 elsif Ekind (Item_Id) not in E_Abstract_State
2776 | E_Constant
2777 | E_Loop_Parameter
2778 | E_Variable
2779 then
2780 SPARK_Msg_N
2781 ("global item must denote object, state or current "
2782 & "instance of concurrent type", Item);
2784 if Is_Named_Number (Item_Id) then
2785 SPARK_Msg_NE
2786 ("\named number & is not an object", Item, Item_Id);
2787 end if;
2789 return;
2790 end if;
2792 -- State related checks
2794 if Ekind (Item_Id) = E_Abstract_State then
2796 -- Package and subprogram bodies are instantiated
2797 -- individually in a separate compiler pass. Due to this
2798 -- mode of instantiation, the refinement of a state may
2799 -- no longer be visible when a subprogram body contract
2800 -- is instantiated. Since the generic template is legal,
2801 -- do not perform this check in the instance to circumvent
2802 -- this oddity.
2804 if In_Instance then
2805 null;
2807 -- An abstract state with visible refinement cannot appear
2808 -- in pragma [Refined_]Global as its place must be taken by
2809 -- some of its constituents (SPARK RM 6.1.4(7)).
2811 elsif Has_Visible_Refinement (Item_Id) then
2812 SPARK_Msg_NE
2813 ("cannot mention state & in global refinement",
2814 Item, Item_Id);
2815 SPARK_Msg_N ("\use its constituents instead", Item);
2816 return;
2818 -- An external state which has Async_Writers or
2819 -- Effective_Reads enabled cannot appear as a global item
2820 -- of a nonvolatile function (SPARK RM 7.1.3(8)).
2822 elsif Is_External_State (Item_Id)
2823 and then (Async_Writers_Enabled (Item_Id)
2824 or else Effective_Reads_Enabled (Item_Id))
2825 and then Ekind (Spec_Id) in E_Function | E_Generic_Function
2826 and then not Is_Volatile_Function (Spec_Id)
2827 then
2828 SPARK_Msg_NE
2829 ("external state & cannot act as global item of "
2830 & "nonvolatile function", Item, Item_Id);
2831 return;
2833 -- If the reference to the abstract state appears in an
2834 -- enclosing package body that will eventually refine the
2835 -- state, record the reference for future checks.
2837 else
2838 Record_Possible_Body_Reference
2839 (State_Id => Item_Id,
2840 Ref => Item);
2841 end if;
2843 -- Constant related checks
2845 elsif Ekind (Item_Id) = E_Constant then
2847 -- Constant is a read-only item, therefore it cannot act as
2848 -- an output.
2850 if Global_Mode in Name_In_Out | Name_Output then
2852 -- Constant of an access-to-variable type is a read-write
2853 -- item in procedures, generic procedures, protected
2854 -- entries and tasks.
2856 if Is_Access_Variable (Etype (Item_Id))
2857 and then (Ekind (Spec_Id) in E_Entry
2858 | E_Entry_Family
2859 | E_Procedure
2860 | E_Generic_Procedure
2861 | E_Task_Type
2862 or else Is_Single_Task_Object (Spec_Id))
2863 then
2864 null;
2865 else
2866 SPARK_Msg_NE
2867 ("constant & cannot act as output", Item, Item_Id);
2868 return;
2869 end if;
2870 end if;
2872 -- Loop parameter related checks
2874 elsif Ekind (Item_Id) = E_Loop_Parameter then
2876 -- A loop parameter is a read-only item, therefore it cannot
2877 -- act as an output.
2879 if Global_Mode in Name_In_Out | Name_Output then
2880 SPARK_Msg_NE
2881 ("loop parameter & cannot act as output",
2882 Item, Item_Id);
2883 return;
2884 end if;
2886 -- Variable related checks. These are only relevant when
2887 -- SPARK_Mode is on as they are not standard Ada legality
2888 -- rules.
2890 elsif SPARK_Mode = On
2891 and then Ekind (Item_Id) = E_Variable
2892 and then Is_Effectively_Volatile_For_Reading (Item_Id)
2893 then
2894 -- The current instance of a protected unit is not an
2895 -- effectively volatile object, unless the protected unit
2896 -- is already volatile for another reason (SPARK RM 7.1.2).
2898 if Is_Single_Protected_Object (Item_Id)
2899 and then Is_CCT_Instance (Etype (Item_Id), Spec_Id)
2900 and then not Is_Effectively_Volatile_For_Reading
2901 (Item_Id, Ignore_Protected => True)
2902 then
2903 null;
2905 -- An effectively volatile object for reading cannot appear
2906 -- as a global item of a nonvolatile function (SPARK RM
2907 -- 7.1.3(8)).
2909 elsif Ekind (Spec_Id) in E_Function | E_Generic_Function
2910 and then not Is_Volatile_Function (Spec_Id)
2911 then
2912 Error_Msg_NE
2913 ("volatile object & cannot act as global item of a "
2914 & "function", Item, Item_Id);
2915 return;
2917 -- An effectively volatile object with external property
2918 -- Effective_Reads set to True must have mode Output or
2919 -- In_Out (SPARK RM 7.1.3(10)).
2921 elsif Effective_Reads_Enabled (Item_Id)
2922 and then Global_Mode = Name_Input
2923 then
2924 Error_Msg_NE
2925 ("volatile object & with property Effective_Reads must "
2926 & "have mode In_Out or Output", Item, Item_Id);
2927 return;
2928 end if;
2929 end if;
2931 -- When the item renames an entire object, replace the item
2932 -- with a reference to the object.
2934 if Entity (Item) /= Item_Id then
2935 Rewrite (Item, New_Occurrence_Of (Item_Id, Sloc (Item)));
2936 Analyze (Item);
2937 end if;
2939 -- Some form of illegal construct masquerading as a name
2940 -- (SPARK RM 6.1.4(4)).
2942 else
2943 Error_Msg_N
2944 ("global item must denote object, state or current instance "
2945 & "of concurrent type", Item);
2946 return;
2947 end if;
2949 -- Verify that an output does not appear as an input in an
2950 -- enclosing subprogram.
2952 if Global_Mode in Name_In_Out | Name_Output then
2953 Check_Mode_Restriction_In_Enclosing_Context (Item, Item_Id);
2954 end if;
2956 -- The same entity might be referenced through various way.
2957 -- Check the entity of the item rather than the item itself
2958 -- (SPARK RM 6.1.4(10)).
2960 if Contains (Seen, Item_Id) then
2961 SPARK_Msg_N ("duplicate global item", Item);
2963 -- Add the entity of the current item to the list of processed
2964 -- items.
2966 else
2967 Append_New_Elmt (Item_Id, Seen);
2969 if Ekind (Item_Id) = E_Abstract_State then
2970 Append_New_Elmt (Item_Id, States_Seen);
2972 -- The variable may eventually become a constituent of a single
2973 -- protected/task type. Record the reference now and verify its
2974 -- legality when analyzing the contract of the variable
2975 -- (SPARK RM 9.3).
2977 elsif Ekind (Item_Id) = E_Variable then
2978 Record_Possible_Part_Of_Reference
2979 (Var_Id => Item_Id,
2980 Ref => Item);
2981 end if;
2983 if Ekind (Item_Id) in E_Abstract_State | E_Constant | E_Variable
2984 and then Present (Encapsulating_State (Item_Id))
2985 then
2986 Append_New_Elmt (Item_Id, Constits_Seen);
2987 end if;
2988 end if;
2989 end Analyze_Global_Item;
2991 --------------------------
2992 -- Check_Duplicate_Mode --
2993 --------------------------
2995 procedure Check_Duplicate_Mode
2996 (Mode : Node_Id;
2997 Status : in out Boolean)
2999 begin
3000 if Status then
3001 SPARK_Msg_N ("duplicate global mode", Mode);
3002 end if;
3004 Status := True;
3005 end Check_Duplicate_Mode;
3007 -------------------------------------------------
3008 -- Check_Mode_Restriction_In_Enclosing_Context --
3009 -------------------------------------------------
3011 procedure Check_Mode_Restriction_In_Enclosing_Context
3012 (Item : Node_Id;
3013 Item_Id : Entity_Id)
3015 Context : Entity_Id;
3016 Dummy : Boolean;
3017 Inputs : Elist_Id := No_Elist;
3018 Outputs : Elist_Id := No_Elist;
3020 begin
3021 -- Traverse the scope stack looking for enclosing subprograms or
3022 -- tasks subject to pragma [Refined_]Global.
3024 Context := Scope (Subp_Id);
3025 while Present (Context) and then Context /= Standard_Standard loop
3027 -- For a single task type, retrieve the corresponding object to
3028 -- which pragma [Refined_]Global is attached.
3030 if Ekind (Context) = E_Task_Type
3031 and then Is_Single_Concurrent_Type (Context)
3032 then
3033 Context := Anonymous_Object (Context);
3034 end if;
3036 if Is_Subprogram_Or_Entry (Context)
3037 or else Ekind (Context) = E_Task_Type
3038 or else Is_Single_Task_Object (Context)
3039 then
3040 Collect_Subprogram_Inputs_Outputs
3041 (Subp_Id => Context,
3042 Subp_Inputs => Inputs,
3043 Subp_Outputs => Outputs,
3044 Global_Seen => Dummy);
3046 -- The item is classified as In_Out or Output but appears as
3047 -- an Input or a formal parameter of mode IN in an enclosing
3048 -- subprogram or task unit (SPARK RM 6.1.4(13)).
3050 if Appears_In (Inputs, Item_Id)
3051 and then not Appears_In (Outputs, Item_Id)
3052 then
3053 SPARK_Msg_NE
3054 ("global item & cannot have mode In_Out or Output",
3055 Item, Item_Id);
3057 if Is_Subprogram_Or_Entry (Context) then
3058 SPARK_Msg_NE
3059 (Fix_Msg (Subp_Id, "\item already appears as input "
3060 & "of subprogram &"), Item, Context);
3061 else
3062 SPARK_Msg_NE
3063 (Fix_Msg (Subp_Id, "\item already appears as input "
3064 & "of task &"), Item, Context);
3065 end if;
3067 -- Stop the traversal once an error has been detected
3069 exit;
3070 end if;
3071 end if;
3073 Context := Scope (Context);
3074 end loop;
3075 end Check_Mode_Restriction_In_Enclosing_Context;
3077 ----------------------------------------
3078 -- Check_Mode_Restriction_In_Function --
3079 ----------------------------------------
3081 procedure Check_Mode_Restriction_In_Function (Mode : Node_Id) is
3082 begin
3083 if Ekind (Spec_Id) in E_Function | E_Generic_Function then
3084 SPARK_Msg_N
3085 ("global mode & is not applicable to functions", Mode);
3086 end if;
3087 end Check_Mode_Restriction_In_Function;
3089 -- Local variables
3091 Assoc : Node_Id;
3092 Item : Node_Id;
3093 Mode : Node_Id;
3095 -- Start of processing for Analyze_Global_List
3097 begin
3098 if Nkind (List) = N_Null then
3099 Set_Analyzed (List);
3101 -- Single global item declaration
3103 elsif Nkind (List) in N_Expanded_Name
3104 | N_Identifier
3105 | N_Selected_Component
3106 then
3107 Analyze_Global_Item (List, Global_Mode);
3109 -- Simple global list or moded global list declaration
3111 elsif Nkind (List) = N_Aggregate then
3112 Set_Analyzed (List);
3114 -- The declaration of a simple global list appear as a collection
3115 -- of expressions.
3117 if Present (Expressions (List)) then
3118 if Present (Component_Associations (List)) then
3119 SPARK_Msg_N
3120 ("cannot mix moded and non-moded global lists", List);
3121 end if;
3123 Item := First (Expressions (List));
3124 while Present (Item) loop
3125 Analyze_Global_Item (Item, Global_Mode);
3126 Next (Item);
3127 end loop;
3129 -- The declaration of a moded global list appears as a collection
3130 -- of component associations where individual choices denote
3131 -- modes.
3133 elsif Present (Component_Associations (List)) then
3134 if Present (Expressions (List)) then
3135 SPARK_Msg_N
3136 ("cannot mix moded and non-moded global lists", List);
3137 end if;
3139 Assoc := First (Component_Associations (List));
3140 while Present (Assoc) loop
3141 Mode := First (Choices (Assoc));
3143 if Nkind (Mode) = N_Identifier then
3144 if Chars (Mode) = Name_In_Out then
3145 Check_Duplicate_Mode (Mode, In_Out_Seen);
3146 Check_Mode_Restriction_In_Function (Mode);
3148 elsif Chars (Mode) = Name_Input then
3149 Check_Duplicate_Mode (Mode, Input_Seen);
3151 elsif Chars (Mode) = Name_Output then
3152 Check_Duplicate_Mode (Mode, Output_Seen);
3153 Check_Mode_Restriction_In_Function (Mode);
3155 elsif Chars (Mode) = Name_Proof_In then
3156 Check_Duplicate_Mode (Mode, Proof_Seen);
3158 else
3159 SPARK_Msg_N ("invalid mode selector", Mode);
3160 end if;
3162 else
3163 SPARK_Msg_N ("invalid mode selector", Mode);
3164 end if;
3166 -- Items in a moded list appear as a collection of
3167 -- expressions. Reuse the existing machinery to analyze
3168 -- them.
3170 Analyze_Global_List
3171 (List => Expression (Assoc),
3172 Global_Mode => Chars (Mode));
3174 Next (Assoc);
3175 end loop;
3177 -- Invalid tree
3179 else
3180 raise Program_Error;
3181 end if;
3183 -- Any other attempt to declare a global item is illegal. This is a
3184 -- syntax error, always report.
3186 else
3187 Error_Msg_N ("malformed global list", List);
3188 end if;
3189 end Analyze_Global_List;
3191 -- Local variables
3193 Items : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
3195 Restore_Scope : Boolean := False;
3197 -- Start of processing for Analyze_Global_In_Decl_Part
3199 begin
3200 -- Do not analyze the pragma multiple times
3202 if Is_Analyzed_Pragma (N) then
3203 return;
3204 end if;
3206 -- There is nothing to be done for a null global list
3208 if Nkind (Items) = N_Null then
3209 Set_Analyzed (Items);
3211 -- Analyze the various forms of global lists and items. Note that some
3212 -- of these may be malformed in which case the analysis emits error
3213 -- messages.
3215 else
3216 -- When pragma [Refined_]Global appears on a single concurrent type,
3217 -- it is relocated to the anonymous object.
3219 if Is_Single_Concurrent_Object (Spec_Id) then
3220 null;
3222 -- Ensure that the formal parameters are visible when processing an
3223 -- item. This falls out of the general rule of aspects pertaining to
3224 -- subprogram declarations.
3226 elsif not In_Open_Scopes (Spec_Id) then
3227 Restore_Scope := True;
3228 Push_Scope (Spec_Id);
3230 if Ekind (Spec_Id) = E_Task_Type then
3232 -- Task discriminants cannot appear in the [Refined_]Global
3233 -- contract, but must be present for the analysis so that we
3234 -- can reject them with an informative error message.
3236 if Has_Discriminants (Spec_Id) then
3237 Install_Discriminants (Spec_Id);
3238 end if;
3240 elsif Is_Generic_Subprogram (Spec_Id) then
3241 Install_Generic_Formals (Spec_Id);
3243 else
3244 Install_Formals (Spec_Id);
3245 end if;
3246 end if;
3248 Analyze_Global_List (Items);
3250 if Restore_Scope then
3251 End_Scope;
3252 end if;
3253 end if;
3255 -- Ensure that a state and a corresponding constituent do not appear
3256 -- together in pragma [Refined_]Global.
3258 Check_State_And_Constituent_Use
3259 (States => States_Seen,
3260 Constits => Constits_Seen,
3261 Context => N);
3263 Set_Is_Analyzed_Pragma (N);
3264 end Analyze_Global_In_Decl_Part;
3266 --------------------------------------------
3267 -- Analyze_Initial_Condition_In_Decl_Part --
3268 --------------------------------------------
3270 -- WARNING: This routine manages Ghost regions. Return statements must be
3271 -- replaced by gotos which jump to the end of the routine and restore the
3272 -- Ghost mode.
3274 procedure Analyze_Initial_Condition_In_Decl_Part (N : Node_Id) is
3275 Pack_Decl : constant Node_Id := Find_Related_Package_Or_Body (N);
3276 Pack_Id : constant Entity_Id := Defining_Entity (Pack_Decl);
3277 Expr : constant Node_Id := Expression (Get_Argument (N, Pack_Id));
3279 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
3280 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
3281 -- Save the Ghost-related attributes to restore on exit
3283 begin
3284 -- Do not analyze the pragma multiple times
3286 if Is_Analyzed_Pragma (N) then
3287 return;
3288 end if;
3290 -- Set the Ghost mode in effect from the pragma. Due to the delayed
3291 -- analysis of the pragma, the Ghost mode at point of declaration and
3292 -- point of analysis may not necessarily be the same. Use the mode in
3293 -- effect at the point of declaration.
3295 Set_Ghost_Mode (N);
3297 -- The expression is preanalyzed because it has not been moved to its
3298 -- final place yet. A direct analysis may generate side effects and this
3299 -- is not desired at this point.
3301 Preanalyze_Assert_Expression (Expr, Standard_Boolean);
3302 Set_Is_Analyzed_Pragma (N);
3304 Restore_Ghost_Region (Saved_GM, Saved_IGR);
3305 end Analyze_Initial_Condition_In_Decl_Part;
3307 --------------------------------------
3308 -- Analyze_Initializes_In_Decl_Part --
3309 --------------------------------------
3311 procedure Analyze_Initializes_In_Decl_Part (N : Node_Id) is
3312 Pack_Decl : constant Node_Id := Find_Related_Package_Or_Body (N);
3313 Pack_Id : constant Entity_Id := Defining_Entity (Pack_Decl);
3315 Constits_Seen : Elist_Id := No_Elist;
3316 -- A list containing the entities of all constituents processed so far.
3317 -- It aids in detecting illegal usage of a state and a corresponding
3318 -- constituent in pragma Initializes.
3320 Items_Seen : Elist_Id := No_Elist;
3321 -- A list of all initialization items processed so far. This list is
3322 -- used to detect duplicate items.
3324 States_And_Objs : Elist_Id := No_Elist;
3325 -- A list of all abstract states and objects declared in the visible
3326 -- declarations of the related package. This list is used to detect the
3327 -- legality of initialization items.
3329 States_Seen : Elist_Id := No_Elist;
3330 -- A list containing the entities of all states processed so far. It
3331 -- helps in detecting illegal usage of a state and a corresponding
3332 -- constituent in pragma Initializes.
3334 procedure Analyze_Initialization_Item (Item : Node_Id);
3335 -- Verify the legality of a single initialization item
3337 procedure Analyze_Initialization_Item_With_Inputs (Item : Node_Id);
3338 -- Verify the legality of a single initialization item followed by a
3339 -- list of input items.
3341 procedure Collect_States_And_Objects (Pack_Decl : Node_Id);
3342 -- Inspect the visible declarations of the related package and gather
3343 -- the entities of all abstract states and objects in States_And_Objs.
3345 ---------------------------------
3346 -- Analyze_Initialization_Item --
3347 ---------------------------------
3349 procedure Analyze_Initialization_Item (Item : Node_Id) is
3350 Item_Id : Entity_Id;
3352 begin
3353 Analyze (Item);
3354 Resolve_State (Item);
3356 if Is_Entity_Name (Item) then
3357 Item_Id := Entity_Of (Item);
3359 if Present (Item_Id)
3360 and then Ekind (Item_Id) in
3361 E_Abstract_State | E_Constant | E_Variable
3362 then
3363 -- When the initialization item is undefined, it appears as
3364 -- Any_Id. Do not continue with the analysis of the item.
3366 if Item_Id = Any_Id then
3367 null;
3369 elsif Ekind (Item_Id) in E_Constant | E_Variable
3370 and then Present (Ultimate_Overlaid_Entity (Item_Id))
3371 then
3372 SPARK_Msg_NE
3373 ("overlaying object & cannot appear in Initializes",
3374 Item, Item_Id);
3375 SPARK_Msg_NE
3376 ("\use the overlaid object & instead",
3377 Item, Ultimate_Overlaid_Entity (Item_Id));
3379 -- The state or variable must be declared in the visible
3380 -- declarations of the package (SPARK RM 7.1.5(7)).
3382 elsif not Contains (States_And_Objs, Item_Id) then
3383 Error_Msg_Name_1 := Chars (Pack_Id);
3384 SPARK_Msg_NE
3385 ("initialization item & must appear in the visible "
3386 & "declarations of package %", Item, Item_Id);
3388 -- Detect a duplicate use of the same initialization item
3389 -- (SPARK RM 7.1.5(5)).
3391 elsif Contains (Items_Seen, Item_Id) then
3392 SPARK_Msg_N ("duplicate initialization item", Item);
3394 -- The item is legal, add it to the list of processed states
3395 -- and variables.
3397 else
3398 Append_New_Elmt (Item_Id, Items_Seen);
3400 if Ekind (Item_Id) = E_Abstract_State then
3401 Append_New_Elmt (Item_Id, States_Seen);
3402 end if;
3404 if Present (Encapsulating_State (Item_Id)) then
3405 Append_New_Elmt (Item_Id, Constits_Seen);
3406 end if;
3407 end if;
3409 -- The item references something that is not a state or object
3410 -- (SPARK RM 7.1.5(3)).
3412 else
3413 SPARK_Msg_N
3414 ("initialization item must denote object or state", Item);
3415 end if;
3417 -- Some form of illegal construct masquerading as a name
3418 -- (SPARK RM 7.1.5(3)). This is a syntax error, always report.
3420 else
3421 Error_Msg_N
3422 ("initialization item must denote object or state", Item);
3423 end if;
3424 end Analyze_Initialization_Item;
3426 ---------------------------------------------
3427 -- Analyze_Initialization_Item_With_Inputs --
3428 ---------------------------------------------
3430 procedure Analyze_Initialization_Item_With_Inputs (Item : Node_Id) is
3431 Inputs_Seen : Elist_Id := No_Elist;
3432 -- A list of all inputs processed so far. This list is used to detect
3433 -- duplicate uses of an input.
3435 Non_Null_Seen : Boolean := False;
3436 Null_Seen : Boolean := False;
3437 -- Flags used to check the legality of an input list
3439 procedure Analyze_Input_Item (Input : Node_Id);
3440 -- Verify the legality of a single input item
3442 ------------------------
3443 -- Analyze_Input_Item --
3444 ------------------------
3446 procedure Analyze_Input_Item (Input : Node_Id) is
3447 Input_Id : Entity_Id;
3449 begin
3450 -- Null input list
3452 if Nkind (Input) = N_Null then
3453 if Null_Seen then
3454 SPARK_Msg_N
3455 ("multiple null initializations not allowed", Item);
3457 elsif Non_Null_Seen then
3458 SPARK_Msg_N
3459 ("cannot mix null and non-null initialization item", Item);
3460 else
3461 Null_Seen := True;
3462 end if;
3464 -- Input item
3466 else
3467 Non_Null_Seen := True;
3469 if Null_Seen then
3470 SPARK_Msg_N
3471 ("cannot mix null and non-null initialization item", Item);
3472 end if;
3474 Analyze (Input);
3475 Resolve_State (Input);
3477 if Is_Entity_Name (Input) then
3478 Input_Id := Entity_Of (Input);
3480 if Present (Input_Id)
3481 and then Ekind (Input_Id) in E_Abstract_State
3482 | E_Constant
3483 | E_Generic_In_Out_Parameter
3484 | E_Generic_In_Parameter
3485 | E_In_Parameter
3486 | E_In_Out_Parameter
3487 | E_Out_Parameter
3488 | E_Protected_Type
3489 | E_Task_Type
3490 | E_Variable
3491 then
3492 -- The input cannot denote states or objects declared
3493 -- within the related package (SPARK RM 7.1.5(4)).
3495 if Within_Scope (Input_Id, Current_Scope) then
3497 -- Do not consider generic formal parameters or their
3498 -- respective mappings to generic formals. Even though
3499 -- the formals appear within the scope of the package,
3500 -- it is allowed for an initialization item to depend
3501 -- on an input item.
3503 if Is_Formal_Object (Input_Id) then
3504 null;
3506 elsif Ekind (Input_Id) in E_Constant | E_Variable
3507 and then Present (Corresponding_Generic_Association
3508 (Declaration_Node (Input_Id)))
3509 then
3510 null;
3512 else
3513 Error_Msg_Name_1 := Chars (Pack_Id);
3514 SPARK_Msg_NE
3515 ("input item & cannot denote a visible object or "
3516 & "state of package %", Input, Input_Id);
3517 return;
3518 end if;
3519 end if;
3521 if Ekind (Input_Id) in E_Constant | E_Variable
3522 and then Present (Ultimate_Overlaid_Entity (Input_Id))
3523 then
3524 SPARK_Msg_NE
3525 ("overlaying object & cannot appear in Initializes",
3526 Input, Input_Id);
3527 SPARK_Msg_NE
3528 ("\use the overlaid object & instead",
3529 Input, Ultimate_Overlaid_Entity (Input_Id));
3530 return;
3531 end if;
3533 -- Detect a duplicate use of the same input item
3534 -- (SPARK RM 7.1.5(5)).
3536 if Contains (Inputs_Seen, Input_Id) then
3537 SPARK_Msg_N ("duplicate input item", Input);
3538 return;
3539 end if;
3541 -- At this point it is known that the input is legal. Add
3542 -- it to the list of processed inputs.
3544 Append_New_Elmt (Input_Id, Inputs_Seen);
3546 if Ekind (Input_Id) = E_Abstract_State then
3547 Append_New_Elmt (Input_Id, States_Seen);
3548 end if;
3550 if Ekind (Input_Id) in E_Abstract_State
3551 | E_Constant
3552 | E_Variable
3553 and then Present (Encapsulating_State (Input_Id))
3554 then
3555 Append_New_Elmt (Input_Id, Constits_Seen);
3556 end if;
3558 -- The input references something that is not a state or an
3559 -- object (SPARK RM 7.1.5(3)).
3561 else
3562 SPARK_Msg_N
3563 ("input item must denote object or state", Input);
3564 end if;
3566 -- Some form of illegal construct masquerading as a name
3567 -- (SPARK RM 7.1.5(3)). This is a syntax error, always report.
3569 else
3570 Error_Msg_N
3571 ("input item must denote object or state", Input);
3572 end if;
3573 end if;
3574 end Analyze_Input_Item;
3576 -- Local variables
3578 Inputs : constant Node_Id := Expression (Item);
3579 Elmt : Node_Id;
3580 Input : Node_Id;
3582 Name_Seen : Boolean := False;
3583 -- A flag used to detect multiple item names
3585 -- Start of processing for Analyze_Initialization_Item_With_Inputs
3587 begin
3588 -- Inspect the name of an item with inputs
3590 Elmt := First (Choices (Item));
3591 while Present (Elmt) loop
3592 if Name_Seen then
3593 SPARK_Msg_N ("only one item allowed in initialization", Elmt);
3594 else
3595 Name_Seen := True;
3596 Analyze_Initialization_Item (Elmt);
3597 end if;
3599 Next (Elmt);
3600 end loop;
3602 -- Multiple input items appear as an aggregate
3604 if Nkind (Inputs) = N_Aggregate then
3605 if Present (Expressions (Inputs)) then
3606 Input := First (Expressions (Inputs));
3607 while Present (Input) loop
3608 Analyze_Input_Item (Input);
3609 Next (Input);
3610 end loop;
3611 end if;
3613 if Present (Component_Associations (Inputs)) then
3614 SPARK_Msg_N
3615 ("inputs must appear in named association form", Inputs);
3616 end if;
3618 -- Single input item
3620 else
3621 Analyze_Input_Item (Inputs);
3622 end if;
3623 end Analyze_Initialization_Item_With_Inputs;
3625 --------------------------------
3626 -- Collect_States_And_Objects --
3627 --------------------------------
3629 procedure Collect_States_And_Objects (Pack_Decl : Node_Id) is
3630 Pack_Spec : constant Node_Id := Specification (Pack_Decl);
3631 Pack_Id : constant Entity_Id := Defining_Entity (Pack_Decl);
3632 Decl : Node_Id;
3633 State_Elmt : Elmt_Id;
3635 begin
3636 -- Collect the abstract states defined in the package (if any)
3638 if Has_Non_Null_Abstract_State (Pack_Id) then
3639 State_Elmt := First_Elmt (Abstract_States (Pack_Id));
3640 while Present (State_Elmt) loop
3641 Append_New_Elmt (Node (State_Elmt), States_And_Objs);
3642 Next_Elmt (State_Elmt);
3643 end loop;
3644 end if;
3646 -- Collect all objects that appear in the visible declarations of the
3647 -- related package.
3649 Decl := First (Visible_Declarations (Pack_Spec));
3650 while Present (Decl) loop
3651 if Comes_From_Source (Decl)
3652 and then Nkind (Decl) in N_Object_Declaration
3653 | N_Object_Renaming_Declaration
3654 then
3655 Append_New_Elmt (Defining_Entity (Decl), States_And_Objs);
3657 elsif Nkind (Decl) = N_Package_Declaration then
3658 Collect_States_And_Objects (Decl);
3660 elsif Is_Single_Concurrent_Type_Declaration (Decl) then
3661 Append_New_Elmt
3662 (Anonymous_Object (Defining_Entity (Decl)),
3663 States_And_Objs);
3664 end if;
3666 Next (Decl);
3667 end loop;
3668 end Collect_States_And_Objects;
3670 -- Local variables
3672 Inits : constant Node_Id := Expression (Get_Argument (N, Pack_Id));
3673 Init : Node_Id;
3675 -- Start of processing for Analyze_Initializes_In_Decl_Part
3677 begin
3678 -- Do not analyze the pragma multiple times
3680 if Is_Analyzed_Pragma (N) then
3681 return;
3682 end if;
3684 -- Nothing to do when the initialization list is empty
3686 if Nkind (Inits) = N_Null then
3687 return;
3688 end if;
3690 -- Single and multiple initialization clauses appear as an aggregate. If
3691 -- this is not the case, then either the parser or the analysis of the
3692 -- pragma failed to produce an aggregate.
3694 pragma Assert (Nkind (Inits) = N_Aggregate);
3696 -- Initialize the various lists used during analysis
3698 Collect_States_And_Objects (Pack_Decl);
3700 if Present (Expressions (Inits)) then
3701 Init := First (Expressions (Inits));
3702 while Present (Init) loop
3703 Analyze_Initialization_Item (Init);
3704 Next (Init);
3705 end loop;
3706 end if;
3708 if Present (Component_Associations (Inits)) then
3709 Init := First (Component_Associations (Inits));
3710 while Present (Init) loop
3711 Analyze_Initialization_Item_With_Inputs (Init);
3712 Next (Init);
3713 end loop;
3714 end if;
3716 -- Ensure that a state and a corresponding constituent do not appear
3717 -- together in pragma Initializes.
3719 Check_State_And_Constituent_Use
3720 (States => States_Seen,
3721 Constits => Constits_Seen,
3722 Context => N);
3724 Set_Is_Analyzed_Pragma (N);
3725 end Analyze_Initializes_In_Decl_Part;
3727 ---------------------
3728 -- Analyze_Part_Of --
3729 ---------------------
3731 procedure Analyze_Part_Of
3732 (Indic : Node_Id;
3733 Item_Id : Entity_Id;
3734 Encap : Node_Id;
3735 Encap_Id : out Entity_Id;
3736 Legal : out Boolean)
3738 procedure Check_Part_Of_Abstract_State;
3739 pragma Inline (Check_Part_Of_Abstract_State);
3740 -- Verify the legality of indicator Part_Of when the encapsulator is an
3741 -- abstract state.
3743 procedure Check_Part_Of_Concurrent_Type;
3744 pragma Inline (Check_Part_Of_Concurrent_Type);
3745 -- Verify the legality of indicator Part_Of when the encapsulator is a
3746 -- single concurrent type.
3748 ----------------------------------
3749 -- Check_Part_Of_Abstract_State --
3750 ----------------------------------
3752 procedure Check_Part_Of_Abstract_State is
3753 Pack_Id : Entity_Id;
3754 Placement : State_Space_Kind;
3755 Parent_Unit : Entity_Id;
3757 begin
3758 -- Determine where the object, package instantiation or state lives
3759 -- with respect to the enclosing packages or package bodies.
3761 Find_Placement_In_State_Space
3762 (Item_Id => Item_Id,
3763 Placement => Placement,
3764 Pack_Id => Pack_Id);
3766 -- The item appears in a non-package construct with a declarative
3767 -- part (subprogram, block, etc). As such, the item is not allowed
3768 -- to be a part of an encapsulating state because the item is not
3769 -- visible.
3771 if Placement = Not_In_Package then
3772 SPARK_Msg_N
3773 ("indicator Part_Of cannot appear in this context "
3774 & "(SPARK RM 7.2.6(5))", Indic);
3776 Error_Msg_Name_1 := Chars (Scope (Encap_Id));
3777 SPARK_Msg_NE
3778 ("\& is not part of the hidden state of package %",
3779 Indic, Item_Id);
3780 return;
3782 -- The item appears in the visible state space of some package. In
3783 -- general this scenario does not warrant Part_Of except when the
3784 -- package is a nongeneric private child unit and the encapsulating
3785 -- state is declared in a parent unit or a public descendant of that
3786 -- parent unit.
3788 elsif Placement = Visible_State_Space then
3789 if Is_Child_Unit (Pack_Id)
3790 and then not Is_Generic_Unit (Pack_Id)
3791 and then Is_Private_Descendant (Pack_Id)
3792 then
3793 -- A variable or state abstraction which is part of the visible
3794 -- state of a nongeneric private child unit or its public
3795 -- descendants must have its Part_Of indicator specified. The
3796 -- Part_Of indicator must denote a state declared by either the
3797 -- parent unit of the private unit or by a public descendant of
3798 -- that parent unit.
3800 -- Find the nearest private ancestor (which can be the current
3801 -- unit itself).
3803 Parent_Unit := Pack_Id;
3804 while Present (Parent_Unit) loop
3805 exit when Is_Private_Library_Unit (Parent_Unit);
3806 Parent_Unit := Scope (Parent_Unit);
3807 end loop;
3809 Parent_Unit := Scope (Parent_Unit);
3811 if not Is_Child_Or_Sibling (Pack_Id, Scope (Encap_Id)) then
3812 SPARK_Msg_NE
3813 ("indicator Part_Of must denote abstract state of & or of "
3814 & "its public descendant (SPARK RM 7.2.6(3))",
3815 Indic, Parent_Unit);
3816 return;
3818 elsif Scope (Encap_Id) = Parent_Unit
3819 or else
3820 (Is_Ancestor_Package (Parent_Unit, Scope (Encap_Id))
3821 and then not Is_Private_Descendant (Scope (Encap_Id)))
3822 then
3823 null;
3825 else
3826 SPARK_Msg_NE
3827 ("indicator Part_Of must denote abstract state of & or of "
3828 & "its public descendant (SPARK RM 7.2.6(3))",
3829 Indic, Parent_Unit);
3830 return;
3831 end if;
3833 -- Indicator Part_Of is not needed when the related package is
3834 -- not a nongeneric private child unit or a public descendant
3835 -- thereof.
3837 else
3838 SPARK_Msg_N
3839 ("indicator Part_Of cannot appear in this context "
3840 & "(SPARK RM 7.2.6(5))", Indic);
3842 Error_Msg_Name_1 := Chars (Pack_Id);
3843 SPARK_Msg_NE
3844 ("\& is declared in the visible part of package %",
3845 Indic, Item_Id);
3846 return;
3847 end if;
3849 -- When the item appears in the private state space of a package, the
3850 -- encapsulating state must be declared in the same package.
3852 elsif Placement = Private_State_Space then
3854 -- In the case of the abstract state of a nongeneric private
3855 -- child package, it may be encapsulated in the state of a
3856 -- public descendant of its parent package.
3858 declare
3859 function Is_Public_Descendant
3860 (Child, Ancestor : Entity_Id)
3861 return Boolean;
3862 -- Return True if Child is a public descendant of Pack
3864 --------------------------
3865 -- Is_Public_Descendant --
3866 --------------------------
3868 function Is_Public_Descendant
3869 (Child, Ancestor : Entity_Id)
3870 return Boolean
3872 P : Entity_Id := Child;
3873 begin
3874 while Is_Child_Unit (P)
3875 and then not Is_Private_Library_Unit (P)
3876 loop
3877 if Scope (P) = Ancestor then
3878 return True;
3879 end if;
3881 P := Scope (P);
3882 end loop;
3884 return False;
3885 end Is_Public_Descendant;
3887 -- Local variables
3889 Immediate_Pack_Id : constant Entity_Id := Scope (Item_Id);
3891 Is_State_Of_Private_Child : constant Boolean :=
3892 Is_Child_Unit (Immediate_Pack_Id)
3893 and then not Is_Generic_Unit (Immediate_Pack_Id)
3894 and then Is_Private_Descendant (Immediate_Pack_Id);
3896 Is_OK_Through_Sibling : Boolean := False;
3898 begin
3899 if Ekind (Item_Id) = E_Abstract_State
3900 and then Is_State_Of_Private_Child
3901 and then Is_Public_Descendant (Scope (Encap_Id), Pack_Id)
3902 then
3903 Is_OK_Through_Sibling := True;
3904 end if;
3906 if Scope (Encap_Id) /= Pack_Id
3907 and then not Is_OK_Through_Sibling
3908 then
3909 if Is_State_Of_Private_Child then
3910 SPARK_Msg_NE
3911 ("indicator Part_Of must denote abstract state of & "
3912 & "or of its public descendant "
3913 & "(SPARK RM 7.2.6(3))", Indic, Pack_Id);
3914 else
3915 SPARK_Msg_NE
3916 ("indicator Part_Of must denote an abstract state of "
3917 & "package & (SPARK RM 7.2.6(2))", Indic, Pack_Id);
3918 end if;
3920 Error_Msg_Name_1 := Chars (Pack_Id);
3921 SPARK_Msg_NE
3922 ("\& is declared in the private part of package %",
3923 Indic, Item_Id);
3924 return;
3925 end if;
3926 end;
3928 -- Items declared in the body state space of a package do not need
3929 -- Part_Of indicators as the refinement has already been seen.
3931 else
3932 SPARK_Msg_N
3933 ("indicator Part_Of cannot appear in this context "
3934 & "(SPARK RM 7.2.6(5))", Indic);
3936 if Scope (Encap_Id) = Pack_Id then
3937 Error_Msg_Name_1 := Chars (Pack_Id);
3938 SPARK_Msg_NE
3939 ("\& is declared in the body of package %", Indic, Item_Id);
3940 end if;
3942 return;
3943 end if;
3945 -- In the case of state in a (descendant of a private) child which
3946 -- is Part_Of the state of another package, the package defining the
3947 -- encapsulating abstract state should have a body, to ensure that it
3948 -- has a state refinement (SPARK RM 7.1.4(4)).
3950 if Enclosing_Comp_Unit_Node (Encap_Id) /=
3951 Enclosing_Comp_Unit_Node (Item_Id)
3952 and then not Unit_Requires_Body (Scope (Encap_Id))
3953 then
3954 SPARK_Msg_N
3955 ("indicator Part_Of must denote abstract state of package "
3956 & "with a body (SPARK RM 7.1.4(4))", Indic);
3957 return;
3958 end if;
3960 -- At this point it is known that the Part_Of indicator is legal
3962 Legal := True;
3963 end Check_Part_Of_Abstract_State;
3965 -----------------------------------
3966 -- Check_Part_Of_Concurrent_Type --
3967 -----------------------------------
3969 procedure Check_Part_Of_Concurrent_Type is
3970 function In_Proper_Order
3971 (First : Node_Id;
3972 Second : Node_Id) return Boolean;
3973 pragma Inline (In_Proper_Order);
3974 -- Determine whether node First precedes node Second
3976 procedure Placement_Error;
3977 pragma Inline (Placement_Error);
3978 -- Emit an error concerning the illegal placement of the item with
3979 -- respect to the single concurrent type.
3981 ---------------------
3982 -- In_Proper_Order --
3983 ---------------------
3985 function In_Proper_Order
3986 (First : Node_Id;
3987 Second : Node_Id) return Boolean
3989 N : Node_Id;
3991 begin
3992 if List_Containing (First) = List_Containing (Second) then
3993 N := First;
3994 while Present (N) loop
3995 if N = Second then
3996 return True;
3997 end if;
3999 Next (N);
4000 end loop;
4001 end if;
4003 return False;
4004 end In_Proper_Order;
4006 ---------------------
4007 -- Placement_Error --
4008 ---------------------
4010 procedure Placement_Error is
4011 begin
4012 SPARK_Msg_N
4013 ("indicator Part_Of must denote a previously declared single "
4014 & "protected type or single task type", Encap);
4015 end Placement_Error;
4017 -- Local variables
4019 Conc_Typ : constant Entity_Id := Etype (Encap_Id);
4020 Encap_Decl : constant Node_Id := Declaration_Node (Encap_Id);
4021 Encap_Context : constant Node_Id := Parent (Encap_Decl);
4023 Item_Context : Node_Id;
4024 Item_Decl : Node_Id;
4025 Prv_Decls : List_Id;
4026 Vis_Decls : List_Id;
4028 -- Start of processing for Check_Part_Of_Concurrent_Type
4030 begin
4031 -- Only abstract states and variables can act as constituents of an
4032 -- encapsulating single concurrent type.
4034 if Ekind (Item_Id) in E_Abstract_State | E_Variable then
4035 null;
4037 -- The constituent is a constant
4039 elsif Ekind (Item_Id) = E_Constant then
4040 Error_Msg_Name_1 := Chars (Encap_Id);
4041 SPARK_Msg_NE
4042 (Fix_Msg (Conc_Typ, "constant & cannot act as constituent of "
4043 & "single protected type %"), Indic, Item_Id);
4044 return;
4046 -- The constituent is a package instantiation
4048 else
4049 Error_Msg_Name_1 := Chars (Encap_Id);
4050 SPARK_Msg_NE
4051 (Fix_Msg (Conc_Typ, "package instantiation & cannot act as "
4052 & "constituent of single protected type %"), Indic, Item_Id);
4053 return;
4054 end if;
4056 -- When the item denotes an abstract state of a nested package, use
4057 -- the declaration of the package to detect proper placement.
4059 -- package Pack is
4060 -- task T;
4061 -- package Nested
4062 -- with Abstract_State => (State with Part_Of => T)
4064 if Ekind (Item_Id) = E_Abstract_State then
4065 Item_Decl := Unit_Declaration_Node (Scope (Item_Id));
4066 else
4067 Item_Decl := Declaration_Node (Item_Id);
4068 end if;
4070 Item_Context := Parent (Item_Decl);
4072 -- The item and the single concurrent type must appear in the same
4073 -- declarative region, with the item following the declaration of
4074 -- the single concurrent type (SPARK RM 9(3)).
4076 if Item_Context = Encap_Context then
4077 if Nkind (Item_Context) in N_Package_Specification
4078 | N_Protected_Definition
4079 | N_Task_Definition
4080 then
4081 Prv_Decls := Private_Declarations (Item_Context);
4082 Vis_Decls := Visible_Declarations (Item_Context);
4084 -- The placement is OK when the single concurrent type appears
4085 -- within the visible declarations and the item in the private
4086 -- declarations.
4088 -- package Pack is
4089 -- protected PO ...
4090 -- private
4091 -- Constit : ... with Part_Of => PO;
4092 -- end Pack;
4094 if List_Containing (Encap_Decl) = Vis_Decls
4095 and then List_Containing (Item_Decl) = Prv_Decls
4096 then
4097 null;
4099 -- The placement is illegal when the item appears within the
4100 -- visible declarations and the single concurrent type is in
4101 -- the private declarations.
4103 -- package Pack is
4104 -- Constit : ... with Part_Of => PO;
4105 -- private
4106 -- protected PO ...
4107 -- end Pack;
4109 elsif List_Containing (Item_Decl) = Vis_Decls
4110 and then List_Containing (Encap_Decl) = Prv_Decls
4111 then
4112 Placement_Error;
4113 return;
4115 -- Otherwise both the item and the single concurrent type are
4116 -- in the same list. Ensure that the declaration of the single
4117 -- concurrent type precedes that of the item.
4119 elsif not In_Proper_Order
4120 (First => Encap_Decl,
4121 Second => Item_Decl)
4122 then
4123 Placement_Error;
4124 return;
4125 end if;
4127 -- Otherwise both the item and the single concurrent type are
4128 -- in the same list. Ensure that the declaration of the single
4129 -- concurrent type precedes that of the item.
4131 elsif not In_Proper_Order
4132 (First => Encap_Decl,
4133 Second => Item_Decl)
4134 then
4135 Placement_Error;
4136 return;
4137 end if;
4139 -- Otherwise the item and the single concurrent type reside within
4140 -- unrelated regions.
4142 else
4143 Error_Msg_Name_1 := Chars (Encap_Id);
4144 SPARK_Msg_NE
4145 (Fix_Msg (Conc_Typ, "constituent & must be declared "
4146 & "immediately within the same region as single protected "
4147 & "type %"), Indic, Item_Id);
4148 return;
4149 end if;
4151 -- At this point it is known that the Part_Of indicator is legal
4153 Legal := True;
4154 end Check_Part_Of_Concurrent_Type;
4156 -- Start of processing for Analyze_Part_Of
4158 begin
4159 -- Assume that the indicator is illegal
4161 Encap_Id := Empty;
4162 Legal := False;
4164 if Nkind (Encap) in
4165 N_Expanded_Name | N_Identifier | N_Selected_Component
4166 then
4167 Analyze (Encap);
4168 Resolve_State (Encap);
4170 Encap_Id := Entity (Encap);
4172 -- The encapsulator is an abstract state
4174 if Ekind (Encap_Id) = E_Abstract_State then
4175 null;
4177 -- The encapsulator is a single concurrent type (SPARK RM 9.3)
4179 elsif Is_Single_Concurrent_Object (Encap_Id) then
4180 null;
4182 -- Otherwise the encapsulator is not a legal choice
4184 else
4185 SPARK_Msg_N
4186 ("indicator Part_Of must denote abstract state, single "
4187 & "protected type or single task type", Encap);
4188 return;
4189 end if;
4191 -- This is a syntax error, always report
4193 else
4194 Error_Msg_N
4195 ("indicator Part_Of must denote abstract state, single protected "
4196 & "type or single task type", Encap);
4197 return;
4198 end if;
4200 -- Catch a case where indicator Part_Of denotes the abstract view of a
4201 -- variable which appears as an abstract state (SPARK RM 10.1.2 2).
4203 if From_Limited_With (Encap_Id)
4204 and then Present (Non_Limited_View (Encap_Id))
4205 and then Ekind (Non_Limited_View (Encap_Id)) = E_Variable
4206 then
4207 SPARK_Msg_N ("indicator Part_Of must denote abstract state", Encap);
4208 SPARK_Msg_N ("\& denotes abstract view of object", Encap);
4209 return;
4210 end if;
4212 -- The encapsulator is an abstract state
4214 if Ekind (Encap_Id) = E_Abstract_State then
4215 Check_Part_Of_Abstract_State;
4217 -- The encapsulator is a single concurrent type
4219 else
4220 Check_Part_Of_Concurrent_Type;
4221 end if;
4222 end Analyze_Part_Of;
4224 ----------------------------------
4225 -- Analyze_Part_Of_In_Decl_Part --
4226 ----------------------------------
4228 procedure Analyze_Part_Of_In_Decl_Part
4229 (N : Node_Id;
4230 Freeze_Id : Entity_Id := Empty)
4232 Encap : constant Node_Id :=
4233 Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
4234 Errors : constant Nat := Serious_Errors_Detected;
4235 Var_Decl : constant Node_Id := Find_Related_Context (N);
4236 Var_Id : constant Entity_Id := Defining_Entity (Var_Decl);
4237 Constits : Elist_Id;
4238 Encap_Id : Entity_Id;
4239 Legal : Boolean;
4241 begin
4242 -- Detect any discrepancies between the placement of the variable with
4243 -- respect to general state space and the encapsulating state or single
4244 -- concurrent type.
4246 Analyze_Part_Of
4247 (Indic => N,
4248 Item_Id => Var_Id,
4249 Encap => Encap,
4250 Encap_Id => Encap_Id,
4251 Legal => Legal);
4253 -- The Part_Of indicator turns the variable into a constituent of the
4254 -- encapsulating state or single concurrent type.
4256 if Legal then
4257 pragma Assert (Present (Encap_Id));
4258 Constits := Part_Of_Constituents (Encap_Id);
4260 if No (Constits) then
4261 Constits := New_Elmt_List;
4262 Set_Part_Of_Constituents (Encap_Id, Constits);
4263 end if;
4265 Append_Elmt (Var_Id, Constits);
4266 Set_Encapsulating_State (Var_Id, Encap_Id);
4268 -- A Part_Of constituent partially refines an abstract state. This
4269 -- property does not apply to protected or task units.
4271 if Ekind (Encap_Id) = E_Abstract_State then
4272 Set_Has_Partial_Visible_Refinement (Encap_Id);
4273 end if;
4274 end if;
4276 -- Emit a clarification message when the encapsulator is undefined,
4277 -- possibly due to contract freezing.
4279 if Errors /= Serious_Errors_Detected
4280 and then Present (Freeze_Id)
4281 and then Has_Undefined_Reference (Encap)
4282 then
4283 Contract_Freeze_Error (Var_Id, Freeze_Id);
4284 end if;
4285 end Analyze_Part_Of_In_Decl_Part;
4287 --------------------
4288 -- Analyze_Pragma --
4289 --------------------
4291 procedure Analyze_Pragma (N : Node_Id) is
4292 Loc : constant Source_Ptr := Sloc (N);
4294 Pname : Name_Id := Pragma_Name (N);
4295 -- Name of the source pragma, or name of the corresponding aspect for
4296 -- pragmas which originate in a source aspect. In the latter case, the
4297 -- name may be different from the pragma name.
4299 Prag_Id : constant Pragma_Id := Get_Pragma_Id (Pname);
4301 Pragma_Exit : exception;
4302 -- This exception is used to exit pragma processing completely. It
4303 -- is used when an error is detected, and no further processing is
4304 -- required. It is also used if an earlier error has left the tree in
4305 -- a state where the pragma should not be processed.
4307 Arg_Count : Nat;
4308 -- Number of pragma argument associations
4310 Arg1 : Node_Id;
4311 Arg2 : Node_Id;
4312 Arg3 : Node_Id;
4313 Arg4 : Node_Id;
4314 Arg5 : Node_Id;
4315 -- First five pragma arguments (pragma argument association nodes, or
4316 -- Empty if the corresponding argument does not exist).
4318 type Name_List is array (Natural range <>) of Name_Id;
4319 type Args_List is array (Natural range <>) of Node_Id;
4320 -- Types used for arguments to Check_Arg_Order and Gather_Associations
4322 -----------------------
4323 -- Local Subprograms --
4324 -----------------------
4326 procedure Ada_2005_Pragma;
4327 -- Called for pragmas defined in Ada 2005, that are not in Ada 95. In
4328 -- Ada 95 mode, these are implementation defined pragmas, so should be
4329 -- caught by the No_Implementation_Pragmas restriction.
4331 procedure Ada_2012_Pragma;
4332 -- Called for pragmas defined in Ada 2012, that are not in Ada 95 or 05.
4333 -- In Ada 95 or 05 mode, these are implementation defined pragmas, so
4334 -- should be caught by the No_Implementation_Pragmas restriction.
4336 procedure Analyze_Depends_Global
4337 (Spec_Id : out Entity_Id;
4338 Subp_Decl : out Node_Id;
4339 Legal : out Boolean);
4340 -- Subsidiary to the analysis of pragmas Depends and Global. Verify the
4341 -- legality of the placement and related context of the pragma. Spec_Id
4342 -- is the entity of the related subprogram. Subp_Decl is the declaration
4343 -- of the related subprogram. Sets flag Legal when the pragma is legal.
4345 procedure Analyze_If_Present (Id : Pragma_Id);
4346 -- Inspect the remainder of the list containing pragma N and look for
4347 -- a pragma that matches Id. If found, analyze the pragma.
4349 procedure Analyze_Pre_Post_Condition;
4350 -- Subsidiary to the analysis of pragmas Precondition and Postcondition
4352 procedure Analyze_Refined_Depends_Global_Post
4353 (Spec_Id : out Entity_Id;
4354 Body_Id : out Entity_Id;
4355 Legal : out Boolean);
4356 -- Subsidiary routine to the analysis of body pragmas Refined_Depends,
4357 -- Refined_Global and Refined_Post. Verify the legality of the placement
4358 -- and related context of the pragma. Spec_Id is the entity of the
4359 -- related subprogram. Body_Id is the entity of the subprogram body.
4360 -- Flag Legal is set when the pragma is legal.
4362 procedure Analyze_Unmodified_Or_Unused (Is_Unused : Boolean := False);
4363 -- Perform full analysis of pragma Unmodified and the write aspect of
4364 -- pragma Unused. Flag Is_Unused should be set when verifying the
4365 -- semantics of pragma Unused.
4367 procedure Analyze_Unreferenced_Or_Unused (Is_Unused : Boolean := False);
4368 -- Perform full analysis of pragma Unreferenced and the read aspect of
4369 -- pragma Unused. Flag Is_Unused should be set when verifying the
4370 -- semantics of pragma Unused.
4372 procedure Check_Ada_83_Warning;
4373 -- Issues a warning message for the current pragma if operating in Ada
4374 -- 83 mode (used for language pragmas that are not a standard part of
4375 -- Ada 83). This procedure does not raise Pragma_Exit. Also notes use
4376 -- of 95 pragma.
4378 procedure Check_Arg_Count (Required : Nat);
4379 -- Check argument count for pragma is equal to given parameter. If not,
4380 -- then issue an error message and raise Pragma_Exit.
4382 -- Note: all routines whose name is Check_Arg_Is_xxx take an argument
4383 -- Arg which can either be a pragma argument association, in which case
4384 -- the check is applied to the expression of the association or an
4385 -- expression directly.
4387 procedure Check_Arg_Is_External_Name (Arg : Node_Id);
4388 -- Check that an argument has the right form for an EXTERNAL_NAME
4389 -- parameter of an extended import/export pragma. The rule is that the
4390 -- name must be an identifier or string literal (in Ada 83 mode) or a
4391 -- static string expression (in Ada 95 mode).
4393 procedure Check_Arg_Is_Identifier (Arg : Node_Id);
4394 -- Check the specified argument Arg to make sure that it is an
4395 -- identifier. If not give error and raise Pragma_Exit.
4397 procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id);
4398 -- Check the specified argument Arg to make sure that it is an integer
4399 -- literal. If not give error and raise Pragma_Exit.
4401 procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id);
4402 -- Check the specified argument Arg to make sure that it has the proper
4403 -- syntactic form for a local name and meets the semantic requirements
4404 -- for a local name. The local name is analyzed as part of the
4405 -- processing for this call. In addition, the local name is required
4406 -- to represent an entity at the library level.
4408 procedure Check_Arg_Is_Local_Name (Arg : Node_Id);
4409 -- Check the specified argument Arg to make sure that it has the proper
4410 -- syntactic form for a local name and meets the semantic requirements
4411 -- for a local name. The local name is analyzed as part of the
4412 -- processing for this call.
4414 procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id);
4415 -- Check the specified argument Arg to make sure that it is a valid
4416 -- locking policy name. If not give error and raise Pragma_Exit.
4418 procedure Check_Arg_Is_Partition_Elaboration_Policy (Arg : Node_Id);
4419 -- Check the specified argument Arg to make sure that it is a valid
4420 -- elaboration policy name. If not give error and raise Pragma_Exit.
4422 procedure Check_Arg_Is_One_Of
4423 (Arg : Node_Id;
4424 N1, N2 : Name_Id);
4425 procedure Check_Arg_Is_One_Of
4426 (Arg : Node_Id;
4427 N1, N2, N3 : Name_Id);
4428 procedure Check_Arg_Is_One_Of
4429 (Arg : Node_Id;
4430 N1, N2, N3, N4 : Name_Id);
4431 procedure Check_Arg_Is_One_Of
4432 (Arg : Node_Id;
4433 N1, N2, N3, N4, N5 : Name_Id);
4434 -- Check the specified argument Arg to make sure that it is an
4435 -- identifier whose name matches either N1 or N2 (or N3, N4, N5 if
4436 -- present). If not then give error and raise Pragma_Exit.
4438 procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id);
4439 -- Check the specified argument Arg to make sure that it is a valid
4440 -- queuing policy name. If not give error and raise Pragma_Exit.
4442 procedure Check_Arg_Is_OK_Static_Expression
4443 (Arg : Node_Id;
4444 Typ : Entity_Id := Empty);
4445 -- Check the specified argument Arg to make sure that it is a static
4446 -- expression of the given type (i.e. it will be analyzed and resolved
4447 -- using this type, which can be any valid argument to Resolve, e.g.
4448 -- Any_Integer is OK). If not, given error and raise Pragma_Exit. If
4449 -- Typ is left Empty, then any static expression is allowed. Includes
4450 -- checking that the argument does not raise Constraint_Error.
4452 procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id);
4453 -- Check the specified argument Arg to make sure that it is a valid task
4454 -- dispatching policy name. If not give error and raise Pragma_Exit.
4456 procedure Check_Arg_Order (Names : Name_List);
4457 -- Checks for an instance of two arguments with identifiers for the
4458 -- current pragma which are not in the sequence indicated by Names,
4459 -- and if so, generates a fatal message about bad order of arguments.
4461 procedure Check_At_Least_N_Arguments (N : Nat);
4462 -- Check there are at least N arguments present
4464 procedure Check_At_Most_N_Arguments (N : Nat);
4465 -- Check there are no more than N arguments present
4467 procedure Check_Component
4468 (Comp : Node_Id;
4469 UU_Typ : Entity_Id;
4470 In_Variant_Part : Boolean := False);
4471 -- Examine an Unchecked_Union component for correct use of per-object
4472 -- constrained subtypes, and for restrictions on finalizable components.
4473 -- UU_Typ is the related Unchecked_Union type. Flag In_Variant_Part
4474 -- should be set when Comp comes from a record variant.
4476 procedure Check_Duplicate_Pragma (E : Entity_Id);
4477 -- Check if a rep item of the same name as the current pragma is already
4478 -- chained as a rep pragma to the given entity. If so give a message
4479 -- about the duplicate, and then raise Pragma_Exit so does not return.
4480 -- Note that if E is a type, then this routine avoids flagging a pragma
4481 -- which applies to a parent type from which E is derived.
4483 procedure Check_Duplicated_Export_Name (Nam : Node_Id);
4484 -- Nam is an N_String_Literal node containing the external name set by
4485 -- an Import or Export pragma (or extended Import or Export pragma).
4486 -- This procedure checks for possible duplications if this is the export
4487 -- case, and if found, issues an appropriate error message.
4489 procedure Check_Expr_Is_OK_Static_Expression
4490 (Expr : Node_Id;
4491 Typ : Entity_Id := Empty);
4492 -- Check the specified expression Expr to make sure that it is a static
4493 -- expression of the given type (i.e. it will be analyzed and resolved
4494 -- using this type, which can be any valid argument to Resolve, e.g.
4495 -- Any_Integer is OK). If not, given error and raise Pragma_Exit. If
4496 -- Typ is left Empty, then any static expression is allowed. Includes
4497 -- checking that the expression does not raise Constraint_Error.
4499 procedure Check_First_Subtype (Arg : Node_Id);
4500 -- Checks that Arg, whose expression is an entity name, references a
4501 -- first subtype.
4503 procedure Check_Identifier (Arg : Node_Id; Id : Name_Id);
4504 -- Checks that the given argument has an identifier, and if so, requires
4505 -- it to match the given identifier name. If there is no identifier, or
4506 -- a non-matching identifier, then an error message is given and
4507 -- Pragma_Exit is raised.
4509 procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
4510 -- Checks that the given argument has an identifier, and if so, requires
4511 -- it to match one of the given identifier names. If there is no
4512 -- identifier, or a non-matching identifier, then an error message is
4513 -- given and Pragma_Exit is raised.
4515 procedure Check_In_Main_Program;
4516 -- Common checks for pragmas that appear within a main program
4517 -- (Priority, Main_Storage, Time_Slice, Relative_Deadline, CPU).
4519 procedure Check_Interrupt_Or_Attach_Handler;
4520 -- Common processing for first argument of pragma Interrupt_Handler or
4521 -- pragma Attach_Handler.
4523 procedure Check_Loop_Pragma_Placement;
4524 -- Verify whether pragmas Loop_Invariant, Loop_Optimize and Loop_Variant
4525 -- appear immediately within a construct restricted to loops, and that
4526 -- pragmas Loop_Invariant and Loop_Variant are grouped together.
4528 procedure Check_Is_In_Decl_Part_Or_Package_Spec;
4529 -- Check that pragma appears in a declarative part, or in a package
4530 -- specification, i.e. that it does not occur in a statement sequence
4531 -- in a body.
4533 procedure Check_No_Identifier (Arg : Node_Id);
4534 -- Checks that the given argument does not have an identifier. If
4535 -- an identifier is present, then an error message is issued, and
4536 -- Pragma_Exit is raised.
4538 procedure Check_No_Identifiers;
4539 -- Checks that none of the arguments to the pragma has an identifier.
4540 -- If any argument has an identifier, then an error message is issued,
4541 -- and Pragma_Exit is raised.
4543 procedure Check_No_Link_Name;
4544 -- Checks that no link name is specified
4546 procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id);
4547 -- Checks if the given argument has an identifier, and if so, requires
4548 -- it to match the given identifier name. If there is a non-matching
4549 -- identifier, then an error message is given and Pragma_Exit is raised.
4551 procedure Check_Optional_Identifier (Arg : Node_Id; Id : String);
4552 -- Checks if the given argument has an identifier, and if so, requires
4553 -- it to match the given identifier name. If there is a non-matching
4554 -- identifier, then an error message is given and Pragma_Exit is raised.
4555 -- In this version of the procedure, the identifier name is given as
4556 -- a string with lower case letters.
4558 procedure Check_Static_Boolean_Expression (Expr : Node_Id);
4559 -- Subsidiary to the analysis of pragmas Async_Readers, Async_Writers,
4560 -- Constant_After_Elaboration, Effective_Reads, Effective_Writes,
4561 -- Extensions_Visible and Volatile_Function. Ensure that expression Expr
4562 -- is an OK static boolean expression. Emit an error if this is not the
4563 -- case.
4565 procedure Check_Static_Constraint (Constr : Node_Id);
4566 -- Constr is a constraint from an N_Subtype_Indication node from a
4567 -- component constraint in an Unchecked_Union type, a range, or a
4568 -- discriminant association. This routine checks that the constraint
4569 -- is static as required by the restrictions for Unchecked_Union.
4571 procedure Check_Valid_Configuration_Pragma;
4572 -- Legality checks for placement of a configuration pragma
4574 procedure Check_Valid_Library_Unit_Pragma;
4575 -- Legality checks for library unit pragmas. A special case arises for
4576 -- pragmas in generic instances that come from copies of the original
4577 -- library unit pragmas in the generic templates. In the case of other
4578 -- than library level instantiations these can appear in contexts which
4579 -- would normally be invalid (they only apply to the original template
4580 -- and to library level instantiations), and they are simply ignored,
4581 -- which is implemented by rewriting them as null statements and
4582 -- optionally raising Pragma_Exit to terminate analysis. An exception
4583 -- is not always raised to avoid exception propagation during the
4584 -- bootstrap, so all callers should check whether N has been rewritten.
4586 procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id);
4587 -- Check an Unchecked_Union variant for lack of nested variants and
4588 -- presence of at least one component. UU_Typ is the related Unchecked_
4589 -- Union type.
4591 procedure Ensure_Aggregate_Form (Arg : Node_Id);
4592 -- Subsidiary routine to the processing of pragmas Abstract_State,
4593 -- Contract_Cases, Depends, Exceptional_Cases, Global, Initializes,
4594 -- Refined_Depends, Refined_Global, Refined_State and
4595 -- Subprogram_Variant. Transform argument Arg into an aggregate if not
4596 -- one already. N_Null is never transformed. Arg may denote an aspect
4597 -- specification or a pragma argument association.
4599 procedure Error_Pragma (Msg : String);
4600 pragma No_Return (Error_Pragma);
4601 -- Outputs error message for current pragma. The message contains a %
4602 -- that will be replaced with the pragma name, and the flag is placed
4603 -- on the pragma itself. Pragma_Exit is then raised. Note: this routine
4604 -- calls Fix_Error (see spec of that procedure for details).
4606 procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id);
4607 pragma No_Return (Error_Pragma_Arg);
4608 -- Outputs error message for current pragma. The message may contain
4609 -- a % that will be replaced with the pragma name. The parameter Arg
4610 -- may either be a pragma argument association, in which case the flag
4611 -- is placed on the expression of this association, or an expression,
4612 -- in which case the flag is placed directly on the expression. The
4613 -- message is placed using Error_Msg_N, so the message may also contain
4614 -- an & insertion character which will reference the given Arg value.
4615 -- After placing the message, Pragma_Exit is raised. Note: this routine
4616 -- calls Fix_Error (see spec of that procedure for details).
4618 procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id);
4619 pragma No_Return (Error_Pragma_Arg);
4620 -- Similar to above form of Error_Pragma_Arg except that two messages
4621 -- are provided, the second is a continuation comment starting with \.
4623 procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id);
4624 pragma No_Return (Error_Pragma_Arg_Ident);
4625 -- Outputs error message for current pragma. The message may contain a %
4626 -- that will be replaced with the pragma name. The parameter Arg must be
4627 -- a pragma argument association with a non-empty identifier (i.e. its
4628 -- Chars field must be set), and the error message is placed on the
4629 -- identifier. The message is placed using Error_Msg_N so the message
4630 -- may also contain an & insertion character which will reference
4631 -- the identifier. After placing the message, Pragma_Exit is raised.
4632 -- Note: this routine calls Fix_Error (see spec of that procedure for
4633 -- details).
4635 procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id);
4636 pragma No_Return (Error_Pragma_Ref);
4637 -- Outputs error message for current pragma. The message may contain
4638 -- a % that will be replaced with the pragma name. The parameter Ref
4639 -- must be an entity whose name can be referenced by & and sloc by #.
4640 -- After placing the message, Pragma_Exit is raised. Note: this routine
4641 -- calls Fix_Error (see spec of that procedure for details).
4643 function Find_Lib_Unit_Name return Entity_Id;
4644 -- Used for a library unit pragma to find the entity to which the
4645 -- library unit pragma applies, returns the entity found.
4647 procedure Find_Program_Unit_Name (Id : Node_Id);
4648 -- If the pragma is a compilation unit pragma, the id must denote the
4649 -- compilation unit in the same compilation, and the pragma must appear
4650 -- in the list of preceding or trailing pragmas. If it is a program
4651 -- unit pragma that is not a compilation unit pragma, then the
4652 -- identifier must be visible.
4654 function Find_Unique_Parameterless_Procedure
4655 (Name : Entity_Id;
4656 Arg : Node_Id) return Entity_Id;
4657 -- Used for a procedure pragma to find the unique parameterless
4658 -- procedure identified by Name, returns it if it exists, otherwise
4659 -- errors out and uses Arg as the pragma argument for the message.
4661 function Fix_Error (Msg : String) return String;
4662 -- This is called prior to issuing an error message. Msg is the normal
4663 -- error message issued in the pragma case. This routine checks for the
4664 -- case of a pragma coming from an aspect in the source, and returns a
4665 -- message suitable for the aspect case as follows:
4667 -- Each substring "pragma" is replaced by "aspect"
4669 -- If "argument of" is at the start of the error message text, it is
4670 -- replaced by "entity for".
4672 -- If "argument" is at the start of the error message text, it is
4673 -- replaced by "entity".
4675 -- So for example, "argument of pragma X must be discrete type"
4676 -- returns "entity for aspect X must be a discrete type".
4678 -- Finally Error_Msg_Name_1 is set to the name of the aspect (which may
4679 -- be different from the pragma name). If the current pragma results
4680 -- from rewriting another pragma, then Error_Msg_Name_1 is set to the
4681 -- original pragma name.
4683 procedure Gather_Associations
4684 (Names : Name_List;
4685 Args : out Args_List);
4686 -- This procedure is used to gather the arguments for a pragma that
4687 -- permits arbitrary ordering of parameters using the normal rules
4688 -- for named and positional parameters. The Names argument is a list
4689 -- of Name_Id values that corresponds to the allowed pragma argument
4690 -- association identifiers in order. The result returned in Args is
4691 -- a list of corresponding expressions that are the pragma arguments.
4692 -- Note that this is a list of expressions, not of pragma argument
4693 -- associations (Gather_Associations has completely checked all the
4694 -- optional identifiers when it returns). An entry in Args is Empty
4695 -- on return if the corresponding argument is not present.
4697 procedure GNAT_Pragma;
4698 -- Called for all GNAT defined pragmas to check the relevant restriction
4699 -- (No_Implementation_Pragmas).
4701 function Is_Before_First_Decl
4702 (Pragma_Node : Node_Id;
4703 Decls : List_Id) return Boolean;
4704 -- Return True if Pragma_Node is before the first declarative item in
4705 -- Decls where Decls is the list of declarative items.
4707 function Is_Configuration_Pragma return Boolean;
4708 -- Determines if the placement of the current pragma is appropriate
4709 -- for a configuration pragma.
4711 function Is_In_Context_Clause return Boolean;
4712 -- Returns True if pragma appears within the context clause of a unit,
4713 -- and False for any other placement (does not generate any messages).
4715 function Is_Static_String_Expression (Arg : Node_Id) return Boolean;
4716 -- Analyzes the argument, and determines if it is a static string
4717 -- expression, returns True if so, False if non-static or not String.
4718 -- A special case is that a string literal returns True in Ada 83 mode
4719 -- (which has no such thing as static string expressions). Note that
4720 -- the call analyzes its argument, so this cannot be used for the case
4721 -- where an identifier might not be declared.
4723 procedure Pragma_Misplaced;
4724 pragma No_Return (Pragma_Misplaced);
4725 -- Issue fatal error message for misplaced pragma
4727 procedure Process_Atomic_Independent_Shared_Volatile;
4728 -- Common processing for pragmas Atomic, Independent, Shared, Volatile,
4729 -- Volatile_Full_Access. Note that Shared is an obsolete Ada 83 pragma
4730 -- and treated as being identical in effect to pragma Atomic.
4732 procedure Process_Compile_Time_Warning_Or_Error;
4733 -- Common processing for Compile_Time_Error and Compile_Time_Warning
4735 procedure Process_Convention
4736 (C : out Convention_Id;
4737 Ent : out Entity_Id);
4738 -- Common processing for Convention, Interface, Import and Export.
4739 -- Checks first two arguments of pragma, and sets the appropriate
4740 -- convention value in the specified entity or entities. On return
4741 -- C is the convention, Ent is the referenced entity.
4743 procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id);
4744 -- Common processing for Disable/Enable_Atomic_Synchronization. Nam is
4745 -- Name_Suppress for Disable and Name_Unsuppress for Enable.
4747 procedure Process_Extended_Import_Export_Object_Pragma
4748 (Arg_Internal : Node_Id;
4749 Arg_External : Node_Id;
4750 Arg_Size : Node_Id);
4751 -- Common processing for the pragmas Import/Export_Object. The three
4752 -- arguments correspond to the three named parameters of the pragmas. An
4753 -- argument is empty if the corresponding parameter is not present in
4754 -- the pragma.
4756 procedure Process_Extended_Import_Export_Internal_Arg
4757 (Arg_Internal : Node_Id := Empty);
4758 -- Common processing for all extended Import and Export pragmas. The
4759 -- argument is the pragma parameter for the Internal argument. If
4760 -- Arg_Internal is empty or inappropriate, an error message is posted.
4761 -- Otherwise, on normal return, the Entity_Field of Arg_Internal is
4762 -- set to identify the referenced entity.
4764 procedure Process_Extended_Import_Export_Subprogram_Pragma
4765 (Arg_Internal : Node_Id;
4766 Arg_External : Node_Id;
4767 Arg_Parameter_Types : Node_Id;
4768 Arg_Result_Type : Node_Id := Empty;
4769 Arg_Mechanism : Node_Id;
4770 Arg_Result_Mechanism : Node_Id := Empty);
4771 -- Common processing for all extended Import and Export pragmas applying
4772 -- to subprograms. The caller omits any arguments that do not apply to
4773 -- the pragma in question (for example, Arg_Result_Type can be non-Empty
4774 -- only in the Import_Function and Export_Function cases). The argument
4775 -- names correspond to the allowed pragma association identifiers.
4777 procedure Process_Generic_List;
4778 -- Common processing for Share_Generic and Inline_Generic
4780 procedure Process_Import_Or_Interface;
4781 -- Common processing for Import or Interface
4783 procedure Process_Import_Predefined_Type;
4784 -- Processing for completing a type with pragma Import. This is used
4785 -- to declare types that match predefined C types, especially for cases
4786 -- without corresponding Ada predefined type.
4788 type Inline_Status is (Suppressed, Disabled, Enabled);
4789 -- Inline status of a subprogram, indicated as follows:
4790 -- Suppressed: inlining is suppressed for the subprogram
4791 -- Disabled: no inlining is requested for the subprogram
4792 -- Enabled: inlining is requested/required for the subprogram
4794 procedure Process_Inline (Status : Inline_Status);
4795 -- Common processing for No_Inline, Inline and Inline_Always. Parameter
4796 -- indicates the inline status specified by the pragma.
4798 procedure Process_Interface_Name
4799 (Subprogram_Def : Entity_Id;
4800 Ext_Arg : Node_Id;
4801 Link_Arg : Node_Id;
4802 Prag : Node_Id);
4803 -- Given the last two arguments of pragma Import, pragma Export, or
4804 -- pragma Interface_Name, performs validity checks and sets the
4805 -- Interface_Name field of the given subprogram entity to the
4806 -- appropriate external or link name, depending on the arguments given.
4807 -- Ext_Arg is always present, but Link_Arg may be missing. Note that
4808 -- Ext_Arg may represent the Link_Name if Link_Arg is missing, and
4809 -- appropriate named notation is used for Ext_Arg. If neither Ext_Arg
4810 -- nor Link_Arg is present, the interface name is set to the default
4811 -- from the subprogram name. In addition, the pragma itself is passed
4812 -- to analyze any expressions in the case the pragma came from an aspect
4813 -- specification.
4815 procedure Process_Interrupt_Or_Attach_Handler;
4816 -- Common processing for Interrupt and Attach_Handler pragmas
4818 procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
4819 -- Common processing for Restrictions and Restriction_Warnings pragmas.
4820 -- Warn is True for Restriction_Warnings, or for Restrictions if the
4821 -- flag Treat_Restrictions_As_Warnings is set, and False if this flag
4822 -- is not set in the Restrictions case.
4824 procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
4825 -- Common processing for Suppress and Unsuppress. The boolean parameter
4826 -- Suppress_Case is True for the Suppress case, and False for the
4827 -- Unsuppress case.
4829 procedure Record_Independence_Check (N : Node_Id; E : Entity_Id);
4830 -- Subsidiary to the analysis of pragmas Independent[_Components].
4831 -- Record such a pragma N applied to entity E for future checks.
4833 procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
4834 -- This procedure sets the Is_Exported flag for the given entity,
4835 -- checking that the entity was not previously imported. Arg is
4836 -- the argument that specified the entity. A check is also made
4837 -- for exporting inappropriate entities.
4839 procedure Set_Extended_Import_Export_External_Name
4840 (Internal_Ent : Entity_Id;
4841 Arg_External : Node_Id);
4842 -- Common processing for all extended import export pragmas. The first
4843 -- argument, Internal_Ent, is the internal entity, which has already
4844 -- been checked for validity by the caller. Arg_External is from the
4845 -- Import or Export pragma, and may be null if no External parameter
4846 -- was present. If Arg_External is present and is a non-null string
4847 -- (a null string is treated as the default), then the Interface_Name
4848 -- field of Internal_Ent is set appropriately.
4850 procedure Set_Imported (E : Entity_Id);
4851 -- This procedure sets the Is_Imported flag for the given entity,
4852 -- checking that it is not previously exported or imported.
4854 procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
4855 -- Mech is a parameter passing mechanism (see Import_Function syntax
4856 -- for MECHANISM_NAME). This routine checks that the mechanism argument
4857 -- has the right form, and if not issues an error message. If the
4858 -- argument has the right form then the Mechanism field of Ent is
4859 -- set appropriately.
4861 procedure Set_Rational_Profile;
4862 -- Activate the set of configuration pragmas and permissions that make
4863 -- up the Rational profile.
4865 procedure Set_Ravenscar_Profile (Profile : Profile_Name; N : Node_Id);
4866 -- Activate the set of configuration pragmas and restrictions that make
4867 -- up the Profile. Profile must be either GNAT_Extended_Ravenscar,
4868 -- GNAT_Ravenscar_EDF, Jorvik, or Ravenscar. N is the corresponding
4869 -- pragma node, which is used for error messages on any constructs
4870 -- violating the profile.
4872 ---------------------
4873 -- Ada_2005_Pragma --
4874 ---------------------
4876 procedure Ada_2005_Pragma is
4877 begin
4878 if Ada_Version <= Ada_95 then
4879 Check_Restriction (No_Implementation_Pragmas, N);
4880 end if;
4881 end Ada_2005_Pragma;
4883 ---------------------
4884 -- Ada_2012_Pragma --
4885 ---------------------
4887 procedure Ada_2012_Pragma is
4888 begin
4889 if Ada_Version <= Ada_2005 then
4890 Check_Restriction (No_Implementation_Pragmas, N);
4891 end if;
4892 end Ada_2012_Pragma;
4894 ----------------------------
4895 -- Analyze_Depends_Global --
4896 ----------------------------
4898 procedure Analyze_Depends_Global
4899 (Spec_Id : out Entity_Id;
4900 Subp_Decl : out Node_Id;
4901 Legal : out Boolean)
4903 begin
4904 -- Assume that the pragma is illegal
4906 Spec_Id := Empty;
4907 Subp_Decl := Empty;
4908 Legal := False;
4910 GNAT_Pragma;
4911 Check_Arg_Count (1);
4913 -- Ensure the proper placement of the pragma. Depends/Global must be
4914 -- associated with a subprogram declaration or a body that acts as a
4915 -- spec.
4917 Subp_Decl := Find_Related_Declaration_Or_Body (N, Do_Checks => True);
4919 -- Entry
4921 if Nkind (Subp_Decl) = N_Entry_Declaration then
4922 null;
4924 -- Generic subprogram
4926 elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
4927 null;
4929 -- Object declaration of a single concurrent type
4931 elsif Nkind (Subp_Decl) = N_Object_Declaration
4932 and then Is_Single_Concurrent_Object
4933 (Unique_Defining_Entity (Subp_Decl))
4934 then
4935 null;
4937 -- Single task type
4939 elsif Nkind (Subp_Decl) = N_Single_Task_Declaration then
4940 null;
4942 -- Abstract subprogram declaration
4944 elsif Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
4945 null;
4947 -- Subprogram body acts as spec
4949 elsif Nkind (Subp_Decl) = N_Subprogram_Body
4950 and then No (Corresponding_Spec (Subp_Decl))
4951 then
4952 null;
4954 -- Subprogram body stub acts as spec
4956 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
4957 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
4958 then
4959 null;
4961 -- Subprogram declaration
4963 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
4965 -- Pragmas Global and Depends are forbidden on null procedures
4966 -- (SPARK RM 6.1.2(2)).
4968 if Nkind (Specification (Subp_Decl)) = N_Procedure_Specification
4969 and then Null_Present (Specification (Subp_Decl))
4970 then
4971 Error_Msg_N (Fix_Error
4972 ("pragma % cannot apply to null procedure"), N);
4973 return;
4974 end if;
4976 -- Task type
4978 elsif Nkind (Subp_Decl) = N_Task_Type_Declaration then
4979 null;
4981 else
4982 Pragma_Misplaced;
4983 end if;
4985 -- If we get here, then the pragma is legal
4987 Legal := True;
4988 Spec_Id := Unique_Defining_Entity (Subp_Decl);
4990 -- When the related context is an entry, the entry must belong to a
4991 -- protected unit (SPARK RM 6.1.4(6)).
4993 if Is_Entry_Declaration (Spec_Id)
4994 and then Ekind (Scope (Spec_Id)) /= E_Protected_Type
4995 then
4996 Pragma_Misplaced;
4998 -- When the related context is an anonymous object created for a
4999 -- simple concurrent type, the type must be a task
5000 -- (SPARK RM 6.1.4(6)).
5002 elsif Is_Single_Concurrent_Object (Spec_Id)
5003 and then Ekind (Etype (Spec_Id)) /= E_Task_Type
5004 then
5005 Pragma_Misplaced;
5006 end if;
5008 -- A pragma that applies to a Ghost entity becomes Ghost for the
5009 -- purposes of legality checks and removal of ignored Ghost code.
5011 Mark_Ghost_Pragma (N, Spec_Id);
5012 Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
5013 end Analyze_Depends_Global;
5015 ------------------------
5016 -- Analyze_If_Present --
5017 ------------------------
5019 procedure Analyze_If_Present (Id : Pragma_Id) is
5020 Stmt : Node_Id;
5022 begin
5023 pragma Assert (Is_List_Member (N));
5025 -- Inspect the declarations or statements following pragma N looking
5026 -- for another pragma whose Id matches the caller's request. If it is
5027 -- available, analyze it.
5029 Stmt := Next (N);
5030 while Present (Stmt) loop
5031 if Nkind (Stmt) = N_Pragma and then Get_Pragma_Id (Stmt) = Id then
5032 Analyze_Pragma (Stmt);
5033 exit;
5035 -- The first source declaration or statement immediately following
5036 -- N ends the region where a pragma may appear.
5038 elsif Comes_From_Source (Stmt) then
5039 exit;
5040 end if;
5042 Next (Stmt);
5043 end loop;
5044 end Analyze_If_Present;
5046 --------------------------------
5047 -- Analyze_Pre_Post_Condition --
5048 --------------------------------
5050 procedure Analyze_Pre_Post_Condition is
5051 Prag_Iden : constant Node_Id := Pragma_Identifier (N);
5052 Subp_Decl : Node_Id;
5053 Subp_Id : Entity_Id;
5055 Duplicates_OK : Boolean := False;
5056 -- Flag set when a pre/postcondition allows multiple pragmas of the
5057 -- same kind.
5059 In_Body_OK : Boolean := False;
5060 -- Flag set when a pre/postcondition is allowed to appear on a body
5061 -- even though the subprogram may have a spec.
5063 Is_Pre_Post : Boolean := False;
5064 -- Flag set when the pragma is one of Pre, Pre_Class, Post or
5065 -- Post_Class.
5067 function Inherits_Class_Wide_Pre (E : Entity_Id) return Boolean;
5068 -- Implement rules in AI12-0131: an overriding operation can have
5069 -- a class-wide precondition only if one of its ancestors has an
5070 -- explicit class-wide precondition.
5072 -----------------------------
5073 -- Inherits_Class_Wide_Pre --
5074 -----------------------------
5076 function Inherits_Class_Wide_Pre (E : Entity_Id) return Boolean is
5077 Typ : constant Entity_Id := Find_Dispatching_Type (E);
5078 Cont : Node_Id;
5079 Prag : Node_Id;
5080 Prev : Entity_Id := Overridden_Operation (E);
5082 begin
5083 -- Check ancestors on the overriding operation to examine the
5084 -- preconditions that may apply to them.
5086 while Present (Prev) loop
5087 Cont := Contract (Prev);
5088 if Present (Cont) then
5089 Prag := Pre_Post_Conditions (Cont);
5090 while Present (Prag) loop
5091 if Pragma_Name (Prag) = Name_Precondition
5092 and then Class_Present (Prag)
5093 then
5094 return True;
5095 end if;
5097 Prag := Next_Pragma (Prag);
5098 end loop;
5099 end if;
5101 -- For a type derived from a generic formal type, the operation
5102 -- inheriting the condition is a renaming, not an overriding of
5103 -- the operation of the formal. Ditto for an inherited
5104 -- operation which has no explicit contracts.
5106 if Is_Generic_Type (Find_Dispatching_Type (Prev))
5107 or else not Comes_From_Source (Prev)
5108 then
5109 Prev := Alias (Prev);
5110 else
5111 Prev := Overridden_Operation (Prev);
5112 end if;
5113 end loop;
5115 -- If the controlling type of the subprogram has progenitors, an
5116 -- interface operation implemented by the current operation may
5117 -- have a class-wide precondition.
5119 if Has_Interfaces (Typ) then
5120 declare
5121 Elmt : Elmt_Id;
5122 Ints : Elist_Id;
5123 Prim : Entity_Id;
5124 Prim_Elmt : Elmt_Id;
5125 Prim_List : Elist_Id;
5127 begin
5128 Collect_Interfaces (Typ, Ints);
5129 Elmt := First_Elmt (Ints);
5131 -- Iterate over the primitive operations of each interface
5133 while Present (Elmt) loop
5134 Prim_List := Direct_Primitive_Operations (Node (Elmt));
5135 Prim_Elmt := First_Elmt (Prim_List);
5136 while Present (Prim_Elmt) loop
5137 Prim := Node (Prim_Elmt);
5138 if Chars (Prim) = Chars (E)
5139 and then Present (Contract (Prim))
5140 and then Class_Present
5141 (Pre_Post_Conditions (Contract (Prim)))
5142 then
5143 return True;
5144 end if;
5146 Next_Elmt (Prim_Elmt);
5147 end loop;
5149 Next_Elmt (Elmt);
5150 end loop;
5151 end;
5152 end if;
5154 return False;
5155 end Inherits_Class_Wide_Pre;
5157 -- Start of processing for Analyze_Pre_Post_Condition
5159 begin
5160 -- Change the name of pragmas Pre, Pre_Class, Post and Post_Class to
5161 -- offer uniformity among the various kinds of pre/postconditions by
5162 -- rewriting the pragma identifier. This allows the retrieval of the
5163 -- original pragma name by routine Original_Aspect_Pragma_Name.
5165 if Comes_From_Source (N) then
5166 if Pname in Name_Pre | Name_Pre_Class then
5167 Is_Pre_Post := True;
5168 Set_Class_Present (N, Pname = Name_Pre_Class);
5169 Rewrite (Prag_Iden, Make_Identifier (Loc, Name_Precondition));
5171 elsif Pname in Name_Post | Name_Post_Class then
5172 Is_Pre_Post := True;
5173 Set_Class_Present (N, Pname = Name_Post_Class);
5174 Rewrite (Prag_Iden, Make_Identifier (Loc, Name_Postcondition));
5175 end if;
5176 end if;
5178 -- Determine the semantics with respect to duplicates and placement
5179 -- in a body. Pragmas Precondition and Postcondition were introduced
5180 -- before aspects and are not subject to the same aspect-like rules.
5182 if Pname in Name_Precondition | Name_Postcondition then
5183 Duplicates_OK := True;
5184 In_Body_OK := True;
5185 end if;
5187 GNAT_Pragma;
5189 -- Pragmas Pre, Pre_Class, Post and Post_Class allow for a single
5190 -- argument without an identifier.
5192 if Is_Pre_Post then
5193 Check_Arg_Count (1);
5194 Check_No_Identifiers;
5196 -- Pragmas Precondition and Postcondition have complex argument
5197 -- profile.
5199 else
5200 Check_At_Least_N_Arguments (1);
5201 Check_At_Most_N_Arguments (2);
5202 Check_Optional_Identifier (Arg1, Name_Check);
5204 if Present (Arg2) then
5205 Check_Optional_Identifier (Arg2, Name_Message);
5206 Preanalyze_Spec_Expression
5207 (Get_Pragma_Arg (Arg2), Standard_String);
5208 end if;
5209 end if;
5211 -- For a pragma PPC in the extended main source unit, record enabled
5212 -- status in SCO.
5213 -- ??? nothing checks that the pragma is in the main source unit
5215 if Is_Checked (N) and then not Split_PPC (N) then
5216 Set_SCO_Pragma_Enabled (Loc);
5217 end if;
5219 -- Ensure the proper placement of the pragma
5221 Subp_Decl :=
5222 Find_Related_Declaration_Or_Body
5223 (N, Do_Checks => not Duplicates_OK);
5225 -- When a pre/postcondition pragma applies to an abstract subprogram,
5226 -- its original form must be an aspect with 'Class.
5228 if Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
5229 if not From_Aspect_Specification (N) then
5230 Error_Pragma
5231 ("pragma % cannot be applied to abstract subprogram");
5233 elsif not Class_Present (N) then
5234 Error_Pragma
5235 ("aspect % requires ''Class for abstract subprogram");
5236 end if;
5238 -- Entry declaration
5240 elsif Nkind (Subp_Decl) = N_Entry_Declaration then
5241 null;
5243 -- Generic subprogram declaration
5245 elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
5246 null;
5248 -- Subprogram body
5250 elsif Nkind (Subp_Decl) = N_Subprogram_Body
5251 and then (No (Corresponding_Spec (Subp_Decl)) or In_Body_OK)
5252 then
5253 null;
5255 -- Subprogram body stub
5257 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
5258 and then (No (Corresponding_Spec_Of_Stub (Subp_Decl)) or In_Body_OK)
5259 then
5260 null;
5262 -- Subprogram declaration
5264 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
5266 -- AI05-0230: When a pre/postcondition pragma applies to a null
5267 -- procedure, its original form must be an aspect with 'Class.
5269 if Nkind (Specification (Subp_Decl)) = N_Procedure_Specification
5270 and then Null_Present (Specification (Subp_Decl))
5271 and then From_Aspect_Specification (N)
5272 and then not Class_Present (N)
5273 then
5274 Error_Pragma ("aspect % requires ''Class for null procedure");
5275 end if;
5277 -- Implement the legality checks mandated by AI12-0131:
5278 -- Pre'Class shall not be specified for an overriding primitive
5279 -- subprogram of a tagged type T unless the Pre'Class aspect is
5280 -- specified for the corresponding primitive subprogram of some
5281 -- ancestor of T.
5283 declare
5284 E : constant Entity_Id := Defining_Entity (Subp_Decl);
5286 begin
5287 if Class_Present (N)
5288 and then Pragma_Name (N) = Name_Precondition
5289 and then Present (Overridden_Operation (E))
5290 and then not Inherits_Class_Wide_Pre (E)
5291 then
5292 Error_Msg_N
5293 ("illegal class-wide precondition on overriding operation",
5294 Corresponding_Aspect (N));
5295 end if;
5296 end;
5298 -- A renaming declaration may inherit a generated pragma, its
5299 -- placement comes from expansion, not from source.
5301 elsif Nkind (Subp_Decl) = N_Subprogram_Renaming_Declaration
5302 and then not Comes_From_Source (N)
5303 then
5304 null;
5306 -- For Ada 2022, pre/postconditions can appear on formal subprograms
5308 elsif Nkind (Subp_Decl) = N_Formal_Concrete_Subprogram_Declaration
5309 and then Ada_Version >= Ada_2022
5310 then
5311 null;
5313 -- An access-to-subprogram type can have pre/postconditions, which
5314 -- are both analyzed when attached to the type and copied to the
5315 -- generated subprogram wrapper and analyzed there.
5317 elsif Nkind (Subp_Decl) = N_Full_Type_Declaration
5318 and then Nkind (Type_Definition (Subp_Decl)) in
5319 N_Access_To_Subprogram_Definition
5320 then
5321 if Ada_Version < Ada_2022 then
5322 Error_Msg_Ada_2022_Feature
5323 ("pre/postcondition on access-to-subprogram", Loc);
5324 raise Pragma_Exit;
5325 end if;
5327 -- Otherwise the placement of the pragma is illegal
5329 else
5330 Pragma_Misplaced;
5331 end if;
5333 Subp_Id := Defining_Entity (Subp_Decl);
5335 -- A pragma that applies to a Ghost entity becomes Ghost for the
5336 -- purposes of legality checks and removal of ignored Ghost code.
5338 Mark_Ghost_Pragma (N, Subp_Id);
5340 -- Chain the pragma on the contract for further processing by
5341 -- Analyze_Pre_Post_Condition_In_Decl_Part.
5343 if Ekind (Subp_Id) in Access_Subprogram_Kind then
5344 Add_Contract_Item (N, Directly_Designated_Type (Subp_Id));
5345 else
5346 Add_Contract_Item (N, Subp_Id);
5347 end if;
5349 -- Fully analyze the pragma when it appears inside an entry or
5350 -- subprogram body because it cannot benefit from forward references.
5352 if Nkind (Subp_Decl) in N_Entry_Body
5353 | N_Subprogram_Body
5354 | N_Subprogram_Body_Stub
5355 then
5356 -- The legality checks of pragmas Precondition and Postcondition
5357 -- are affected by the SPARK mode in effect and the volatility of
5358 -- the context. Analyze all pragmas in a specific order.
5360 Analyze_If_Present (Pragma_SPARK_Mode);
5361 Analyze_If_Present (Pragma_Volatile_Function);
5362 Analyze_Pre_Post_Condition_In_Decl_Part (N);
5363 end if;
5364 end Analyze_Pre_Post_Condition;
5366 -----------------------------------------
5367 -- Analyze_Refined_Depends_Global_Post --
5368 -----------------------------------------
5370 procedure Analyze_Refined_Depends_Global_Post
5371 (Spec_Id : out Entity_Id;
5372 Body_Id : out Entity_Id;
5373 Legal : out Boolean)
5375 Body_Decl : Node_Id;
5376 Spec_Decl : Node_Id;
5378 begin
5379 -- Assume that the pragma is illegal
5381 Spec_Id := Empty;
5382 Body_Id := Empty;
5383 Legal := False;
5385 GNAT_Pragma;
5386 Check_Arg_Count (1);
5387 Check_No_Identifiers;
5389 -- Verify the placement of the pragma and check for duplicates. The
5390 -- pragma must apply to a subprogram body [stub].
5392 Body_Decl := Find_Related_Declaration_Or_Body (N, Do_Checks => True);
5394 if Nkind (Body_Decl) not in
5395 N_Entry_Body | N_Subprogram_Body | N_Subprogram_Body_Stub |
5396 N_Task_Body | N_Task_Body_Stub
5397 then
5398 Pragma_Misplaced;
5399 end if;
5401 Body_Id := Defining_Entity (Body_Decl);
5402 Spec_Id := Unique_Defining_Entity (Body_Decl);
5404 -- The pragma must apply to the second declaration of a subprogram.
5405 -- In other words, the body [stub] cannot acts as a spec.
5407 if No (Spec_Id) then
5408 Error_Pragma ("pragma % cannot apply to a stand alone body");
5410 -- Catch the case where the subprogram body is a subunit and acts as
5411 -- the third declaration of the subprogram.
5413 elsif Nkind (Parent (Body_Decl)) = N_Subunit then
5414 Error_Pragma ("pragma % cannot apply to a subunit");
5415 end if;
5417 -- A refined pragma can only apply to the body [stub] of a subprogram
5418 -- declared in the visible part of a package. Retrieve the context of
5419 -- the subprogram declaration.
5421 Spec_Decl := Unit_Declaration_Node (Spec_Id);
5423 -- When dealing with protected entries or protected subprograms, use
5424 -- the enclosing protected type as the proper context.
5426 if Ekind (Spec_Id) in E_Entry
5427 | E_Entry_Family
5428 | E_Function
5429 | E_Procedure
5430 and then Ekind (Scope (Spec_Id)) = E_Protected_Type
5431 then
5432 Spec_Decl := Declaration_Node (Scope (Spec_Id));
5433 end if;
5435 if Nkind (Parent (Spec_Decl)) /= N_Package_Specification then
5436 Error_Pragma
5437 (Fix_Msg (Spec_Id, "pragma % must apply to the body of "
5438 & "subprogram declared in a package specification"));
5439 end if;
5441 -- If we get here, then the pragma is legal
5443 Legal := True;
5445 -- A pragma that applies to a Ghost entity becomes Ghost for the
5446 -- purposes of legality checks and removal of ignored Ghost code.
5448 Mark_Ghost_Pragma (N, Spec_Id);
5450 if Pname in Name_Refined_Depends | Name_Refined_Global then
5451 Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
5452 end if;
5453 end Analyze_Refined_Depends_Global_Post;
5455 ----------------------------------
5456 -- Analyze_Unmodified_Or_Unused --
5457 ----------------------------------
5459 procedure Analyze_Unmodified_Or_Unused (Is_Unused : Boolean := False) is
5460 Arg : Node_Id;
5461 Arg_Expr : Node_Id;
5462 Arg_Id : Entity_Id;
5464 Ghost_Error_Posted : Boolean := False;
5465 -- Flag set when an error concerning the illegal mix of Ghost and
5466 -- non-Ghost variables is emitted.
5468 Ghost_Id : Entity_Id := Empty;
5469 -- The entity of the first Ghost variable encountered while
5470 -- processing the arguments of the pragma.
5472 begin
5473 GNAT_Pragma;
5474 Check_At_Least_N_Arguments (1);
5476 -- Loop through arguments
5478 Arg := Arg1;
5479 while Present (Arg) loop
5480 Check_No_Identifier (Arg);
5482 -- Note: the analyze call done by Check_Arg_Is_Local_Name will
5483 -- in fact generate reference, so that the entity will have a
5484 -- reference, which will inhibit any warnings about it not
5485 -- being referenced, and also properly show up in the ali file
5486 -- as a reference. But this reference is recorded before the
5487 -- Has_Pragma_Unreferenced flag is set, so that no warning is
5488 -- generated for this reference.
5490 Check_Arg_Is_Local_Name (Arg);
5491 Arg_Expr := Get_Pragma_Arg (Arg);
5493 if Is_Entity_Name (Arg_Expr) then
5494 Arg_Id := Entity (Arg_Expr);
5496 -- Skip processing the argument if already flagged
5498 if Is_Assignable (Arg_Id)
5499 and then not Has_Pragma_Unmodified (Arg_Id)
5500 and then not Has_Pragma_Unused (Arg_Id)
5501 then
5502 Set_Has_Pragma_Unmodified (Arg_Id);
5504 if Is_Unused then
5505 Set_Has_Pragma_Unused (Arg_Id);
5506 end if;
5508 -- A pragma that applies to a Ghost entity becomes Ghost for
5509 -- the purposes of legality checks and removal of ignored
5510 -- Ghost code.
5512 Mark_Ghost_Pragma (N, Arg_Id);
5514 -- Capture the entity of the first Ghost variable being
5515 -- processed for error detection purposes.
5517 if Is_Ghost_Entity (Arg_Id) then
5518 if No (Ghost_Id) then
5519 Ghost_Id := Arg_Id;
5520 end if;
5522 -- Otherwise the variable is non-Ghost. It is illegal to mix
5523 -- references to Ghost and non-Ghost entities
5524 -- (SPARK RM 6.9).
5526 elsif Present (Ghost_Id)
5527 and then not Ghost_Error_Posted
5528 then
5529 Ghost_Error_Posted := True;
5531 Error_Msg_Name_1 := Pname;
5532 Error_Msg_N
5533 ("pragma % cannot mention ghost and non-ghost "
5534 & "variables", N);
5536 Error_Msg_Sloc := Sloc (Ghost_Id);
5537 Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
5539 Error_Msg_Sloc := Sloc (Arg_Id);
5540 Error_Msg_NE ("\& # declared as non-ghost", N, Arg_Id);
5541 end if;
5543 -- Warn if already flagged as Unused or Unmodified
5545 elsif Has_Pragma_Unmodified (Arg_Id) then
5546 if Has_Pragma_Unused (Arg_Id) then
5547 Error_Msg_NE
5548 (Fix_Error ("??pragma Unused already given for &!"),
5549 Arg_Expr, Arg_Id);
5550 else
5551 Error_Msg_NE
5552 (Fix_Error ("??pragma Unmodified already given for &!"),
5553 Arg_Expr, Arg_Id);
5554 end if;
5556 -- Otherwise the pragma referenced an illegal entity
5558 else
5559 Error_Pragma_Arg
5560 ("pragma% can only be applied to a variable", Arg_Expr);
5561 end if;
5562 end if;
5564 Next (Arg);
5565 end loop;
5566 end Analyze_Unmodified_Or_Unused;
5568 ------------------------------------
5569 -- Analyze_Unreferenced_Or_Unused --
5570 ------------------------------------
5572 procedure Analyze_Unreferenced_Or_Unused
5573 (Is_Unused : Boolean := False)
5575 Arg : Node_Id;
5576 Arg_Expr : Node_Id;
5577 Arg_Id : Entity_Id;
5578 Citem : Node_Id;
5580 Ghost_Error_Posted : Boolean := False;
5581 -- Flag set when an error concerning the illegal mix of Ghost and
5582 -- non-Ghost names is emitted.
5584 Ghost_Id : Entity_Id := Empty;
5585 -- The entity of the first Ghost name encountered while processing
5586 -- the arguments of the pragma.
5588 begin
5589 GNAT_Pragma;
5590 Check_At_Least_N_Arguments (1);
5592 -- Check case of appearing within context clause
5594 if not Is_Unused and then Is_In_Context_Clause then
5596 -- The arguments must all be units mentioned in a with clause in
5597 -- the same context clause. Note that Par.Prag already checked
5598 -- that the arguments are either identifiers or selected
5599 -- components.
5601 Arg := Arg1;
5602 while Present (Arg) loop
5603 Citem := First (List_Containing (N));
5604 while Citem /= N loop
5605 Arg_Expr := Get_Pragma_Arg (Arg);
5607 if Nkind (Citem) = N_With_Clause
5608 and then Same_Name (Name (Citem), Arg_Expr)
5609 then
5610 Set_Has_Pragma_Unreferenced
5611 (Cunit_Entity
5612 (Get_Source_Unit
5613 (Library_Unit (Citem))));
5614 Set_Elab_Unit_Name (Arg_Expr, Name (Citem));
5615 exit;
5616 end if;
5618 Next (Citem);
5619 end loop;
5621 if Citem = N then
5622 Error_Pragma_Arg
5623 ("argument of pragma% is not withed unit", Arg);
5624 end if;
5626 Next (Arg);
5627 end loop;
5629 -- Case of not in list of context items
5631 else
5632 Arg := Arg1;
5633 while Present (Arg) loop
5634 Check_No_Identifier (Arg);
5636 -- Note: the analyze call done by Check_Arg_Is_Local_Name will
5637 -- in fact generate reference, so that the entity will have a
5638 -- reference, which will inhibit any warnings about it not
5639 -- being referenced, and also properly show up in the ali file
5640 -- as a reference. But this reference is recorded before the
5641 -- Has_Pragma_Unreferenced flag is set, so that no warning is
5642 -- generated for this reference.
5644 Check_Arg_Is_Local_Name (Arg);
5645 Arg_Expr := Get_Pragma_Arg (Arg);
5647 if Is_Entity_Name (Arg_Expr) then
5648 Arg_Id := Entity (Arg_Expr);
5650 -- Warn if already flagged as Unused or Unreferenced and
5651 -- skip processing the argument.
5653 if Has_Pragma_Unreferenced (Arg_Id) then
5654 if Has_Pragma_Unused (Arg_Id) then
5655 Error_Msg_NE
5656 (Fix_Error ("??pragma Unused already given for &!"),
5657 Arg_Expr, Arg_Id);
5658 else
5659 Error_Msg_NE
5660 (Fix_Error
5661 ("??pragma Unreferenced already given for &!"),
5662 Arg_Expr, Arg_Id);
5663 end if;
5665 -- Apply Unreferenced to the entity
5667 else
5668 -- If the entity is overloaded, the pragma applies to the
5669 -- most recent overloading, as documented. In this case,
5670 -- name resolution does not generate a reference, so it
5671 -- must be done here explicitly.
5673 if Is_Overloaded (Arg_Expr) then
5674 Generate_Reference (Arg_Id, N);
5675 end if;
5677 Set_Has_Pragma_Unreferenced (Arg_Id);
5679 if Is_Unused then
5680 Set_Has_Pragma_Unused (Arg_Id);
5681 end if;
5683 -- A pragma that applies to a Ghost entity becomes Ghost
5684 -- for the purposes of legality checks and removal of
5685 -- ignored Ghost code.
5687 Mark_Ghost_Pragma (N, Arg_Id);
5689 -- Capture the entity of the first Ghost name being
5690 -- processed for error detection purposes.
5692 if Is_Ghost_Entity (Arg_Id) then
5693 if No (Ghost_Id) then
5694 Ghost_Id := Arg_Id;
5695 end if;
5697 -- Otherwise the name is non-Ghost. It is illegal to mix
5698 -- references to Ghost and non-Ghost entities
5699 -- (SPARK RM 6.9).
5701 elsif Present (Ghost_Id)
5702 and then not Ghost_Error_Posted
5703 then
5704 Ghost_Error_Posted := True;
5706 Error_Msg_Name_1 := Pname;
5707 Error_Msg_N
5708 ("pragma % cannot mention ghost and non-ghost "
5709 & "names", N);
5711 Error_Msg_Sloc := Sloc (Ghost_Id);
5712 Error_Msg_NE
5713 ("\& # declared as ghost", N, Ghost_Id);
5715 Error_Msg_Sloc := Sloc (Arg_Id);
5716 Error_Msg_NE
5717 ("\& # declared as non-ghost", N, Arg_Id);
5718 end if;
5719 end if;
5720 end if;
5722 Next (Arg);
5723 end loop;
5724 end if;
5725 end Analyze_Unreferenced_Or_Unused;
5727 --------------------------
5728 -- Check_Ada_83_Warning --
5729 --------------------------
5731 procedure Check_Ada_83_Warning is
5732 begin
5733 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
5734 Error_Msg_N ("(Ada 83) pragma& is non-standard??", N);
5735 end if;
5736 end Check_Ada_83_Warning;
5738 ---------------------
5739 -- Check_Arg_Count --
5740 ---------------------
5742 procedure Check_Arg_Count (Required : Nat) is
5743 begin
5744 if Arg_Count /= Required then
5745 Error_Pragma ("wrong number of arguments for pragma%");
5746 end if;
5747 end Check_Arg_Count;
5749 --------------------------------
5750 -- Check_Arg_Is_External_Name --
5751 --------------------------------
5753 procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
5754 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5756 begin
5757 if Nkind (Argx) = N_Identifier then
5758 return;
5760 else
5761 Analyze_And_Resolve (Argx, Standard_String);
5763 if Is_OK_Static_Expression (Argx) then
5764 return;
5766 elsif Etype (Argx) = Any_Type then
5767 raise Pragma_Exit;
5769 -- An interesting special case, if we have a string literal and
5770 -- we are in Ada 83 mode, then we allow it even though it will
5771 -- not be flagged as static. This allows expected Ada 83 mode
5772 -- use of external names which are string literals, even though
5773 -- technically these are not static in Ada 83.
5775 elsif Ada_Version = Ada_83
5776 and then Nkind (Argx) = N_String_Literal
5777 then
5778 return;
5780 -- Here we have a real error (non-static expression)
5782 else
5783 Error_Msg_Name_1 := Pname;
5784 Flag_Non_Static_Expr
5785 (Fix_Error ("argument for pragma% must be a identifier or "
5786 & "static string expression!"), Argx);
5788 raise Pragma_Exit;
5789 end if;
5790 end if;
5791 end Check_Arg_Is_External_Name;
5793 -----------------------------
5794 -- Check_Arg_Is_Identifier --
5795 -----------------------------
5797 procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
5798 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5799 begin
5800 if Nkind (Argx) /= N_Identifier then
5801 Error_Pragma_Arg ("argument for pragma% must be identifier", Argx);
5802 end if;
5803 end Check_Arg_Is_Identifier;
5805 ----------------------------------
5806 -- Check_Arg_Is_Integer_Literal --
5807 ----------------------------------
5809 procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
5810 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5811 begin
5812 if Nkind (Argx) /= N_Integer_Literal then
5813 Error_Pragma_Arg
5814 ("argument for pragma% must be integer literal", Argx);
5815 end if;
5816 end Check_Arg_Is_Integer_Literal;
5818 -------------------------------------------
5819 -- Check_Arg_Is_Library_Level_Local_Name --
5820 -------------------------------------------
5822 -- LOCAL_NAME ::=
5823 -- DIRECT_NAME
5824 -- | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
5825 -- | library_unit_NAME
5827 procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
5828 begin
5829 Check_Arg_Is_Local_Name (Arg);
5831 -- If it came from an aspect, we want to give the error just as if it
5832 -- came from source.
5834 if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
5835 and then (Comes_From_Source (N)
5836 or else Present (Corresponding_Aspect (Parent (Arg))))
5837 then
5838 Error_Pragma_Arg
5839 ("argument for pragma% must be library level entity", Arg);
5840 end if;
5841 end Check_Arg_Is_Library_Level_Local_Name;
5843 -----------------------------
5844 -- Check_Arg_Is_Local_Name --
5845 -----------------------------
5847 -- LOCAL_NAME ::=
5848 -- DIRECT_NAME
5849 -- | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
5850 -- | library_unit_NAME
5852 procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
5853 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5855 begin
5856 -- If this pragma came from an aspect specification, we don't want to
5857 -- check for this error, because that would cause spurious errors, in
5858 -- case a type is frozen in a scope more nested than the type. The
5859 -- aspect itself of course can't be anywhere but on the declaration
5860 -- itself.
5862 if Nkind (Arg) = N_Pragma_Argument_Association then
5863 if From_Aspect_Specification (Parent (Arg)) then
5864 return;
5865 end if;
5867 -- Arg is the Expression of an N_Pragma_Argument_Association
5869 else
5870 if From_Aspect_Specification (Parent (Parent (Arg))) then
5871 return;
5872 end if;
5873 end if;
5875 Analyze (Argx);
5877 if Nkind (Argx) not in N_Direct_Name
5878 and then (Nkind (Argx) /= N_Attribute_Reference
5879 or else Present (Expressions (Argx))
5880 or else Nkind (Prefix (Argx)) /= N_Identifier)
5881 and then (not Is_Entity_Name (Argx)
5882 or else not Is_Compilation_Unit (Entity (Argx)))
5883 then
5884 Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
5885 end if;
5887 -- No further check required if not an entity name
5889 if not Is_Entity_Name (Argx) then
5890 null;
5892 else
5893 declare
5894 OK : Boolean;
5895 Ent : constant Entity_Id := Entity (Argx);
5896 Scop : constant Entity_Id := Scope (Ent);
5898 begin
5899 -- Case of a pragma applied to a compilation unit: pragma must
5900 -- occur immediately after the program unit in the compilation.
5902 if Is_Compilation_Unit (Ent) then
5903 declare
5904 Decl : constant Node_Id := Unit_Declaration_Node (Ent);
5906 begin
5907 -- Case of pragma placed immediately after spec
5909 if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
5910 OK := True;
5912 -- Case of pragma placed immediately after body
5914 elsif Nkind (Decl) = N_Subprogram_Declaration
5915 and then Present (Corresponding_Body (Decl))
5916 then
5917 OK := Parent (N) =
5918 Aux_Decls_Node
5919 (Parent (Unit_Declaration_Node
5920 (Corresponding_Body (Decl))));
5922 -- All other cases are illegal
5924 else
5925 OK := False;
5926 end if;
5927 end;
5929 -- Special restricted placement rule from 10.2.1(11.8/2)
5931 elsif Is_Generic_Formal (Ent)
5932 and then Prag_Id = Pragma_Preelaborable_Initialization
5933 then
5934 OK := List_Containing (N) =
5935 Generic_Formal_Declarations
5936 (Unit_Declaration_Node (Scop));
5938 -- If this is an aspect applied to a subprogram body, the
5939 -- pragma is inserted in its declarative part.
5941 elsif From_Aspect_Specification (N)
5942 and then Ent = Current_Scope
5943 and then
5944 Nkind (Unit_Declaration_Node (Ent)) = N_Subprogram_Body
5945 then
5946 OK := True;
5948 -- If the aspect is a predicate (possibly others ???) and the
5949 -- context is a record type, this is a discriminant expression
5950 -- within a type declaration, that freezes the predicated
5951 -- subtype.
5953 elsif From_Aspect_Specification (N)
5954 and then Prag_Id = Pragma_Predicate
5955 and then Ekind (Current_Scope) = E_Record_Type
5956 and then Scop = Scope (Current_Scope)
5957 then
5958 OK := True;
5960 -- Special case for postconditions wrappers
5962 elsif Ekind (Scop) in Subprogram_Kind
5963 and then Present (Wrapped_Statements (Scop))
5964 and then Wrapped_Statements (Scop) = Current_Scope
5965 then
5966 OK := True;
5968 -- Default case, just check that the pragma occurs in the scope
5969 -- of the entity denoted by the name.
5971 else
5972 OK := Current_Scope = Scop;
5973 end if;
5975 if not OK then
5976 Error_Pragma_Arg
5977 ("pragma% argument must be in same declarative part", Arg);
5978 end if;
5979 end;
5980 end if;
5981 end Check_Arg_Is_Local_Name;
5983 ---------------------------------
5984 -- Check_Arg_Is_Locking_Policy --
5985 ---------------------------------
5987 procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
5988 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5990 begin
5991 Check_Arg_Is_Identifier (Argx);
5993 if not Is_Locking_Policy_Name (Chars (Argx)) then
5994 Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
5995 end if;
5996 end Check_Arg_Is_Locking_Policy;
5998 -----------------------------------------------
5999 -- Check_Arg_Is_Partition_Elaboration_Policy --
6000 -----------------------------------------------
6002 procedure Check_Arg_Is_Partition_Elaboration_Policy (Arg : Node_Id) is
6003 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6005 begin
6006 Check_Arg_Is_Identifier (Argx);
6008 if not Is_Partition_Elaboration_Policy_Name (Chars (Argx)) then
6009 Error_Pragma_Arg
6010 ("& is not a valid partition elaboration policy name", Argx);
6011 end if;
6012 end Check_Arg_Is_Partition_Elaboration_Policy;
6014 -------------------------
6015 -- Check_Arg_Is_One_Of --
6016 -------------------------
6018 procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
6019 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6021 begin
6022 Check_Arg_Is_Identifier (Argx);
6024 if Chars (Argx) not in N1 | N2 then
6025 Error_Msg_Name_2 := N1;
6026 Error_Msg_Name_3 := N2;
6027 Error_Pragma_Arg ("argument for pragma% must be% or%", Argx);
6028 end if;
6029 end Check_Arg_Is_One_Of;
6031 procedure Check_Arg_Is_One_Of
6032 (Arg : Node_Id;
6033 N1, N2, N3 : Name_Id)
6035 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6037 begin
6038 Check_Arg_Is_Identifier (Argx);
6040 if Chars (Argx) not in N1 | N2 | N3 then
6041 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
6042 end if;
6043 end Check_Arg_Is_One_Of;
6045 procedure Check_Arg_Is_One_Of
6046 (Arg : Node_Id;
6047 N1, N2, N3, N4 : Name_Id)
6049 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6051 begin
6052 Check_Arg_Is_Identifier (Argx);
6054 if Chars (Argx) not in N1 | N2 | N3 | N4 then
6055 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
6056 end if;
6057 end Check_Arg_Is_One_Of;
6059 procedure Check_Arg_Is_One_Of
6060 (Arg : Node_Id;
6061 N1, N2, N3, N4, N5 : Name_Id)
6063 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6065 begin
6066 Check_Arg_Is_Identifier (Argx);
6068 if Chars (Argx) not in N1 | N2 | N3 | N4 | N5 then
6069 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
6070 end if;
6071 end Check_Arg_Is_One_Of;
6073 ---------------------------------
6074 -- Check_Arg_Is_Queuing_Policy --
6075 ---------------------------------
6077 procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
6078 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6080 begin
6081 Check_Arg_Is_Identifier (Argx);
6083 if not Is_Queuing_Policy_Name (Chars (Argx)) then
6084 Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
6085 end if;
6086 end Check_Arg_Is_Queuing_Policy;
6088 ---------------------------------------
6089 -- Check_Arg_Is_OK_Static_Expression --
6090 ---------------------------------------
6092 procedure Check_Arg_Is_OK_Static_Expression
6093 (Arg : Node_Id;
6094 Typ : Entity_Id := Empty)
6096 begin
6097 Check_Expr_Is_OK_Static_Expression (Get_Pragma_Arg (Arg), Typ);
6098 end Check_Arg_Is_OK_Static_Expression;
6100 ------------------------------------------
6101 -- Check_Arg_Is_Task_Dispatching_Policy --
6102 ------------------------------------------
6104 procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
6105 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6107 begin
6108 Check_Arg_Is_Identifier (Argx);
6110 if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
6111 Error_Pragma_Arg
6112 ("& is not an allowed task dispatching policy name", Argx);
6113 end if;
6114 end Check_Arg_Is_Task_Dispatching_Policy;
6116 ---------------------
6117 -- Check_Arg_Order --
6118 ---------------------
6120 procedure Check_Arg_Order (Names : Name_List) is
6121 Arg : Node_Id;
6123 Highest_So_Far : Natural := 0;
6124 -- Highest index in Names seen do far
6126 begin
6127 Arg := Arg1;
6128 for J in 1 .. Arg_Count loop
6129 if Chars (Arg) /= No_Name then
6130 for K in Names'Range loop
6131 if Chars (Arg) = Names (K) then
6132 if K < Highest_So_Far then
6133 Error_Msg_Name_1 := Pname;
6134 Error_Msg_N
6135 ("parameters out of order for pragma%", Arg);
6136 Error_Msg_Name_1 := Names (K);
6137 Error_Msg_Name_2 := Names (Highest_So_Far);
6138 Error_Msg_N ("\% must appear before %", Arg);
6139 raise Pragma_Exit;
6141 else
6142 Highest_So_Far := K;
6143 end if;
6144 end if;
6145 end loop;
6146 end if;
6148 Arg := Next (Arg);
6149 end loop;
6150 end Check_Arg_Order;
6152 --------------------------------
6153 -- Check_At_Least_N_Arguments --
6154 --------------------------------
6156 procedure Check_At_Least_N_Arguments (N : Nat) is
6157 begin
6158 if Arg_Count < N then
6159 Error_Pragma ("too few arguments for pragma%");
6160 end if;
6161 end Check_At_Least_N_Arguments;
6163 -------------------------------
6164 -- Check_At_Most_N_Arguments --
6165 -------------------------------
6167 procedure Check_At_Most_N_Arguments (N : Nat) is
6168 Arg : Node_Id;
6169 begin
6170 if Arg_Count > N then
6171 Arg := Arg1;
6172 for J in 1 .. N loop
6173 Next (Arg);
6174 Error_Pragma_Arg ("too many arguments for pragma%", Arg);
6175 end loop;
6176 end if;
6177 end Check_At_Most_N_Arguments;
6179 ---------------------
6180 -- Check_Component --
6181 ---------------------
6183 procedure Check_Component
6184 (Comp : Node_Id;
6185 UU_Typ : Entity_Id;
6186 In_Variant_Part : Boolean := False)
6188 Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
6189 Sindic : constant Node_Id :=
6190 Subtype_Indication (Component_Definition (Comp));
6191 Typ : constant Entity_Id := Etype (Comp_Id);
6193 begin
6194 -- Ada 2005 (AI-216): If a component subtype is subject to a per-
6195 -- object constraint, then the component type shall be an Unchecked_
6196 -- Union.
6198 if Nkind (Sindic) = N_Subtype_Indication
6199 and then Has_Per_Object_Constraint (Comp_Id)
6200 and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
6201 then
6202 Error_Msg_N
6203 ("component subtype subject to per-object constraint "
6204 & "must be an Unchecked_Union", Comp);
6206 -- Ada 2012 (AI05-0026): For an unchecked union type declared within
6207 -- the body of a generic unit, or within the body of any of its
6208 -- descendant library units, no part of the type of a component
6209 -- declared in a variant_part of the unchecked union type shall be of
6210 -- a formal private type or formal private extension declared within
6211 -- the formal part of the generic unit.
6213 elsif Ada_Version >= Ada_2012
6214 and then In_Generic_Body (UU_Typ)
6215 and then In_Variant_Part
6216 and then Is_Private_Type (Typ)
6217 and then Is_Generic_Type (Typ)
6218 then
6219 Error_Msg_N
6220 ("component of unchecked union cannot be of generic type", Comp);
6222 elsif Needs_Finalization (Typ) then
6223 Error_Msg_N
6224 ("component of unchecked union cannot be controlled", Comp);
6226 elsif Has_Task (Typ) then
6227 Error_Msg_N
6228 ("component of unchecked union cannot have tasks", Comp);
6229 end if;
6230 end Check_Component;
6232 ----------------------------
6233 -- Check_Duplicate_Pragma --
6234 ----------------------------
6236 procedure Check_Duplicate_Pragma (E : Entity_Id) is
6237 Id : Entity_Id := E;
6238 P : Node_Id;
6240 begin
6241 -- Nothing to do if this pragma comes from an aspect specification,
6242 -- since we could not be duplicating a pragma, and we dealt with the
6243 -- case of duplicated aspects in Analyze_Aspect_Specifications.
6245 if From_Aspect_Specification (N) then
6246 return;
6247 end if;
6249 -- Otherwise current pragma may duplicate previous pragma or a
6250 -- previously given aspect specification or attribute definition
6251 -- clause for the same pragma.
6253 P := Get_Rep_Item (E, Pragma_Name (N), Check_Parents => False);
6255 if Present (P) then
6257 -- If the entity is a type, then we have to make sure that the
6258 -- ostensible duplicate is not for a parent type from which this
6259 -- type is derived.
6261 if Is_Type (E) then
6262 if Nkind (P) = N_Pragma then
6263 declare
6264 Args : constant List_Id :=
6265 Pragma_Argument_Associations (P);
6266 begin
6267 if Present (Args)
6268 and then Is_Entity_Name (Expression (First (Args)))
6269 and then Is_Type (Entity (Expression (First (Args))))
6270 and then Entity (Expression (First (Args))) /= E
6271 then
6272 return;
6273 end if;
6274 end;
6276 elsif Nkind (P) = N_Aspect_Specification
6277 and then Is_Type (Entity (P))
6278 and then Entity (P) /= E
6279 then
6280 return;
6281 end if;
6282 end if;
6284 -- Here we have a definite duplicate
6286 Error_Msg_Name_1 := Pragma_Name (N);
6287 Error_Msg_Sloc := Sloc (P);
6289 -- For a single protected or a single task object, the error is
6290 -- issued on the original entity.
6292 if Ekind (Id) in E_Task_Type | E_Protected_Type then
6293 Id := Defining_Identifier (Original_Node (Parent (Id)));
6294 end if;
6296 if Nkind (P) = N_Aspect_Specification
6297 or else From_Aspect_Specification (P)
6298 then
6299 Error_Msg_NE ("aspect% for & previously given#", N, Id);
6300 else
6301 -- If -gnatwr is set, warn in case of a duplicate pragma
6302 -- [No_]Inline which is suspicious but not an error, generate
6303 -- an error for other pragmas.
6305 if Pragma_Name (N) in Name_Inline | Name_No_Inline then
6306 if Warn_On_Redundant_Constructs then
6307 Error_Msg_NE
6308 ("?r?pragma% for & duplicates pragma#", N, Id);
6309 end if;
6310 else
6311 Error_Msg_NE ("pragma% for & duplicates pragma#", N, Id);
6312 end if;
6313 end if;
6315 raise Pragma_Exit;
6316 end if;
6317 end Check_Duplicate_Pragma;
6319 ----------------------------------
6320 -- Check_Duplicated_Export_Name --
6321 ----------------------------------
6323 procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
6324 String_Val : constant String_Id := Strval (Nam);
6326 begin
6327 -- We are only interested in the export case, and in the case of
6328 -- generics, it is the instance, not the template, that is the
6329 -- problem (the template will generate a warning in any case).
6331 if not Inside_A_Generic
6332 and then (Prag_Id = Pragma_Export
6333 or else
6334 Prag_Id = Pragma_Export_Procedure
6335 or else
6336 Prag_Id = Pragma_Export_Valued_Procedure
6337 or else
6338 Prag_Id = Pragma_Export_Function)
6339 then
6340 for J in Externals.First .. Externals.Last loop
6341 if String_Equal (String_Val, Strval (Externals.Table (J))) then
6342 Error_Msg_Sloc := Sloc (Externals.Table (J));
6343 Error_Msg_N ("external name duplicates name given#", Nam);
6344 exit;
6345 end if;
6346 end loop;
6348 Externals.Append (Nam);
6349 end if;
6350 end Check_Duplicated_Export_Name;
6352 ----------------------------------------
6353 -- Check_Expr_Is_OK_Static_Expression --
6354 ----------------------------------------
6356 procedure Check_Expr_Is_OK_Static_Expression
6357 (Expr : Node_Id;
6358 Typ : Entity_Id := Empty)
6360 begin
6361 if Present (Typ) then
6362 Analyze_And_Resolve (Expr, Typ);
6363 else
6364 Analyze_And_Resolve (Expr);
6365 end if;
6367 -- An expression cannot be considered static if its resolution failed
6368 -- or if it's erroneous. Stop the analysis of the related pragma.
6370 if Etype (Expr) = Any_Type or else Error_Posted (Expr) then
6371 raise Pragma_Exit;
6373 elsif Is_OK_Static_Expression (Expr) then
6374 return;
6376 -- An interesting special case, if we have a string literal and we
6377 -- are in Ada 83 mode, then we allow it even though it will not be
6378 -- flagged as static. This allows the use of Ada 95 pragmas like
6379 -- Import in Ada 83 mode. They will of course be flagged with
6380 -- warnings as usual, but will not cause errors.
6382 elsif Ada_Version = Ada_83
6383 and then Nkind (Expr) = N_String_Literal
6384 then
6385 return;
6387 -- Finally, we have a real error
6389 else
6390 Error_Msg_Name_1 := Pname;
6391 Flag_Non_Static_Expr
6392 (Fix_Error ("argument for pragma% must be a static expression!"),
6393 Expr);
6394 raise Pragma_Exit;
6395 end if;
6396 end Check_Expr_Is_OK_Static_Expression;
6398 -------------------------
6399 -- Check_First_Subtype --
6400 -------------------------
6402 procedure Check_First_Subtype (Arg : Node_Id) is
6403 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
6404 Ent : constant Entity_Id := Entity (Argx);
6406 begin
6407 if Is_First_Subtype (Ent) then
6408 null;
6410 elsif Is_Type (Ent) then
6411 Error_Pragma_Arg
6412 ("pragma% cannot apply to subtype", Argx);
6414 elsif Is_Object (Ent) then
6415 Error_Pragma_Arg
6416 ("pragma% cannot apply to object, requires a type", Argx);
6418 else
6419 Error_Pragma_Arg
6420 ("pragma% cannot apply to&, requires a type", Argx);
6421 end if;
6422 end Check_First_Subtype;
6424 ----------------------
6425 -- Check_Identifier --
6426 ----------------------
6428 procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
6429 begin
6430 if Present (Arg)
6431 and then Nkind (Arg) = N_Pragma_Argument_Association
6432 then
6433 if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
6434 Error_Msg_Name_1 := Pname;
6435 Error_Msg_Name_2 := Id;
6436 Error_Msg_N ("pragma% argument expects identifier%", Arg);
6437 raise Pragma_Exit;
6438 end if;
6439 end if;
6440 end Check_Identifier;
6442 --------------------------------
6443 -- Check_Identifier_Is_One_Of --
6444 --------------------------------
6446 procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
6447 begin
6448 if Present (Arg)
6449 and then Nkind (Arg) = N_Pragma_Argument_Association
6450 then
6451 if Chars (Arg) = No_Name then
6452 Error_Msg_Name_1 := Pname;
6453 Error_Msg_N ("pragma% argument expects an identifier", Arg);
6454 raise Pragma_Exit;
6456 elsif Chars (Arg) /= N1
6457 and then Chars (Arg) /= N2
6458 then
6459 Error_Msg_Name_1 := Pname;
6460 Error_Msg_N ("invalid identifier for pragma% argument", Arg);
6461 raise Pragma_Exit;
6462 end if;
6463 end if;
6464 end Check_Identifier_Is_One_Of;
6466 ---------------------------
6467 -- Check_In_Main_Program --
6468 ---------------------------
6470 procedure Check_In_Main_Program is
6471 P : constant Node_Id := Parent (N);
6473 begin
6474 -- Must be in subprogram body
6476 if Nkind (P) /= N_Subprogram_Body then
6477 Error_Pragma ("% pragma allowed only in subprogram");
6479 -- Otherwise warn if obviously not main program
6481 elsif Present (Parameter_Specifications (Specification (P)))
6482 or else not Is_Compilation_Unit (Defining_Entity (P))
6483 then
6484 Error_Msg_Name_1 := Pname;
6485 Error_Msg_N
6486 ("??pragma% is only effective in main program", N);
6487 end if;
6488 end Check_In_Main_Program;
6490 ---------------------------------------
6491 -- Check_Interrupt_Or_Attach_Handler --
6492 ---------------------------------------
6494 procedure Check_Interrupt_Or_Attach_Handler is
6495 Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
6496 Handler_Proc, Proc_Scope : Entity_Id;
6498 begin
6499 Analyze (Arg1_X);
6501 if Prag_Id = Pragma_Interrupt_Handler then
6502 Check_Restriction (No_Dynamic_Attachment, N);
6503 end if;
6505 Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
6506 Proc_Scope := Scope (Handler_Proc);
6508 if Ekind (Proc_Scope) /= E_Protected_Type then
6509 Error_Pragma_Arg
6510 ("argument of pragma% must be protected procedure", Arg1);
6511 end if;
6513 -- For pragma case (as opposed to access case), check placement.
6514 -- We don't need to do that for aspects, because we have the
6515 -- check that they aspect applies an appropriate procedure.
6517 if not From_Aspect_Specification (N)
6518 and then Parent (N) /= Protected_Definition (Parent (Proc_Scope))
6519 then
6520 Error_Pragma ("pragma% must be in protected definition");
6521 end if;
6523 if not Is_Library_Level_Entity (Proc_Scope) then
6524 Error_Pragma_Arg
6525 ("argument for pragma% must be library level entity", Arg1);
6526 end if;
6528 -- AI05-0033: A pragma cannot appear within a generic body, because
6529 -- instance can be in a nested scope. The check that protected type
6530 -- is itself a library-level declaration is done elsewhere.
6532 -- Note: we omit this check in Relaxed_RM_Semantics mode to properly
6533 -- handle code prior to AI-0033. Analysis tools typically are not
6534 -- interested in this pragma in any case, so no need to worry too
6535 -- much about its placement.
6537 if Inside_A_Generic then
6538 if Ekind (Scope (Current_Scope)) = E_Generic_Package
6539 and then In_Package_Body (Scope (Current_Scope))
6540 and then not Relaxed_RM_Semantics
6541 then
6542 Error_Pragma ("pragma% cannot be used inside a generic");
6543 end if;
6544 end if;
6545 end Check_Interrupt_Or_Attach_Handler;
6547 ---------------------------------
6548 -- Check_Loop_Pragma_Placement --
6549 ---------------------------------
6551 procedure Check_Loop_Pragma_Placement is
6552 procedure Check_Loop_Pragma_Grouping (Loop_Stmt : Node_Id);
6553 -- Verify whether the current pragma is properly grouped with other
6554 -- pragma Loop_Invariant and/or Loop_Variant. Node Loop_Stmt is the
6555 -- related loop where the pragma appears.
6557 function Is_Loop_Pragma (Stmt : Node_Id) return Boolean;
6558 -- Determine whether an arbitrary statement Stmt denotes pragma
6559 -- Loop_Invariant or Loop_Variant.
6561 procedure Placement_Error (Constr : Node_Id);
6562 pragma No_Return (Placement_Error);
6563 -- Node Constr denotes the last loop restricted construct before we
6564 -- encountered an illegal relation between enclosing constructs. Emit
6565 -- an error depending on what Constr was.
6567 --------------------------------
6568 -- Check_Loop_Pragma_Grouping --
6569 --------------------------------
6571 procedure Check_Loop_Pragma_Grouping (Loop_Stmt : Node_Id) is
6572 function Check_Grouping (L : List_Id) return Boolean;
6573 -- Find the first group of pragmas in list L and if successful,
6574 -- ensure that the current pragma is part of that group. The
6575 -- routine returns True once such a check is performed to
6576 -- stop the analysis.
6578 procedure Grouping_Error (Prag : Node_Id);
6579 pragma No_Return (Grouping_Error);
6580 -- Emit an error concerning the current pragma indicating that it
6581 -- should be placed after pragma Prag.
6583 --------------------
6584 -- Check_Grouping --
6585 --------------------
6587 function Check_Grouping (L : List_Id) return Boolean is
6588 HSS : Node_Id;
6589 Stmt : Node_Id;
6590 Prag : Node_Id := Empty; -- init to avoid warning
6592 begin
6593 -- Inspect the list of declarations or statements looking for
6594 -- the first grouping of pragmas:
6596 -- loop
6597 -- pragma Loop_Invariant ...;
6598 -- pragma Loop_Variant ...;
6599 -- . . . -- (1)
6600 -- pragma Loop_Variant ...; -- current pragma
6602 -- If the current pragma is not in the grouping, then it must
6603 -- either appear in a different declarative or statement list
6604 -- or the construct at (1) is separating the pragma from the
6605 -- grouping.
6607 Stmt := First (L);
6608 while Present (Stmt) loop
6610 -- First pragma of the first topmost grouping has been found
6612 if Is_Loop_Pragma (Stmt) then
6614 -- The group and the current pragma are not in the same
6615 -- declarative or statement list.
6617 if not In_Same_List (Stmt, N) then
6618 Grouping_Error (Stmt);
6620 -- Try to reach the current pragma from the first pragma
6621 -- of the grouping while skipping other members:
6623 -- pragma Loop_Invariant ...; -- first pragma
6624 -- pragma Loop_Variant ...; -- member
6625 -- . . .
6626 -- pragma Loop_Variant ...; -- current pragma
6628 else
6629 while Present (Stmt) loop
6630 -- The current pragma is either the first pragma
6631 -- of the group or is a member of the group.
6632 -- Stop the search as the placement is legal.
6634 if Stmt = N then
6635 return True;
6637 -- Skip group members, but keep track of the
6638 -- last pragma in the group.
6640 elsif Is_Loop_Pragma (Stmt) then
6641 Prag := Stmt;
6643 -- Skip Annotate pragmas, typically used to justify
6644 -- unproved loop pragmas in GNATprove.
6646 elsif Nkind (Stmt) = N_Pragma
6647 and then Pragma_Name (Stmt) = Name_Annotate
6648 then
6649 null;
6651 -- Skip declarations and statements generated by
6652 -- the compiler during expansion. Note that some
6653 -- source statements (e.g. pragma Assert) may have
6654 -- been transformed so that they do not appear as
6655 -- coming from source anymore, so we instead look
6656 -- at their Original_Node.
6658 elsif not Comes_From_Source (Original_Node (Stmt))
6659 then
6660 null;
6662 -- A non-pragma is separating the group from the
6663 -- current pragma, the placement is illegal.
6665 else
6666 Grouping_Error (Prag);
6667 end if;
6669 Next (Stmt);
6670 end loop;
6672 -- If the traversal did not reach the current pragma,
6673 -- then the list must be malformed.
6675 raise Program_Error;
6676 end if;
6678 -- Pragmas Loop_Invariant and Loop_Variant may only appear
6679 -- inside a loop or a block housed inside a loop. Inspect
6680 -- the declarations and statements of the block as they may
6681 -- contain the first grouping. This case follows the one for
6682 -- loop pragmas, as block statements which originate in a
6683 -- loop pragma (and so Is_Loop_Pragma will return True on
6684 -- that block statement) should be treated in the previous
6685 -- case.
6687 elsif Nkind (Stmt) = N_Block_Statement then
6688 HSS := Handled_Statement_Sequence (Stmt);
6690 if Check_Grouping (Declarations (Stmt)) then
6691 return True;
6692 end if;
6694 if Present (HSS) then
6695 if Check_Grouping (Statements (HSS)) then
6696 return True;
6697 end if;
6698 end if;
6699 end if;
6701 Next (Stmt);
6702 end loop;
6704 return False;
6705 end Check_Grouping;
6707 --------------------
6708 -- Grouping_Error --
6709 --------------------
6711 procedure Grouping_Error (Prag : Node_Id) is
6712 begin
6713 Error_Msg_Sloc := Sloc (Prag);
6714 Error_Pragma ("pragma% must appear next to pragma#");
6715 end Grouping_Error;
6717 Ignore : Boolean;
6719 -- Start of processing for Check_Loop_Pragma_Grouping
6721 begin
6722 -- Inspect the statements of the loop or nested blocks housed
6723 -- within to determine whether the current pragma is part of the
6724 -- first topmost grouping of Loop_Invariant and Loop_Variant.
6726 Ignore := Check_Grouping (Statements (Loop_Stmt));
6727 end Check_Loop_Pragma_Grouping;
6729 --------------------
6730 -- Is_Loop_Pragma --
6731 --------------------
6733 function Is_Loop_Pragma (Stmt : Node_Id) return Boolean is
6734 Original_Stmt : constant Node_Id := Original_Node (Stmt);
6736 begin
6737 -- Inspect the original node as Loop_Invariant and Loop_Variant
6738 -- pragmas are rewritten to null when assertions are disabled.
6740 return Nkind (Original_Stmt) = N_Pragma
6741 and then Pragma_Name_Unmapped (Original_Stmt)
6742 in Name_Loop_Invariant | Name_Loop_Variant;
6743 end Is_Loop_Pragma;
6745 ---------------------
6746 -- Placement_Error --
6747 ---------------------
6749 procedure Placement_Error (Constr : Node_Id) is
6750 LA : constant String := " with Loop_Entry";
6752 begin
6753 if Prag_Id = Pragma_Assert then
6754 Error_Msg_String (1 .. LA'Length) := LA;
6755 Error_Msg_Strlen := LA'Length;
6756 else
6757 Error_Msg_Strlen := 0;
6758 end if;
6760 if Nkind (Constr) = N_Pragma then
6761 Error_Pragma
6762 ("pragma %~ must appear immediately within the statements "
6763 & "of a loop");
6764 else
6765 Error_Pragma_Arg
6766 ("block containing pragma %~ must appear immediately within "
6767 & "the statements of a loop", Constr);
6768 end if;
6769 end Placement_Error;
6771 -- Local declarations
6773 Prev : Node_Id;
6774 Stmt : Node_Id;
6776 -- Start of processing for Check_Loop_Pragma_Placement
6778 begin
6779 -- Check that pragma appears immediately within a loop statement,
6780 -- ignoring intervening block statements.
6782 Prev := N;
6783 Stmt := Parent (N);
6784 while Present (Stmt) loop
6786 -- The pragma or previous block must appear immediately within the
6787 -- current block's declarative or statement part.
6789 if Nkind (Stmt) = N_Block_Statement then
6790 if (No (Declarations (Stmt))
6791 or else List_Containing (Prev) /= Declarations (Stmt))
6792 and then
6793 List_Containing (Prev) /=
6794 Statements (Handled_Statement_Sequence (Stmt))
6795 then
6796 Placement_Error (Prev);
6798 -- Keep inspecting the parents because we are now within a
6799 -- chain of nested blocks.
6801 else
6802 Prev := Stmt;
6803 Stmt := Parent (Stmt);
6804 end if;
6806 -- The pragma or previous block must appear immediately within the
6807 -- statements of the loop.
6809 elsif Nkind (Stmt) = N_Loop_Statement then
6810 if List_Containing (Prev) /= Statements (Stmt) then
6811 Placement_Error (Prev);
6812 end if;
6814 -- Stop the traversal because we reached the innermost loop
6815 -- regardless of whether we encountered an error or not.
6817 exit;
6819 -- Ignore a handled statement sequence. Note that this node may
6820 -- be related to a subprogram body in which case we will emit an
6821 -- error on the next iteration of the search.
6823 elsif Nkind (Stmt) = N_Handled_Sequence_Of_Statements then
6824 Stmt := Parent (Stmt);
6826 -- Any other statement breaks the chain from the pragma to the
6827 -- loop.
6829 else
6830 Placement_Error (Prev);
6831 end if;
6832 end loop;
6834 -- Check that the current pragma Loop_Invariant or Loop_Variant is
6835 -- grouped together with other such pragmas.
6837 if Is_Loop_Pragma (N) then
6839 -- The previous check should have located the related loop
6841 pragma Assert (Nkind (Stmt) = N_Loop_Statement);
6842 Check_Loop_Pragma_Grouping (Stmt);
6843 end if;
6844 end Check_Loop_Pragma_Placement;
6846 -------------------------------------------
6847 -- Check_Is_In_Decl_Part_Or_Package_Spec --
6848 -------------------------------------------
6850 procedure Check_Is_In_Decl_Part_Or_Package_Spec is
6851 P : Node_Id;
6853 begin
6854 P := Parent (N);
6855 loop
6856 if No (P) then
6857 exit;
6859 elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
6860 exit;
6862 elsif Nkind (P) in N_Package_Specification | N_Block_Statement then
6863 return;
6865 -- Note: the following tests seem a little peculiar, because
6866 -- they test for bodies, but if we were in the statement part
6867 -- of the body, we would already have hit the handled statement
6868 -- sequence, so the only way we get here is by being in the
6869 -- declarative part of the body.
6871 elsif Nkind (P) in
6872 N_Subprogram_Body | N_Package_Body | N_Task_Body | N_Entry_Body
6873 then
6874 return;
6875 end if;
6877 P := Parent (P);
6878 end loop;
6880 Error_Pragma ("pragma% is not in declarative part or package spec");
6881 end Check_Is_In_Decl_Part_Or_Package_Spec;
6883 -------------------------
6884 -- Check_No_Identifier --
6885 -------------------------
6887 procedure Check_No_Identifier (Arg : Node_Id) is
6888 begin
6889 if Nkind (Arg) = N_Pragma_Argument_Association
6890 and then Chars (Arg) /= No_Name
6891 then
6892 Error_Pragma_Arg_Ident
6893 ("pragma% does not permit identifier& here", Arg);
6894 end if;
6895 end Check_No_Identifier;
6897 --------------------------
6898 -- Check_No_Identifiers --
6899 --------------------------
6901 procedure Check_No_Identifiers is
6902 Arg_Node : Node_Id;
6903 begin
6904 Arg_Node := Arg1;
6905 for J in 1 .. Arg_Count loop
6906 Check_No_Identifier (Arg_Node);
6907 Next (Arg_Node);
6908 end loop;
6909 end Check_No_Identifiers;
6911 ------------------------
6912 -- Check_No_Link_Name --
6913 ------------------------
6915 procedure Check_No_Link_Name is
6916 begin
6917 if Present (Arg3) and then Chars (Arg3) = Name_Link_Name then
6918 Arg4 := Arg3;
6919 end if;
6921 if Present (Arg4) then
6922 Error_Pragma_Arg
6923 ("Link_Name argument not allowed for Import Intrinsic", Arg4);
6924 end if;
6925 end Check_No_Link_Name;
6927 -------------------------------
6928 -- Check_Optional_Identifier --
6929 -------------------------------
6931 procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
6932 begin
6933 if Present (Arg)
6934 and then Nkind (Arg) = N_Pragma_Argument_Association
6935 and then Chars (Arg) /= No_Name
6936 then
6937 if Chars (Arg) /= Id then
6938 Error_Msg_Name_1 := Pname;
6939 Error_Msg_Name_2 := Id;
6940 Error_Msg_N ("pragma% argument expects identifier%", Arg);
6941 raise Pragma_Exit;
6942 end if;
6943 end if;
6944 end Check_Optional_Identifier;
6946 procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
6947 begin
6948 Check_Optional_Identifier (Arg, Name_Find (Id));
6949 end Check_Optional_Identifier;
6951 -------------------------------------
6952 -- Check_Static_Boolean_Expression --
6953 -------------------------------------
6955 procedure Check_Static_Boolean_Expression (Expr : Node_Id) is
6956 begin
6957 if Present (Expr) then
6958 Analyze_And_Resolve (Expr, Standard_Boolean);
6960 if not Is_OK_Static_Expression (Expr) then
6961 Error_Pragma_Arg
6962 ("expression of pragma % must be static", Expr);
6963 end if;
6964 end if;
6965 end Check_Static_Boolean_Expression;
6967 -----------------------------
6968 -- Check_Static_Constraint --
6969 -----------------------------
6971 procedure Check_Static_Constraint (Constr : Node_Id) is
6973 procedure Require_Static (E : Node_Id);
6974 -- Require given expression to be static expression
6976 --------------------
6977 -- Require_Static --
6978 --------------------
6980 procedure Require_Static (E : Node_Id) is
6981 begin
6982 if not Is_OK_Static_Expression (E) then
6983 Flag_Non_Static_Expr
6984 ("non-static constraint not allowed in Unchecked_Union!", E);
6985 raise Pragma_Exit;
6986 end if;
6987 end Require_Static;
6989 -- Start of processing for Check_Static_Constraint
6991 begin
6992 case Nkind (Constr) is
6993 when N_Discriminant_Association =>
6994 Require_Static (Expression (Constr));
6996 when N_Range =>
6997 Require_Static (Low_Bound (Constr));
6998 Require_Static (High_Bound (Constr));
7000 when N_Attribute_Reference =>
7001 Require_Static (Type_Low_Bound (Etype (Prefix (Constr))));
7002 Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
7004 when N_Range_Constraint =>
7005 Check_Static_Constraint (Range_Expression (Constr));
7007 when N_Index_Or_Discriminant_Constraint =>
7008 declare
7009 IDC : Entity_Id;
7010 begin
7011 IDC := First (Constraints (Constr));
7012 while Present (IDC) loop
7013 Check_Static_Constraint (IDC);
7014 Next (IDC);
7015 end loop;
7016 end;
7018 when others =>
7019 null;
7020 end case;
7021 end Check_Static_Constraint;
7023 --------------------------------------
7024 -- Check_Valid_Configuration_Pragma --
7025 --------------------------------------
7027 -- A configuration pragma must appear in the context clause of a
7028 -- compilation unit, and only other pragmas may precede it. Note that
7029 -- the test also allows use in a configuration pragma file.
7031 procedure Check_Valid_Configuration_Pragma is
7032 begin
7033 if not Is_Configuration_Pragma then
7034 Error_Pragma ("incorrect placement for configuration pragma%");
7035 end if;
7036 end Check_Valid_Configuration_Pragma;
7038 -------------------------------------
7039 -- Check_Valid_Library_Unit_Pragma --
7040 -------------------------------------
7042 procedure Check_Valid_Library_Unit_Pragma is
7043 Plist : List_Id;
7044 Parent_Node : Node_Id;
7045 Unit_Name : Entity_Id;
7046 Unit_Kind : Node_Kind;
7047 Unit_Node : Node_Id;
7048 Sindex : Source_File_Index;
7050 begin
7051 if not Is_List_Member (N) then
7052 Pragma_Misplaced;
7054 else
7055 Plist := List_Containing (N);
7056 Parent_Node := Parent (Plist);
7058 if Parent_Node = Empty then
7059 Pragma_Misplaced;
7061 -- Case of pragma appearing after a compilation unit. In this case
7062 -- it must have an argument with the corresponding name and must
7063 -- be part of the following pragmas of its parent.
7065 elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
7066 if Plist /= Pragmas_After (Parent_Node) then
7067 Error_Pragma
7068 ("pragma% misplaced, must be inside or after the "
7069 & "compilation unit");
7071 elsif Arg_Count = 0 then
7072 Error_Pragma
7073 ("argument required if outside compilation unit");
7075 else
7076 Check_No_Identifiers;
7077 Check_Arg_Count (1);
7078 Unit_Node := Unit (Parent (Parent_Node));
7079 Unit_Kind := Nkind (Unit_Node);
7081 Analyze (Get_Pragma_Arg (Arg1));
7083 if Unit_Kind = N_Generic_Subprogram_Declaration
7084 or else Unit_Kind = N_Subprogram_Declaration
7085 then
7086 Unit_Name := Defining_Entity (Unit_Node);
7088 elsif Unit_Kind in N_Generic_Instantiation then
7089 Unit_Name := Defining_Entity (Unit_Node);
7091 else
7092 Unit_Name := Cunit_Entity (Current_Sem_Unit);
7093 end if;
7095 if Chars (Unit_Name) /=
7096 Chars (Entity (Get_Pragma_Arg (Arg1)))
7097 then
7098 Error_Pragma_Arg
7099 ("pragma% argument is not current unit name", Arg1);
7100 end if;
7102 if Ekind (Unit_Name) = E_Package
7103 and then Present (Renamed_Entity (Unit_Name))
7104 then
7105 Error_Pragma ("pragma% not allowed for renamed package");
7106 end if;
7107 end if;
7109 -- Pragma appears other than after a compilation unit
7111 else
7112 -- Here we check for the generic instantiation case and also
7113 -- for the case of processing a generic formal package. We
7114 -- detect these cases by noting that the Sloc on the node
7115 -- does not belong to the current compilation unit.
7117 Sindex := Source_Index (Current_Sem_Unit);
7119 if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
7120 -- We do not want to raise an exception here since this code
7121 -- is part of the bootstrap path where we cannot rely on
7122 -- exception propagation working.
7123 -- Instead the caller should check for N being rewritten as
7124 -- a null statement.
7125 -- This code triggers when compiling a-except.adb.
7127 Rewrite (N, Make_Null_Statement (Loc));
7129 -- If before first declaration, the pragma applies to the
7130 -- enclosing unit, and the name if present must be this name.
7132 elsif Is_Before_First_Decl (N, Plist) then
7133 Unit_Node := Unit_Declaration_Node (Current_Scope);
7134 Unit_Kind := Nkind (Unit_Node);
7136 if Unit_Node = Standard_Package_Node then
7137 Error_Pragma
7138 ("pragma% misplaced, must be inside or after the "
7139 & "compilation unit");
7141 elsif Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
7142 Error_Pragma
7143 ("pragma% misplaced, must be on library unit");
7145 elsif Unit_Kind = N_Subprogram_Body
7146 and then not Acts_As_Spec (Unit_Node)
7147 then
7148 Error_Pragma
7149 ("pragma% misplaced, must be on the subprogram spec");
7151 elsif Nkind (Parent_Node) = N_Package_Body then
7152 Error_Pragma
7153 ("pragma% misplaced, must be on the package spec");
7155 elsif Nkind (Parent_Node) = N_Package_Specification
7156 and then Plist = Private_Declarations (Parent_Node)
7157 then
7158 Error_Pragma
7159 ("pragma% misplaced, must be in the public part");
7161 elsif Nkind (Parent_Node) in N_Generic_Declaration
7162 and then Plist = Generic_Formal_Declarations (Parent_Node)
7163 then
7164 Error_Pragma
7165 ("pragma% misplaced, must not be in formal part");
7167 elsif Arg_Count > 0 then
7168 Analyze (Get_Pragma_Arg (Arg1));
7170 if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
7171 Error_Pragma_Arg
7172 ("name in pragma% must be enclosing unit", Arg1);
7173 end if;
7175 -- It is legal to have no argument in this context
7177 else
7178 return;
7179 end if;
7181 -- Error if not before first declaration. This is because a
7182 -- library unit pragma argument must be the name of a library
7183 -- unit (RM 10.1.5(7)), but the only names permitted in this
7184 -- context are (RM 10.1.5(6)) names of subprogram declarations,
7185 -- generic subprogram declarations or generic instantiations.
7187 else
7188 Error_Pragma
7189 ("pragma% misplaced, must be before first declaration");
7190 end if;
7191 end if;
7192 end if;
7193 end Check_Valid_Library_Unit_Pragma;
7195 -------------------
7196 -- Check_Variant --
7197 -------------------
7199 procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
7200 Clist : constant Node_Id := Component_List (Variant);
7201 Comp : Node_Id;
7203 begin
7204 Comp := First_Non_Pragma (Component_Items (Clist));
7205 while Present (Comp) loop
7206 Check_Component (Comp, UU_Typ, In_Variant_Part => True);
7207 Next_Non_Pragma (Comp);
7208 end loop;
7209 end Check_Variant;
7211 ---------------------------
7212 -- Ensure_Aggregate_Form --
7213 ---------------------------
7215 procedure Ensure_Aggregate_Form (Arg : Node_Id) is
7216 CFSD : constant Boolean := Get_Comes_From_Source_Default;
7217 Expr : constant Node_Id := Expression (Arg);
7218 Loc : constant Source_Ptr := Sloc (Expr);
7219 Comps : List_Id := No_List;
7220 Exprs : List_Id := No_List;
7221 Nam : Name_Id := No_Name;
7222 Nam_Loc : Source_Ptr;
7224 begin
7225 -- The pragma argument is in positional form:
7227 -- pragma Depends (Nam => ...)
7228 -- ^
7229 -- Chars field
7231 -- Note that the Sloc of the Chars field is the Sloc of the pragma
7232 -- argument association.
7234 if Nkind (Arg) = N_Pragma_Argument_Association then
7235 Nam := Chars (Arg);
7236 Nam_Loc := Sloc (Arg);
7238 -- Remove the pragma argument name as this will be captured in the
7239 -- aggregate.
7241 Set_Chars (Arg, No_Name);
7242 end if;
7244 -- The argument is already in aggregate form, but the presence of a
7245 -- name causes this to be interpreted as named association which in
7246 -- turn must be converted into an aggregate.
7248 -- pragma Global (In_Out => (A, B, C))
7249 -- ^ ^
7250 -- name aggregate
7252 -- pragma Global ((In_Out => (A, B, C)))
7253 -- ^ ^
7254 -- aggregate aggregate
7256 if Nkind (Expr) = N_Aggregate then
7257 if Nam = No_Name then
7258 return;
7259 end if;
7261 -- Do not transform a null argument into an aggregate as N_Null has
7262 -- special meaning in formal verification pragmas.
7264 elsif Nkind (Expr) = N_Null then
7265 return;
7266 end if;
7268 -- Everything comes from source if the original comes from source
7270 Set_Comes_From_Source_Default (Comes_From_Source (Arg));
7272 -- Positional argument is transformed into an aggregate with an
7273 -- Expressions list.
7275 if Nam = No_Name then
7276 Exprs := New_List (Relocate_Node (Expr));
7278 -- An associative argument is transformed into an aggregate with
7279 -- Component_Associations.
7281 else
7282 Comps := New_List (
7283 Make_Component_Association (Loc,
7284 Choices => New_List (Make_Identifier (Nam_Loc, Nam)),
7285 Expression => Relocate_Node (Expr)));
7286 end if;
7288 Set_Expression (Arg,
7289 Make_Aggregate (Loc,
7290 Component_Associations => Comps,
7291 Expressions => Exprs));
7293 -- Restore Comes_From_Source default
7295 Set_Comes_From_Source_Default (CFSD);
7296 end Ensure_Aggregate_Form;
7298 ------------------
7299 -- Error_Pragma --
7300 ------------------
7302 procedure Error_Pragma (Msg : String) is
7303 begin
7304 Error_Msg_Name_1 := Pname;
7305 Error_Msg_N (Fix_Error (Msg), N);
7306 raise Pragma_Exit;
7307 end Error_Pragma;
7309 ----------------------
7310 -- Error_Pragma_Arg --
7311 ----------------------
7313 procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
7314 begin
7315 Error_Msg_Name_1 := Pname;
7316 Error_Msg_N (Fix_Error (Msg), Get_Pragma_Arg (Arg));
7317 raise Pragma_Exit;
7318 end Error_Pragma_Arg;
7320 procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
7321 begin
7322 Error_Msg_Name_1 := Pname;
7323 Error_Msg_N (Fix_Error (Msg1), Get_Pragma_Arg (Arg));
7324 Error_Pragma_Arg (Msg2, Arg);
7325 end Error_Pragma_Arg;
7327 ----------------------------
7328 -- Error_Pragma_Arg_Ident --
7329 ----------------------------
7331 procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
7332 begin
7333 Error_Msg_Name_1 := Pname;
7334 Error_Msg_N (Fix_Error (Msg), Arg);
7335 raise Pragma_Exit;
7336 end Error_Pragma_Arg_Ident;
7338 ----------------------
7339 -- Error_Pragma_Ref --
7340 ----------------------
7342 procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
7343 begin
7344 Error_Msg_Name_1 := Pname;
7345 Error_Msg_Sloc := Sloc (Ref);
7346 Error_Msg_NE (Fix_Error (Msg), N, Ref);
7347 raise Pragma_Exit;
7348 end Error_Pragma_Ref;
7350 ------------------------
7351 -- Find_Lib_Unit_Name --
7352 ------------------------
7354 function Find_Lib_Unit_Name return Entity_Id is
7355 begin
7356 -- Return inner compilation unit entity, for case of nested
7357 -- categorization pragmas. This happens in generic unit.
7359 if Nkind (Parent (N)) = N_Package_Specification
7360 and then Defining_Entity (Parent (N)) /= Current_Scope
7361 then
7362 return Defining_Entity (Parent (N));
7363 else
7364 return Current_Scope;
7365 end if;
7366 end Find_Lib_Unit_Name;
7368 ----------------------------
7369 -- Find_Program_Unit_Name --
7370 ----------------------------
7372 procedure Find_Program_Unit_Name (Id : Node_Id) is
7373 Unit_Name : Entity_Id;
7374 Unit_Kind : Node_Kind;
7375 P : constant Node_Id := Parent (N);
7377 begin
7378 if Nkind (P) = N_Compilation_Unit then
7379 Unit_Kind := Nkind (Unit (P));
7381 if Unit_Kind in N_Subprogram_Declaration
7382 | N_Package_Declaration
7383 | N_Generic_Declaration
7384 then
7385 Unit_Name := Defining_Entity (Unit (P));
7387 if Chars (Id) = Chars (Unit_Name) then
7388 Set_Entity (Id, Unit_Name);
7389 Set_Etype (Id, Etype (Unit_Name));
7390 else
7391 Set_Etype (Id, Any_Type);
7392 Error_Pragma
7393 ("cannot find program unit referenced by pragma%");
7394 end if;
7396 else
7397 Set_Etype (Id, Any_Type);
7398 Error_Pragma ("pragma% inapplicable to this unit");
7399 end if;
7401 else
7402 Analyze (Id);
7403 end if;
7404 end Find_Program_Unit_Name;
7406 -----------------------------------------
7407 -- Find_Unique_Parameterless_Procedure --
7408 -----------------------------------------
7410 function Find_Unique_Parameterless_Procedure
7411 (Name : Entity_Id;
7412 Arg : Node_Id) return Entity_Id
7414 Proc : Entity_Id := Empty;
7416 begin
7417 -- Perform sanity checks on Name
7419 if not Is_Entity_Name (Name) then
7420 Error_Pragma_Arg
7421 ("argument of pragma% must be entity name", Arg);
7423 elsif not Is_Overloaded (Name) then
7424 Proc := Entity (Name);
7426 if Ekind (Proc) /= E_Procedure
7427 or else Present (First_Formal (Proc))
7428 then
7429 Error_Pragma_Arg
7430 ("argument of pragma% must be parameterless procedure", Arg);
7431 end if;
7433 -- Otherwise, search through interpretations looking for one which
7434 -- has no parameters.
7436 else
7437 declare
7438 Found : Boolean := False;
7439 It : Interp;
7440 Index : Interp_Index;
7442 begin
7443 Get_First_Interp (Name, Index, It);
7444 while Present (It.Nam) loop
7445 Proc := It.Nam;
7447 if Ekind (Proc) = E_Procedure
7448 and then No (First_Formal (Proc))
7449 then
7450 -- We found an interpretation, note it and continue
7451 -- looking looking to verify it is unique.
7453 if not Found then
7454 Found := True;
7455 Set_Entity (Name, Proc);
7456 Set_Is_Overloaded (Name, False);
7458 -- Two procedures with the same name, log an error
7459 -- since the name is ambiguous.
7461 else
7462 Error_Pragma_Arg
7463 ("ambiguous handler name for pragma%", Arg);
7464 end if;
7465 end if;
7467 Get_Next_Interp (Index, It);
7468 end loop;
7470 if not Found then
7471 -- Issue an error if we haven't found a suitable match for
7472 -- Name.
7474 Error_Pragma_Arg
7475 ("argument of pragma% must be parameterless procedure",
7476 Arg);
7478 else
7479 Proc := Entity (Name);
7480 end if;
7481 end;
7482 end if;
7484 return Proc;
7485 end Find_Unique_Parameterless_Procedure;
7487 ---------------
7488 -- Fix_Error --
7489 ---------------
7491 function Fix_Error (Msg : String) return String is
7492 Res : String (Msg'Range) := Msg;
7493 Res_Last : Natural := Msg'Last;
7494 J : Natural;
7496 begin
7497 -- If we have a rewriting of another pragma, go to that pragma
7499 if Is_Rewrite_Substitution (N)
7500 and then Nkind (Original_Node (N)) = N_Pragma
7501 then
7502 Error_Msg_Name_1 := Pragma_Name (Original_Node (N));
7503 end if;
7505 -- Case where pragma comes from an aspect specification
7507 if From_Aspect_Specification (N) then
7509 -- Change appearance of "pragma" in message to "aspect"
7511 J := Res'First;
7512 while J <= Res_Last - 5 loop
7513 if Res (J .. J + 5) = "pragma" then
7514 Res (J .. J + 5) := "aspect";
7515 J := J + 6;
7517 else
7518 J := J + 1;
7519 end if;
7520 end loop;
7522 -- Change "argument of" at start of message to "entity for"
7524 if Res'Length > 11
7525 and then Res (Res'First .. Res'First + 10) = "argument of"
7526 then
7527 Res (Res'First .. Res'First + 9) := "entity for";
7528 Res (Res'First + 10 .. Res_Last - 1) :=
7529 Res (Res'First + 11 .. Res_Last);
7530 Res_Last := Res_Last - 1;
7531 end if;
7533 -- Change "argument" at start of message to "entity"
7535 if Res'Length > 8
7536 and then Res (Res'First .. Res'First + 7) = "argument"
7537 then
7538 Res (Res'First .. Res'First + 5) := "entity";
7539 Res (Res'First + 6 .. Res_Last - 2) :=
7540 Res (Res'First + 8 .. Res_Last);
7541 Res_Last := Res_Last - 2;
7542 end if;
7544 -- Get name from corresponding aspect
7546 Error_Msg_Name_1 := Original_Aspect_Pragma_Name (N);
7547 end if;
7549 -- Return possibly modified message
7551 return Res (Res'First .. Res_Last);
7552 end Fix_Error;
7554 -------------------------
7555 -- Gather_Associations --
7556 -------------------------
7558 procedure Gather_Associations
7559 (Names : Name_List;
7560 Args : out Args_List)
7562 Arg : Node_Id;
7564 begin
7565 -- Initialize all parameters to Empty
7567 for J in Args'Range loop
7568 Args (J) := Empty;
7569 end loop;
7571 -- That's all we have to do if there are no argument associations
7573 if No (Pragma_Argument_Associations (N)) then
7574 return;
7575 end if;
7577 -- Otherwise first deal with any positional parameters present
7579 Arg := First (Pragma_Argument_Associations (N));
7580 for Index in Args'Range loop
7581 exit when No (Arg) or else Chars (Arg) /= No_Name;
7582 Args (Index) := Get_Pragma_Arg (Arg);
7583 Next (Arg);
7584 end loop;
7586 -- Positional parameters all processed, if any left, then we
7587 -- have too many positional parameters.
7589 if Present (Arg) and then Chars (Arg) = No_Name then
7590 Error_Pragma_Arg
7591 ("too many positional associations for pragma%", Arg);
7592 end if;
7594 -- Process named parameters if any are present
7596 while Present (Arg) loop
7597 if Chars (Arg) = No_Name then
7598 Error_Pragma_Arg
7599 ("positional association cannot follow named association",
7600 Arg);
7602 else
7603 for Index in Names'Range loop
7604 if Names (Index) = Chars (Arg) then
7605 if Present (Args (Index)) then
7606 Error_Pragma_Arg
7607 ("duplicate argument association for pragma%", Arg);
7608 else
7609 Args (Index) := Get_Pragma_Arg (Arg);
7610 exit;
7611 end if;
7612 end if;
7614 if Index = Names'Last then
7615 Error_Msg_Name_1 := Pname;
7616 Error_Msg_N ("pragma% does not allow & argument", Arg);
7618 -- Check for possible misspelling
7620 for Index1 in Names'Range loop
7621 if Is_Bad_Spelling_Of
7622 (Chars (Arg), Names (Index1))
7623 then
7624 Error_Msg_Name_1 := Names (Index1);
7625 Error_Msg_N -- CODEFIX
7626 ("\possible misspelling of%", Arg);
7627 exit;
7628 end if;
7629 end loop;
7631 raise Pragma_Exit;
7632 end if;
7633 end loop;
7634 end if;
7636 Next (Arg);
7637 end loop;
7638 end Gather_Associations;
7640 -----------------
7641 -- GNAT_Pragma --
7642 -----------------
7644 procedure GNAT_Pragma is
7645 begin
7646 -- We need to check the No_Implementation_Pragmas restriction for
7647 -- the case of a pragma from source. Note that the case of aspects
7648 -- generating corresponding pragmas marks these pragmas as not being
7649 -- from source, so this test also catches that case.
7651 if Comes_From_Source (N) then
7652 Check_Restriction (No_Implementation_Pragmas, N);
7653 end if;
7654 end GNAT_Pragma;
7656 --------------------------
7657 -- Is_Before_First_Decl --
7658 --------------------------
7660 function Is_Before_First_Decl
7661 (Pragma_Node : Node_Id;
7662 Decls : List_Id) return Boolean
7664 Item : Node_Id := First (Decls);
7666 begin
7667 -- Only other pragmas can come before this pragma, but they might
7668 -- have been rewritten so check the original node.
7670 loop
7671 if No (Item) or else Nkind (Original_Node (Item)) /= N_Pragma then
7672 return False;
7674 elsif Item = Pragma_Node then
7675 return True;
7676 end if;
7678 Next (Item);
7679 end loop;
7680 end Is_Before_First_Decl;
7682 -----------------------------
7683 -- Is_Configuration_Pragma --
7684 -----------------------------
7686 -- A configuration pragma must appear in the context clause of a
7687 -- compilation unit, and only other pragmas may precede it. Note that
7688 -- the test below also permits use in a configuration pragma file.
7690 function Is_Configuration_Pragma return Boolean is
7691 Lis : List_Id;
7692 Par : constant Node_Id := Parent (N);
7693 Prg : Node_Id;
7695 begin
7696 -- Don't evaluate List_Containing (N) if Parent (N) could be
7697 -- an N_Aspect_Specification node.
7699 if not Is_List_Member (N) then
7700 return False;
7701 end if;
7703 Lis := List_Containing (N);
7705 -- If no parent, then we are in the configuration pragma file,
7706 -- so the placement is definitely appropriate.
7708 if No (Par) then
7709 return True;
7711 -- Otherwise we must be in the context clause of a compilation unit
7712 -- and the only thing allowed before us in the context list is more
7713 -- configuration pragmas.
7715 elsif Nkind (Par) = N_Compilation_Unit
7716 and then Context_Items (Par) = Lis
7717 then
7718 Prg := First (Lis);
7720 loop
7721 if Prg = N then
7722 return True;
7723 elsif Nkind (Prg) /= N_Pragma then
7724 return False;
7725 end if;
7727 Next (Prg);
7728 end loop;
7730 else
7731 return False;
7732 end if;
7733 end Is_Configuration_Pragma;
7735 --------------------------
7736 -- Is_In_Context_Clause --
7737 --------------------------
7739 function Is_In_Context_Clause return Boolean is
7740 Plist : List_Id;
7741 Parent_Node : Node_Id;
7743 begin
7744 if Is_List_Member (N) then
7745 Plist := List_Containing (N);
7746 Parent_Node := Parent (Plist);
7748 return Present (Parent_Node)
7749 and then Nkind (Parent_Node) = N_Compilation_Unit
7750 and then Context_Items (Parent_Node) = Plist;
7751 end if;
7753 return False;
7754 end Is_In_Context_Clause;
7756 ---------------------------------
7757 -- Is_Static_String_Expression --
7758 ---------------------------------
7760 function Is_Static_String_Expression (Arg : Node_Id) return Boolean is
7761 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
7762 Lit : constant Boolean := Nkind (Argx) = N_String_Literal;
7764 begin
7765 Analyze_And_Resolve (Argx);
7767 -- Special case Ada 83, where the expression will never be static,
7768 -- but we will return true if we had a string literal to start with.
7770 if Ada_Version = Ada_83 then
7771 return Lit;
7773 -- Normal case, true only if we end up with a string literal that
7774 -- is marked as being the result of evaluating a static expression.
7776 else
7777 return Is_OK_Static_Expression (Argx)
7778 and then Nkind (Argx) = N_String_Literal;
7779 end if;
7781 end Is_Static_String_Expression;
7783 ----------------------
7784 -- Pragma_Misplaced --
7785 ----------------------
7787 procedure Pragma_Misplaced is
7788 begin
7789 Error_Pragma ("incorrect placement of pragma%");
7790 end Pragma_Misplaced;
7792 ------------------------------------------------
7793 -- Process_Atomic_Independent_Shared_Volatile --
7794 ------------------------------------------------
7796 procedure Process_Atomic_Independent_Shared_Volatile is
7797 procedure Check_Full_Access_Only (Ent : Entity_Id);
7798 -- Apply legality checks to type or object Ent subject to the
7799 -- Full_Access_Only aspect in Ada 2022 (RM C.6(8.2)).
7801 procedure Mark_Component_Or_Object (Ent : Entity_Id);
7802 -- Appropriately set flags on the given entity, either an array or
7803 -- record component, or an object declaration) according to the
7804 -- current pragma.
7806 procedure Mark_Type (Ent : Entity_Id);
7807 -- Appropriately set flags on the given entity, a type
7809 procedure Set_Atomic_VFA (Ent : Entity_Id);
7810 -- Set given type as Is_Atomic or Is_Volatile_Full_Access. Also, if
7811 -- no explicit alignment was given, set alignment to unknown, since
7812 -- back end knows what the alignment requirements are for atomic and
7813 -- full access arrays. Note: this is necessary for derived types.
7815 -------------------------
7816 -- Check_Full_Access_Only --
7817 -------------------------
7819 procedure Check_Full_Access_Only (Ent : Entity_Id) is
7820 Typ : Entity_Id;
7822 Full_Access_Subcomponent : exception;
7823 -- Exception raised if a full access subcomponent is found
7825 Generic_Type_Subcomponent : exception;
7826 -- Exception raised if a subcomponent with generic type is found
7828 procedure Check_Subcomponents (Typ : Entity_Id);
7829 -- Apply checks to subcomponents recursively
7831 -------------------------
7832 -- Check_Subcomponents --
7833 -------------------------
7835 procedure Check_Subcomponents (Typ : Entity_Id) is
7836 Comp : Entity_Id;
7838 begin
7839 if Is_Array_Type (Typ) then
7840 Comp := Component_Type (Typ);
7842 if Has_Atomic_Components (Typ)
7843 or else Is_Full_Access (Comp)
7844 then
7845 raise Full_Access_Subcomponent;
7847 elsif Is_Generic_Type (Comp) then
7848 raise Generic_Type_Subcomponent;
7849 end if;
7851 -- Recurse on the component type
7853 Check_Subcomponents (Comp);
7855 elsif Is_Record_Type (Typ) then
7856 Comp := First_Component_Or_Discriminant (Typ);
7857 while Present (Comp) loop
7859 if Is_Full_Access (Comp)
7860 or else Is_Full_Access (Etype (Comp))
7861 then
7862 raise Full_Access_Subcomponent;
7864 elsif Is_Generic_Type (Etype (Comp)) then
7865 raise Generic_Type_Subcomponent;
7866 end if;
7868 -- Recurse on the component type
7870 Check_Subcomponents (Etype (Comp));
7872 Next_Component_Or_Discriminant (Comp);
7873 end loop;
7874 end if;
7875 end Check_Subcomponents;
7877 -- Start of processing for Check_Full_Access_Only
7879 begin
7880 -- Fetch the type in case we are dealing with an object or
7881 -- component.
7883 if Is_Type (Ent) then
7884 Typ := Ent;
7885 else
7886 pragma Assert (Is_Object (Ent)
7887 or else
7888 Nkind (Declaration_Node (Ent)) = N_Component_Declaration);
7890 Typ := Etype (Ent);
7891 end if;
7893 if not Is_Volatile (Ent) and then not Is_Volatile (Typ) then
7894 Error_Pragma
7895 ("cannot have Full_Access_Only without Volatile/Atomic "
7896 & "(RM C.6(8.2))");
7897 end if;
7899 -- Check all the subcomponents of the type recursively, if any
7901 Check_Subcomponents (Typ);
7903 exception
7904 when Full_Access_Subcomponent =>
7905 Error_Pragma
7906 ("cannot have Full_Access_Only with full access subcomponent "
7907 & "(RM C.6(8.2))");
7909 when Generic_Type_Subcomponent =>
7910 Error_Pragma
7911 ("cannot have Full_Access_Only with subcomponent of generic "
7912 & "type (RM C.6(8.2))");
7914 end Check_Full_Access_Only;
7916 ------------------------------
7917 -- Mark_Component_Or_Object --
7918 ------------------------------
7920 procedure Mark_Component_Or_Object (Ent : Entity_Id) is
7921 begin
7922 if Prag_Id = Pragma_Atomic
7923 or else Prag_Id = Pragma_Shared
7924 or else Prag_Id = Pragma_Volatile_Full_Access
7925 then
7926 if Prag_Id = Pragma_Volatile_Full_Access then
7927 Set_Is_Volatile_Full_Access (Ent);
7928 else
7929 Set_Is_Atomic (Ent);
7930 end if;
7932 -- If the object declaration has an explicit initialization, a
7933 -- temporary may have to be created to hold the expression, to
7934 -- ensure that access to the object remains atomic.
7936 if Nkind (Parent (Ent)) = N_Object_Declaration
7937 and then Present (Expression (Parent (Ent)))
7938 then
7939 Set_Has_Delayed_Freeze (Ent);
7940 end if;
7941 end if;
7943 -- Atomic/Shared/Volatile_Full_Access imply Independent
7945 if Prag_Id /= Pragma_Volatile then
7946 Set_Is_Independent (Ent);
7948 if Prag_Id = Pragma_Independent then
7949 Record_Independence_Check (N, Ent);
7950 end if;
7951 end if;
7953 -- Atomic/Shared/Volatile_Full_Access imply Volatile
7955 if Prag_Id /= Pragma_Independent then
7956 Set_Is_Volatile (Ent);
7957 Set_Treat_As_Volatile (Ent);
7958 end if;
7959 end Mark_Component_Or_Object;
7961 ---------------
7962 -- Mark_Type --
7963 ---------------
7965 procedure Mark_Type (Ent : Entity_Id) is
7966 begin
7967 -- Attribute belongs on the base type. If the view of the type is
7968 -- currently private, it also belongs on the underlying type.
7970 -- In Ada 2022, the pragma can apply to a formal type, for which
7971 -- there may be no underlying type.
7973 if Prag_Id = Pragma_Atomic
7974 or else Prag_Id = Pragma_Shared
7975 or else Prag_Id = Pragma_Volatile_Full_Access
7976 then
7977 Set_Atomic_VFA (Ent);
7978 Set_Atomic_VFA (Base_Type (Ent));
7980 if not Is_Generic_Type (Ent) then
7981 Set_Atomic_VFA (Underlying_Type (Ent));
7982 end if;
7983 end if;
7985 -- Atomic/Shared/Volatile_Full_Access imply Independent
7987 if Prag_Id /= Pragma_Volatile then
7988 Set_Is_Independent (Ent);
7989 Set_Is_Independent (Base_Type (Ent));
7991 if not Is_Generic_Type (Ent) then
7992 Set_Is_Independent (Underlying_Type (Ent));
7994 if Prag_Id = Pragma_Independent then
7995 Record_Independence_Check (N, Base_Type (Ent));
7996 end if;
7997 end if;
7998 end if;
8000 -- Atomic/Shared/Volatile_Full_Access imply Volatile
8002 if Prag_Id /= Pragma_Independent then
8003 Set_Is_Volatile (Ent);
8004 Set_Is_Volatile (Base_Type (Ent));
8006 if not Is_Generic_Type (Ent) then
8007 Set_Is_Volatile (Underlying_Type (Ent));
8008 Set_Treat_As_Volatile (Underlying_Type (Ent));
8009 end if;
8011 Set_Treat_As_Volatile (Ent);
8012 end if;
8014 -- Apply Volatile to the composite type's individual components,
8015 -- (RM C.6(8/3)).
8017 if Prag_Id = Pragma_Volatile
8018 and then Is_Record_Type (Etype (Ent))
8019 then
8020 declare
8021 Comp : Entity_Id;
8022 begin
8023 Comp := First_Component (Ent);
8024 while Present (Comp) loop
8025 Mark_Component_Or_Object (Comp);
8027 Next_Component (Comp);
8028 end loop;
8029 end;
8030 end if;
8031 end Mark_Type;
8033 --------------------
8034 -- Set_Atomic_VFA --
8035 --------------------
8037 procedure Set_Atomic_VFA (Ent : Entity_Id) is
8038 begin
8039 if Prag_Id = Pragma_Volatile_Full_Access then
8040 Set_Is_Volatile_Full_Access (Ent);
8041 else
8042 Set_Is_Atomic (Ent);
8043 end if;
8045 if not Has_Alignment_Clause (Ent) then
8046 Reinit_Alignment (Ent);
8047 end if;
8048 end Set_Atomic_VFA;
8050 -- Local variables
8052 Decl : Node_Id;
8053 E : Entity_Id;
8054 E_Arg : Node_Id;
8056 -- Start of processing for Process_Atomic_Independent_Shared_Volatile
8058 begin
8059 Check_Ada_83_Warning;
8060 Check_No_Identifiers;
8061 Check_Arg_Count (1);
8062 Check_Arg_Is_Local_Name (Arg1);
8063 E_Arg := Get_Pragma_Arg (Arg1);
8065 if Etype (E_Arg) = Any_Type then
8066 return;
8067 end if;
8069 E := Entity (E_Arg);
8070 Decl := Declaration_Node (E);
8072 -- A pragma that applies to a Ghost entity becomes Ghost for the
8073 -- purposes of legality checks and removal of ignored Ghost code.
8075 Mark_Ghost_Pragma (N, E);
8077 -- Check duplicate before we chain ourselves
8079 Check_Duplicate_Pragma (E);
8081 -- Check the constraints of Full_Access_Only in Ada 2022. Note that
8082 -- they do not apply to GNAT's Volatile_Full_Access because 1) this
8083 -- aspect subsumes the Volatile aspect and 2) nesting is supported
8084 -- for this aspect and the outermost enclosing VFA object prevails.
8086 -- Note also that we used to forbid specifying both Atomic and VFA on
8087 -- the same type or object, but the restriction has been lifted in
8088 -- light of the semantics of Full_Access_Only and Atomic in Ada 2022.
8090 if Prag_Id = Pragma_Volatile_Full_Access
8091 and then From_Aspect_Specification (N)
8092 and then
8093 Get_Aspect_Id (Corresponding_Aspect (N)) = Aspect_Full_Access_Only
8094 then
8095 Check_Full_Access_Only (E);
8096 end if;
8098 -- The following check is only relevant when SPARK_Mode is on as
8099 -- this is not a standard Ada legality rule. Pragma Volatile can
8100 -- only apply to a full type declaration or an object declaration
8101 -- (SPARK RM 7.1.3(2)). Original_Node is necessary to account for
8102 -- untagged derived types that are rewritten as subtypes of their
8103 -- respective root types.
8105 if SPARK_Mode = On
8106 and then Prag_Id = Pragma_Volatile
8107 and then Nkind (Original_Node (Decl)) not in
8108 N_Full_Type_Declaration |
8109 N_Formal_Type_Declaration |
8110 N_Object_Declaration |
8111 N_Single_Protected_Declaration |
8112 N_Single_Task_Declaration
8113 then
8114 Error_Pragma_Arg
8115 ("argument of pragma % must denote a full type or object "
8116 & "declaration", Arg1);
8117 end if;
8119 -- Deal with the case where the pragma/attribute is applied to a type
8121 if Is_Type (E) then
8122 if Rep_Item_Too_Early (E, N)
8123 or else Rep_Item_Too_Late (E, N)
8124 then
8125 return;
8126 else
8127 Check_First_Subtype (Arg1);
8128 end if;
8130 Mark_Type (E);
8132 -- Deal with the case where the pragma/attribute applies to a
8133 -- component or object declaration.
8135 elsif Nkind (Decl) = N_Object_Declaration
8136 or else (Nkind (Decl) = N_Component_Declaration
8137 and then Original_Record_Component (E) = E)
8138 then
8139 if Rep_Item_Too_Late (E, N) then
8140 return;
8141 end if;
8143 Mark_Component_Or_Object (E);
8145 -- In other cases give an error
8147 else
8148 Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
8149 end if;
8150 end Process_Atomic_Independent_Shared_Volatile;
8152 -------------------------------------------
8153 -- Process_Compile_Time_Warning_Or_Error --
8154 -------------------------------------------
8156 procedure Process_Compile_Time_Warning_Or_Error is
8157 P : Node_Id := Parent (N);
8158 Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
8160 begin
8161 Check_Arg_Count (2);
8162 Check_No_Identifiers;
8163 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
8164 Analyze_And_Resolve (Arg1x, Standard_Boolean);
8166 -- In GNATprove mode, pragma Compile_Time_Error is translated as
8167 -- a Check pragma in GNATprove mode, handled as an assumption in
8168 -- GNATprove. This is correct as the compiler will issue an error
8169 -- if the condition cannot be statically evaluated to False.
8170 -- Compile_Time_Warning are ignored, as the analyzer may not have the
8171 -- same information as the compiler (in particular regarding size of
8172 -- objects decided in gigi) so it makes no sense to issue a warning
8173 -- in GNATprove.
8175 if GNATprove_Mode then
8176 if Prag_Id = Pragma_Compile_Time_Error then
8177 declare
8178 New_Args : List_Id;
8179 begin
8180 -- Implement Compile_Time_Error by generating
8181 -- a corresponding Check pragma:
8183 -- pragma Check (name, condition);
8185 -- where name is the identifier matching the pragma name. So
8186 -- rewrite pragma in this manner and analyze the result.
8188 New_Args := New_List
8189 (Make_Pragma_Argument_Association
8190 (Loc,
8191 Expression => Make_Identifier (Loc, Pname)),
8192 Make_Pragma_Argument_Association
8193 (Sloc (Arg1x),
8194 Expression => Arg1x));
8196 -- Rewrite as Check pragma
8198 Rewrite (N,
8199 Make_Pragma (Loc,
8200 Chars => Name_Check,
8201 Pragma_Argument_Associations => New_Args));
8203 Analyze (N);
8204 end;
8206 else
8207 Rewrite (N, Make_Null_Statement (Loc));
8208 end if;
8210 return;
8211 end if;
8213 -- If the condition is known at compile time (now), validate it now.
8214 -- Otherwise, register the expression for validation after the back
8215 -- end has been called, because it might be known at compile time
8216 -- then. For example, if the expression is "Record_Type'Size /= 32"
8217 -- it might be known after the back end has determined the size of
8218 -- Record_Type. We do not defer validation if we're inside a generic
8219 -- unit, because we will have more information in the instances, and
8220 -- this ultimately applies to the main unit itself, because it is not
8221 -- compiled by the back end when it is generic.
8223 if Compile_Time_Known_Value (Arg1x) then
8224 Validate_Compile_Time_Warning_Or_Error (N, Sloc (Arg1));
8226 else
8227 while Present (P) and then Nkind (P) not in N_Generic_Declaration
8228 loop
8229 if (Nkind (P) = N_Subprogram_Body and then not Acts_As_Spec (P))
8230 or else Nkind (P) = N_Package_Body
8231 then
8232 P := Parent (Corresponding_Spec (P));
8234 else
8235 P := Parent (P);
8236 end if;
8237 end loop;
8239 if No (P)
8240 and then
8241 Nkind (Unit (Cunit (Main_Unit))) not in N_Generic_Declaration
8242 then
8243 Defer_Compile_Time_Warning_Error_To_BE (N);
8244 end if;
8245 end if;
8246 end Process_Compile_Time_Warning_Or_Error;
8248 ------------------------
8249 -- Process_Convention --
8250 ------------------------
8252 procedure Process_Convention
8253 (C : out Convention_Id;
8254 Ent : out Entity_Id)
8256 Cname : Name_Id;
8258 procedure Diagnose_Multiple_Pragmas (S : Entity_Id);
8259 -- Called if we have more than one Export/Import/Convention pragma.
8260 -- This is generally illegal, but we have a special case of allowing
8261 -- Import and Interface to coexist if they specify the convention in
8262 -- a consistent manner. We are allowed to do this, since Interface is
8263 -- an implementation defined pragma, and we choose to do it since we
8264 -- know Rational allows this combination. S is the entity id of the
8265 -- subprogram in question. This procedure also sets the special flag
8266 -- Import_Interface_Present in both pragmas in the case where we do
8267 -- have matching Import and Interface pragmas.
8269 procedure Set_Convention_From_Pragma (E : Entity_Id);
8270 -- Set convention in entity E, and also flag that the entity has a
8271 -- convention pragma. If entity is for a private or incomplete type,
8272 -- also set convention and flag on underlying type. This procedure
8273 -- also deals with the special case of C_Pass_By_Copy convention,
8274 -- and error checks for inappropriate convention specification.
8276 -------------------------------
8277 -- Diagnose_Multiple_Pragmas --
8278 -------------------------------
8280 procedure Diagnose_Multiple_Pragmas (S : Entity_Id) is
8281 Pdec : constant Node_Id := Declaration_Node (S);
8282 Decl : Node_Id;
8283 Err : Boolean;
8285 function Same_Convention (Decl : Node_Id) return Boolean;
8286 -- Decl is a pragma node. This function returns True if this
8287 -- pragma has a first argument that is an identifier with a
8288 -- Chars field corresponding to the Convention_Id C.
8290 function Same_Name (Decl : Node_Id) return Boolean;
8291 -- Decl is a pragma node. This function returns True if this
8292 -- pragma has a second argument that is an identifier with a
8293 -- Chars field that matches the Chars of the current subprogram.
8295 ---------------------
8296 -- Same_Convention --
8297 ---------------------
8299 function Same_Convention (Decl : Node_Id) return Boolean is
8300 Arg1 : constant Node_Id :=
8301 First (Pragma_Argument_Associations (Decl));
8303 begin
8304 if Present (Arg1) then
8305 declare
8306 Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
8307 begin
8308 if Nkind (Arg) = N_Identifier
8309 and then Is_Convention_Name (Chars (Arg))
8310 and then Get_Convention_Id (Chars (Arg)) = C
8311 then
8312 return True;
8313 end if;
8314 end;
8315 end if;
8317 return False;
8318 end Same_Convention;
8320 ---------------
8321 -- Same_Name --
8322 ---------------
8324 function Same_Name (Decl : Node_Id) return Boolean is
8325 Arg1 : constant Node_Id :=
8326 First (Pragma_Argument_Associations (Decl));
8327 Arg2 : Node_Id;
8329 begin
8330 if No (Arg1) then
8331 return False;
8332 end if;
8334 Arg2 := Next (Arg1);
8336 if No (Arg2) then
8337 return False;
8338 end if;
8340 declare
8341 Arg : constant Node_Id := Get_Pragma_Arg (Arg2);
8342 begin
8343 if Nkind (Arg) = N_Identifier
8344 and then Chars (Arg) = Chars (S)
8345 then
8346 return True;
8347 end if;
8348 end;
8350 return False;
8351 end Same_Name;
8353 -- Start of processing for Diagnose_Multiple_Pragmas
8355 begin
8356 Err := True;
8358 -- Definitely give message if we have Convention/Export here
8360 if Prag_Id = Pragma_Convention or else Prag_Id = Pragma_Export then
8361 null;
8363 -- If we have an Import or Export, scan back from pragma to
8364 -- find any previous pragma applying to the same procedure.
8365 -- The scan will be terminated by the start of the list, or
8366 -- hitting the subprogram declaration. This won't allow one
8367 -- pragma to appear in the public part and one in the private
8368 -- part, but that seems very unlikely in practice.
8370 else
8371 Decl := Prev (N);
8372 while Present (Decl) and then Decl /= Pdec loop
8374 -- Look for pragma with same name as us
8376 if Nkind (Decl) = N_Pragma
8377 and then Same_Name (Decl)
8378 then
8379 -- Give error if same as our pragma or Export/Convention
8381 if Pragma_Name_Unmapped (Decl)
8382 in Name_Export
8383 | Name_Convention
8384 | Pragma_Name_Unmapped (N)
8385 then
8386 exit;
8388 -- Case of Import/Interface or the other way round
8390 elsif Pragma_Name_Unmapped (Decl)
8391 in Name_Interface | Name_Import
8392 then
8393 -- Here we know that we have Import and Interface. It
8394 -- doesn't matter which way round they are. See if
8395 -- they specify the same convention. If so, all OK,
8396 -- and set special flags to stop other messages
8398 if Same_Convention (Decl) then
8399 Set_Import_Interface_Present (N);
8400 Set_Import_Interface_Present (Decl);
8401 Err := False;
8403 -- If different conventions, special message
8405 else
8406 Error_Msg_Sloc := Sloc (Decl);
8407 Error_Pragma_Arg
8408 ("convention differs from that given#", Arg1);
8409 end if;
8410 end if;
8411 end if;
8413 Next (Decl);
8414 end loop;
8415 end if;
8417 -- Give message if needed if we fall through those tests
8418 -- except on Relaxed_RM_Semantics where we let go: either this
8419 -- is a case accepted/ignored by other Ada compilers (e.g.
8420 -- a mix of Convention and Import), or another error will be
8421 -- generated later (e.g. using both Import and Export).
8423 if Err and not Relaxed_RM_Semantics then
8424 Error_Pragma_Arg
8425 ("at most one Convention/Export/Import pragma is allowed",
8426 Arg2);
8427 end if;
8428 end Diagnose_Multiple_Pragmas;
8430 --------------------------------
8431 -- Set_Convention_From_Pragma --
8432 --------------------------------
8434 procedure Set_Convention_From_Pragma (E : Entity_Id) is
8435 begin
8436 -- Ada 2005 (AI-430): Check invalid attempt to change convention
8437 -- for an overridden dispatching operation. Technically this is
8438 -- an amendment and should only be done in Ada 2005 mode. However,
8439 -- this is clearly a mistake, since the problem that is addressed
8440 -- by this AI is that there is a clear gap in the RM.
8442 if Is_Dispatching_Operation (E)
8443 and then Present (Overridden_Operation (E))
8444 and then C /= Convention (Overridden_Operation (E))
8445 then
8446 Error_Pragma_Arg
8447 ("cannot change convention for overridden dispatching "
8448 & "operation", Arg1);
8450 -- Special check for convention Stdcall: a dispatching call is not
8451 -- allowed. A dispatching subprogram cannot be used to interface
8452 -- to the Win32 API, so this check actually does not impose any
8453 -- effective restriction.
8455 elsif Is_Dispatching_Operation (E)
8456 and then C = Convention_Stdcall
8457 then
8458 -- Note: make this unconditional so that if there is more
8459 -- than one call to which the pragma applies, we get a
8460 -- message for each call. Also don't use Error_Pragma,
8461 -- so that we get multiple messages.
8463 Error_Msg_Sloc := Sloc (E);
8464 Error_Msg_N
8465 ("dispatching subprogram# cannot use Stdcall convention!",
8466 Get_Pragma_Arg (Arg1));
8467 end if;
8469 -- Set the convention
8471 Set_Convention (E, C);
8472 Set_Has_Convention_Pragma (E);
8474 -- For the case of a record base type, also set the convention of
8475 -- any anonymous access types declared in the record which do not
8476 -- currently have a specified convention.
8477 -- Similarly for an array base type and anonymous access types
8478 -- components.
8480 if Is_Base_Type (E) then
8481 if Is_Record_Type (E) then
8482 declare
8483 Comp : Node_Id;
8485 begin
8486 Comp := First_Component (E);
8487 while Present (Comp) loop
8488 if Present (Etype (Comp))
8489 and then
8490 Ekind (Etype (Comp)) in
8491 E_Anonymous_Access_Type |
8492 E_Anonymous_Access_Subprogram_Type
8493 and then not Has_Convention_Pragma (Comp)
8494 then
8495 Set_Convention (Comp, C);
8496 end if;
8498 Next_Component (Comp);
8499 end loop;
8500 end;
8502 elsif Is_Array_Type (E)
8503 and then Ekind (Component_Type (E)) in
8504 E_Anonymous_Access_Type |
8505 E_Anonymous_Access_Subprogram_Type
8506 then
8507 Set_Convention (Designated_Type (Component_Type (E)), C);
8508 end if;
8509 end if;
8511 -- Deal with incomplete/private type case, where underlying type
8512 -- is available, so set convention of that underlying type.
8514 if Is_Incomplete_Or_Private_Type (E)
8515 and then Present (Underlying_Type (E))
8516 then
8517 Set_Convention (Underlying_Type (E), C);
8518 Set_Has_Convention_Pragma (Underlying_Type (E), True);
8519 end if;
8521 -- A class-wide type should inherit the convention of the specific
8522 -- root type (although this isn't specified clearly by the RM).
8524 if Is_Type (E) and then Present (Class_Wide_Type (E)) then
8525 Set_Convention (Class_Wide_Type (E), C);
8526 end if;
8528 -- If the entity is a record type, then check for special case of
8529 -- C_Pass_By_Copy, which is treated the same as C except that the
8530 -- special record flag is set. This convention is only permitted
8531 -- on record types (see AI95-00131).
8533 if Cname = Name_C_Pass_By_Copy then
8534 if Is_Record_Type (E) then
8535 Set_C_Pass_By_Copy (Base_Type (E));
8536 elsif Is_Incomplete_Or_Private_Type (E)
8537 and then Is_Record_Type (Underlying_Type (E))
8538 then
8539 Set_C_Pass_By_Copy (Base_Type (Underlying_Type (E)));
8540 else
8541 Error_Pragma_Arg
8542 ("C_Pass_By_Copy convention allowed only for record type",
8543 Arg2);
8544 end if;
8545 end if;
8547 -- If the entity is a derived boolean type, check for the special
8548 -- case of convention C, C++, or Fortran, where we consider any
8549 -- nonzero value to represent true.
8551 if Is_Discrete_Type (E)
8552 and then Root_Type (Etype (E)) = Standard_Boolean
8553 and then
8554 (C = Convention_C
8555 or else
8556 C = Convention_CPP
8557 or else
8558 C = Convention_Fortran)
8559 then
8560 Set_Nonzero_Is_True (Base_Type (E));
8561 end if;
8562 end Set_Convention_From_Pragma;
8564 -- Local variables
8566 Comp_Unit : Unit_Number_Type;
8567 E : Entity_Id;
8568 E1 : Entity_Id;
8569 Id : Node_Id;
8570 Subp : Entity_Id;
8572 -- Start of processing for Process_Convention
8574 begin
8575 Check_At_Least_N_Arguments (2);
8576 Check_Optional_Identifier (Arg1, Name_Convention);
8577 Check_Arg_Is_Identifier (Arg1);
8578 Cname := Chars (Get_Pragma_Arg (Arg1));
8580 -- C_Pass_By_Copy is treated as a synonym for convention C (this is
8581 -- tested again below to set the critical flag).
8583 if Cname = Name_C_Pass_By_Copy then
8584 C := Convention_C;
8586 -- Otherwise we must have something in the standard convention list
8588 elsif Is_Convention_Name (Cname) then
8589 C := Get_Convention_Id (Chars (Get_Pragma_Arg (Arg1)));
8591 -- Otherwise warn on unrecognized convention
8593 else
8594 if Warn_On_Export_Import then
8595 Error_Msg_N
8596 ("??unrecognized convention name, C assumed",
8597 Get_Pragma_Arg (Arg1));
8598 end if;
8600 C := Convention_C;
8601 end if;
8603 Check_Optional_Identifier (Arg2, Name_Entity);
8604 Check_Arg_Is_Local_Name (Arg2);
8606 Id := Get_Pragma_Arg (Arg2);
8607 Analyze (Id);
8609 if not Is_Entity_Name (Id) then
8610 Error_Pragma_Arg ("entity name required", Arg2);
8611 end if;
8613 E := Entity (Id);
8615 -- Set entity to return
8617 Ent := E;
8619 -- Ada_Pass_By_Copy special checking
8621 if C = Convention_Ada_Pass_By_Copy then
8622 if not Is_First_Subtype (E) then
8623 Error_Pragma_Arg
8624 ("convention `Ada_Pass_By_Copy` only allowed for types",
8625 Arg2);
8626 end if;
8628 if Is_By_Reference_Type (E) then
8629 Error_Pragma_Arg
8630 ("convention `Ada_Pass_By_Copy` not allowed for by-reference "
8631 & "type", Arg1);
8632 end if;
8634 -- Ada_Pass_By_Reference special checking
8636 elsif C = Convention_Ada_Pass_By_Reference then
8637 if not Is_First_Subtype (E) then
8638 Error_Pragma_Arg
8639 ("convention `Ada_Pass_By_Reference` only allowed for types",
8640 Arg2);
8641 end if;
8643 if Is_By_Copy_Type (E) then
8644 Error_Pragma_Arg
8645 ("convention `Ada_Pass_By_Reference` not allowed for by-copy "
8646 & "type", Arg1);
8647 end if;
8648 end if;
8650 -- Go to renamed subprogram if present, since convention applies to
8651 -- the actual renamed entity, not to the renaming entity. If the
8652 -- subprogram is inherited, go to parent subprogram.
8654 if Is_Subprogram (E)
8655 and then Present (Alias (E))
8656 then
8657 if Nkind (Parent (Declaration_Node (E))) =
8658 N_Subprogram_Renaming_Declaration
8659 then
8660 if Scope (E) /= Scope (Alias (E)) then
8661 Error_Pragma_Ref
8662 ("cannot apply pragma% to non-local entity&#", E);
8663 end if;
8665 E := Alias (E);
8667 elsif Nkind (Parent (E)) in
8668 N_Full_Type_Declaration | N_Private_Extension_Declaration
8669 and then Scope (E) = Scope (Alias (E))
8670 then
8671 E := Alias (E);
8673 -- Return the parent subprogram the entity was inherited from
8675 Ent := E;
8676 end if;
8677 end if;
8679 -- Check that we are not applying this to a specless body. Relax this
8680 -- check if Relaxed_RM_Semantics to accommodate other Ada compilers.
8682 if Is_Subprogram (E)
8683 and then Nkind (Parent (Declaration_Node (E))) = N_Subprogram_Body
8684 and then not Relaxed_RM_Semantics
8685 then
8686 Error_Pragma
8687 ("pragma% requires separate spec and must come before body");
8688 end if;
8690 -- Check that we are not applying this to a named constant
8692 if Is_Named_Number (E) then
8693 Error_Msg_Name_1 := Pname;
8694 Error_Msg_N
8695 ("cannot apply pragma% to named constant!",
8696 Get_Pragma_Arg (Arg2));
8697 Error_Pragma_Arg
8698 ("\supply appropriate type for&!", Arg2);
8699 end if;
8701 if Ekind (E) = E_Enumeration_Literal then
8702 Error_Pragma ("enumeration literal not allowed for pragma%");
8703 end if;
8705 -- Check for rep item appearing too early or too late
8707 if Etype (E) = Any_Type
8708 or else Rep_Item_Too_Early (E, N)
8709 then
8710 raise Pragma_Exit;
8712 elsif Present (Underlying_Type (E)) then
8713 E := Underlying_Type (E);
8714 end if;
8716 if Rep_Item_Too_Late (E, N) then
8717 raise Pragma_Exit;
8718 end if;
8720 if Has_Convention_Pragma (E) then
8721 Diagnose_Multiple_Pragmas (E);
8723 elsif Convention (E) = Convention_Protected
8724 or else Ekind (Scope (E)) = E_Protected_Type
8725 then
8726 Error_Pragma_Arg
8727 ("a protected operation cannot be given a different convention",
8728 Arg2);
8729 end if;
8731 -- For Intrinsic, a subprogram is required
8733 if C = Convention_Intrinsic
8734 and then not Is_Subprogram_Or_Generic_Subprogram (E)
8735 then
8736 -- Accept Intrinsic Export on types if Relaxed_RM_Semantics
8738 if not (Is_Type (E) and then Relaxed_RM_Semantics) then
8739 if From_Aspect_Specification (N) then
8740 Error_Pragma_Arg
8741 ("entity for aspect% must be a subprogram", Arg2);
8742 else
8743 Error_Pragma_Arg
8744 ("second argument of pragma% must be a subprogram", Arg2);
8745 end if;
8746 end if;
8748 -- Special checks for C_Variadic_n
8750 elsif C in Convention_C_Variadic then
8752 -- Several allowed cases
8754 if Is_Subprogram_Or_Generic_Subprogram (E) then
8755 Subp := E;
8757 -- An access to subprogram is also allowed
8759 elsif Is_Access_Type (E)
8760 and then Ekind (Designated_Type (E)) = E_Subprogram_Type
8761 then
8762 Subp := Designated_Type (E);
8764 -- Allow internal call to set convention of subprogram type
8766 elsif Ekind (E) = E_Subprogram_Type then
8767 Subp := E;
8769 else
8770 Error_Pragma_Arg
8771 ("argument of pragma% must be subprogram or access type",
8772 Arg2);
8773 end if;
8775 -- ISO C requires a named parameter before the ellipsis, so a
8776 -- variadic C function taking 0 fixed parameter cannot exist.
8778 if C = Convention_C_Variadic_0 then
8780 Error_Msg_N
8781 ("??C_Variadic_0 cannot be used for an 'I'S'O C function",
8782 Get_Pragma_Arg (Arg2));
8784 -- Now check the number of parameters of the subprogram and give
8785 -- an error if it is lower than n.
8787 elsif Present (Subp) then
8788 declare
8789 Minimum : constant Nat :=
8790 Convention_Id'Pos (C) -
8791 Convention_Id'Pos (Convention_C_Variadic_0);
8793 Count : Nat;
8794 Formal : Entity_Id;
8796 begin
8797 Count := 0;
8798 Formal := First_Formal (Subp);
8799 while Present (Formal) loop
8800 Count := Count + 1;
8801 Next_Formal (Formal);
8802 end loop;
8804 if Count < Minimum then
8805 Error_Msg_Uint_1 := UI_From_Int (Minimum);
8806 Error_Pragma_Arg
8807 ("argument of pragma% must have at least"
8808 & "^ parameters", Arg2);
8809 end if;
8810 end;
8811 end if;
8813 -- Special checks for Stdcall
8815 elsif C = Convention_Stdcall then
8817 -- Several allowed cases
8819 if Is_Subprogram_Or_Generic_Subprogram (E)
8821 -- A variable is OK
8823 or else Ekind (E) = E_Variable
8825 -- A component as well. The entity does not have its Ekind
8826 -- set until the enclosing record declaration is fully
8827 -- analyzed.
8829 or else Nkind (Parent (E)) = N_Component_Declaration
8831 -- An access to subprogram is also allowed
8833 or else
8834 (Is_Access_Type (E)
8835 and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
8837 -- Allow internal call to set convention of subprogram type
8839 or else Ekind (E) = E_Subprogram_Type
8840 then
8841 null;
8843 else
8844 Error_Pragma_Arg
8845 ("argument of pragma% must be subprogram or access type",
8846 Arg2);
8847 end if;
8848 end if;
8850 Set_Convention_From_Pragma (E);
8852 -- Deal with non-subprogram cases
8854 if not Is_Subprogram_Or_Generic_Subprogram (E) then
8855 if Is_Type (E) then
8857 -- The pragma must apply to a first subtype, but it can also
8858 -- apply to a generic type in a generic formal part, in which
8859 -- case it will also appear in the corresponding instance.
8861 if Is_Generic_Type (E) or else In_Instance then
8862 null;
8863 else
8864 Check_First_Subtype (Arg2);
8865 end if;
8867 Set_Convention_From_Pragma (Base_Type (E));
8869 -- For access subprograms, we must set the convention on the
8870 -- internally generated directly designated type as well.
8872 if Ekind (E) = E_Access_Subprogram_Type then
8873 Set_Convention_From_Pragma (Directly_Designated_Type (E));
8874 end if;
8875 end if;
8877 -- For the subprogram case, set proper convention for all homonyms
8878 -- in same scope and the same declarative part, i.e. the same
8879 -- compilation unit.
8881 else
8882 -- Treat a pragma Import as an implicit body, and pragma import
8883 -- as implicit reference (for navigation in GNAT Studio).
8885 if Prag_Id = Pragma_Import then
8886 Generate_Reference (E, Id, 'b');
8888 -- For exported entities we restrict the generation of references
8889 -- to entities exported to foreign languages since entities
8890 -- exported to Ada do not provide further information to
8891 -- GNAT Studio and add undesired references to the output of the
8892 -- gnatxref tool.
8894 elsif Prag_Id = Pragma_Export
8895 and then Convention (E) /= Convention_Ada
8896 then
8897 Generate_Reference (E, Id, 'i');
8898 end if;
8900 -- If the pragma comes from an aspect, it only applies to the
8901 -- given entity, not its homonyms.
8903 if From_Aspect_Specification (N) then
8904 if C = Convention_Intrinsic
8905 and then Nkind (Ent) = N_Defining_Operator_Symbol
8906 then
8907 if Is_Fixed_Point_Type (Etype (Ent))
8908 or else Is_Fixed_Point_Type (Etype (First_Entity (Ent)))
8909 or else Is_Fixed_Point_Type (Etype (Last_Entity (Ent)))
8910 then
8911 Error_Msg_N
8912 ("no intrinsic operator available for this fixed-point "
8913 & "operation", N);
8914 Error_Msg_N
8915 ("\use expression functions with the desired "
8916 & "conversions made explicit", N);
8917 end if;
8918 end if;
8920 return;
8921 end if;
8923 -- Otherwise Loop through the homonyms of the pragma argument's
8924 -- entity, an apply convention to those in the current scope.
8926 Comp_Unit := Get_Source_Unit (E);
8927 E1 := Ent;
8929 loop
8930 E1 := Homonym (E1);
8931 exit when No (E1) or else Scope (E1) /= Current_Scope;
8933 -- Ignore entry for which convention is already set
8935 if Has_Convention_Pragma (E1) then
8936 goto Continue;
8937 end if;
8939 if Is_Subprogram (E1)
8940 and then Nkind (Parent (Declaration_Node (E1))) =
8941 N_Subprogram_Body
8942 and then not Relaxed_RM_Semantics
8943 then
8944 Set_Has_Completion (E); -- to prevent cascaded error
8945 Error_Pragma_Ref
8946 ("pragma% requires separate spec and must come before "
8947 & "body#", E1);
8948 end if;
8950 -- Do not set the pragma on inherited operations or on formal
8951 -- subprograms.
8953 if Comes_From_Source (E1)
8954 and then Comp_Unit = Get_Source_Unit (E1)
8955 and then not Is_Formal_Subprogram (E1)
8956 and then Nkind (Original_Node (Parent (E1))) /=
8957 N_Full_Type_Declaration
8958 then
8959 if Present (Alias (E1))
8960 and then Scope (E1) /= Scope (Alias (E1))
8961 then
8962 Error_Pragma_Ref
8963 ("cannot apply pragma% to non-local entity& declared#",
8964 E1);
8965 end if;
8967 Set_Convention_From_Pragma (E1);
8969 if Prag_Id = Pragma_Import then
8970 Generate_Reference (E1, Id, 'b');
8971 end if;
8972 end if;
8974 <<Continue>>
8975 null;
8976 end loop;
8977 end if;
8978 end Process_Convention;
8980 ----------------------------------------
8981 -- Process_Disable_Enable_Atomic_Sync --
8982 ----------------------------------------
8984 procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id) is
8985 begin
8986 Check_No_Identifiers;
8987 Check_At_Most_N_Arguments (1);
8989 -- Modeled internally as
8990 -- pragma Suppress/Unsuppress (Atomic_Synchronization [,Entity])
8992 Rewrite (N,
8993 Make_Pragma (Loc,
8994 Chars => Nam,
8995 Pragma_Argument_Associations => New_List (
8996 Make_Pragma_Argument_Association (Loc,
8997 Expression =>
8998 Make_Identifier (Loc, Name_Atomic_Synchronization)))));
9000 if Present (Arg1) then
9001 Append_To (Pragma_Argument_Associations (N), New_Copy (Arg1));
9002 end if;
9004 Analyze (N);
9005 end Process_Disable_Enable_Atomic_Sync;
9007 -------------------------------------------------
9008 -- Process_Extended_Import_Export_Internal_Arg --
9009 -------------------------------------------------
9011 procedure Process_Extended_Import_Export_Internal_Arg
9012 (Arg_Internal : Node_Id := Empty)
9014 begin
9015 if No (Arg_Internal) then
9016 Error_Pragma ("Internal parameter required for pragma%");
9017 end if;
9019 if Nkind (Arg_Internal) = N_Identifier then
9020 null;
9022 elsif Nkind (Arg_Internal) = N_Operator_Symbol
9023 and then (Prag_Id = Pragma_Import_Function
9024 or else
9025 Prag_Id = Pragma_Export_Function)
9026 then
9027 null;
9029 else
9030 Error_Pragma_Arg
9031 ("wrong form for Internal parameter for pragma%", Arg_Internal);
9032 end if;
9034 Check_Arg_Is_Local_Name (Arg_Internal);
9035 end Process_Extended_Import_Export_Internal_Arg;
9037 --------------------------------------------------
9038 -- Process_Extended_Import_Export_Object_Pragma --
9039 --------------------------------------------------
9041 procedure Process_Extended_Import_Export_Object_Pragma
9042 (Arg_Internal : Node_Id;
9043 Arg_External : Node_Id;
9044 Arg_Size : Node_Id)
9046 Def_Id : Entity_Id;
9048 begin
9049 Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
9050 Def_Id := Entity (Arg_Internal);
9052 if Ekind (Def_Id) not in E_Constant | E_Variable then
9053 Error_Pragma_Arg
9054 ("pragma% must designate an object", Arg_Internal);
9055 end if;
9057 if Has_Rep_Pragma (Def_Id, Name_Common_Object)
9058 or else
9059 Has_Rep_Pragma (Def_Id, Name_Psect_Object)
9060 then
9061 Error_Pragma_Arg
9062 ("previous Common/Psect_Object applies, pragma % not permitted",
9063 Arg_Internal);
9064 end if;
9066 if Rep_Item_Too_Late (Def_Id, N) then
9067 raise Pragma_Exit;
9068 end if;
9070 Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
9072 if Present (Arg_Size) then
9073 Check_Arg_Is_External_Name (Arg_Size);
9074 end if;
9076 -- Export_Object case
9078 if Prag_Id = Pragma_Export_Object then
9079 if not Is_Library_Level_Entity (Def_Id) then
9080 Error_Pragma_Arg
9081 ("argument for pragma% must be library level entity",
9082 Arg_Internal);
9083 end if;
9085 if Ekind (Current_Scope) = E_Generic_Package then
9086 Error_Pragma ("pragma& cannot appear in a generic unit");
9087 end if;
9089 if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
9090 Error_Pragma_Arg
9091 ("exported object must have compile time known size",
9092 Arg_Internal);
9093 end if;
9095 if Warn_On_Export_Import and then Is_Exported (Def_Id) then
9096 Error_Msg_N ("??duplicate Export_Object pragma", N);
9097 else
9098 Set_Exported (Def_Id, Arg_Internal);
9099 end if;
9101 -- Import_Object case
9103 else
9104 if Is_Concurrent_Type (Etype (Def_Id)) then
9105 Error_Pragma_Arg
9106 ("cannot use pragma% for task/protected object",
9107 Arg_Internal);
9108 end if;
9110 if Ekind (Def_Id) = E_Constant then
9111 Error_Pragma_Arg
9112 ("cannot import a constant", Arg_Internal);
9113 end if;
9115 if Warn_On_Export_Import
9116 and then Has_Discriminants (Etype (Def_Id))
9117 then
9118 Error_Msg_N
9119 ("imported value must be initialized??", Arg_Internal);
9120 end if;
9122 if Warn_On_Export_Import
9123 and then Is_Access_Type (Etype (Def_Id))
9124 then
9125 Error_Pragma_Arg
9126 ("cannot import object of an access type??", Arg_Internal);
9127 end if;
9129 if Warn_On_Export_Import
9130 and then Is_Imported (Def_Id)
9131 then
9132 Error_Msg_N ("??duplicate Import_Object pragma", N);
9134 -- Check for explicit initialization present. Note that an
9135 -- initialization generated by the code generator, e.g. for an
9136 -- access type, does not count here.
9138 elsif Present (Expression (Parent (Def_Id)))
9139 and then
9140 Comes_From_Source
9141 (Original_Node (Expression (Parent (Def_Id))))
9142 then
9143 Error_Msg_Sloc := Sloc (Def_Id);
9144 Error_Pragma_Arg
9145 ("imported entities cannot be initialized (RM B.1(24))",
9146 "\no initialization allowed for & declared#", Arg1);
9147 else
9148 Set_Imported (Def_Id);
9149 Note_Possible_Modification (Arg_Internal, Sure => False);
9150 end if;
9151 end if;
9152 end Process_Extended_Import_Export_Object_Pragma;
9154 ------------------------------------------------------
9155 -- Process_Extended_Import_Export_Subprogram_Pragma --
9156 ------------------------------------------------------
9158 procedure Process_Extended_Import_Export_Subprogram_Pragma
9159 (Arg_Internal : Node_Id;
9160 Arg_External : Node_Id;
9161 Arg_Parameter_Types : Node_Id;
9162 Arg_Result_Type : Node_Id := Empty;
9163 Arg_Mechanism : Node_Id;
9164 Arg_Result_Mechanism : Node_Id := Empty)
9166 Ent : Entity_Id;
9167 Def_Id : Entity_Id;
9168 Hom_Id : Entity_Id;
9169 Formal : Entity_Id;
9170 Ambiguous : Boolean;
9171 Match : Boolean;
9173 function Same_Base_Type
9174 (Ptype : Node_Id;
9175 Formal : Entity_Id) return Boolean;
9176 -- Determines if Ptype references the type of Formal. Note that only
9177 -- the base types need to match according to the spec. Ptype here is
9178 -- the argument from the pragma, which is either a type name, or an
9179 -- access attribute.
9181 --------------------
9182 -- Same_Base_Type --
9183 --------------------
9185 function Same_Base_Type
9186 (Ptype : Node_Id;
9187 Formal : Entity_Id) return Boolean
9189 Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
9190 Pref : Node_Id;
9192 begin
9193 -- Case where pragma argument is typ'Access
9195 if Nkind (Ptype) = N_Attribute_Reference
9196 and then Attribute_Name (Ptype) = Name_Access
9197 then
9198 Pref := Prefix (Ptype);
9199 Find_Type (Pref);
9201 if not Is_Entity_Name (Pref)
9202 or else Entity (Pref) = Any_Type
9203 then
9204 raise Pragma_Exit;
9205 end if;
9207 -- We have a match if the corresponding argument is of an
9208 -- anonymous access type, and its designated type matches the
9209 -- type of the prefix of the access attribute
9211 return Ekind (Ftyp) = E_Anonymous_Access_Type
9212 and then Base_Type (Entity (Pref)) =
9213 Base_Type (Etype (Designated_Type (Ftyp)));
9215 -- Case where pragma argument is a type name
9217 else
9218 Find_Type (Ptype);
9220 if not Is_Entity_Name (Ptype)
9221 or else Entity (Ptype) = Any_Type
9222 then
9223 raise Pragma_Exit;
9224 end if;
9226 -- We have a match if the corresponding argument is of the type
9227 -- given in the pragma (comparing base types)
9229 return Base_Type (Entity (Ptype)) = Ftyp;
9230 end if;
9231 end Same_Base_Type;
9233 -- Start of processing for
9234 -- Process_Extended_Import_Export_Subprogram_Pragma
9236 begin
9237 Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
9238 Ent := Empty;
9239 Ambiguous := False;
9241 -- Loop through homonyms (overloadings) of the entity
9243 Hom_Id := Entity (Arg_Internal);
9244 while Present (Hom_Id) loop
9245 Def_Id := Get_Base_Subprogram (Hom_Id);
9247 -- We need a subprogram in the current scope
9249 if not Is_Subprogram (Def_Id)
9250 or else Scope (Def_Id) /= Current_Scope
9251 then
9252 null;
9254 else
9255 Match := True;
9257 -- Pragma cannot apply to subprogram body
9259 if Is_Subprogram (Def_Id)
9260 and then Nkind (Parent (Declaration_Node (Def_Id))) =
9261 N_Subprogram_Body
9262 then
9263 Error_Pragma
9264 ("pragma% requires separate spec and must come before "
9265 & "body");
9266 end if;
9268 -- Test result type if given, note that the result type
9269 -- parameter can only be present for the function cases.
9271 if Present (Arg_Result_Type)
9272 and then not Same_Base_Type (Arg_Result_Type, Def_Id)
9273 then
9274 Match := False;
9276 elsif Etype (Def_Id) /= Standard_Void_Type
9277 and then
9278 Pname in Name_Export_Procedure | Name_Import_Procedure
9279 then
9280 Match := False;
9282 -- Test parameter types if given. Note that this parameter has
9283 -- not been analyzed (and must not be, since it is semantic
9284 -- nonsense), so we get it as the parser left it.
9286 elsif Present (Arg_Parameter_Types) then
9287 Check_Matching_Types : declare
9288 Formal : Entity_Id;
9289 Ptype : Node_Id;
9291 begin
9292 Formal := First_Formal (Def_Id);
9294 if Nkind (Arg_Parameter_Types) = N_Null then
9295 if Present (Formal) then
9296 Match := False;
9297 end if;
9299 -- A list of one type, e.g. (List) is parsed as a
9300 -- parenthesized expression.
9302 elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
9303 and then Paren_Count (Arg_Parameter_Types) = 1
9304 then
9305 if No (Formal)
9306 or else Present (Next_Formal (Formal))
9307 then
9308 Match := False;
9309 else
9310 Match :=
9311 Same_Base_Type (Arg_Parameter_Types, Formal);
9312 end if;
9314 -- A list of more than one type is parsed as a aggregate
9316 elsif Nkind (Arg_Parameter_Types) = N_Aggregate
9317 and then Paren_Count (Arg_Parameter_Types) = 0
9318 then
9319 Ptype := First (Expressions (Arg_Parameter_Types));
9320 while Present (Ptype) or else Present (Formal) loop
9321 if No (Ptype)
9322 or else No (Formal)
9323 or else not Same_Base_Type (Ptype, Formal)
9324 then
9325 Match := False;
9326 exit;
9327 else
9328 Next_Formal (Formal);
9329 Next (Ptype);
9330 end if;
9331 end loop;
9333 -- Anything else is of the wrong form
9335 else
9336 Error_Pragma_Arg
9337 ("wrong form for Parameter_Types parameter",
9338 Arg_Parameter_Types);
9339 end if;
9340 end Check_Matching_Types;
9341 end if;
9343 -- Match is now False if the entry we found did not match
9344 -- either a supplied Parameter_Types or Result_Types argument
9346 if Match then
9347 if No (Ent) then
9348 Ent := Def_Id;
9350 -- Ambiguous case, the flag Ambiguous shows if we already
9351 -- detected this and output the initial messages.
9353 else
9354 if not Ambiguous then
9355 Ambiguous := True;
9356 Error_Msg_Name_1 := Pname;
9357 Error_Msg_N
9358 ("pragma% does not uniquely identify subprogram!",
9360 Error_Msg_Sloc := Sloc (Ent);
9361 Error_Msg_N ("matching subprogram #!", N);
9362 Ent := Empty;
9363 end if;
9365 Error_Msg_Sloc := Sloc (Def_Id);
9366 Error_Msg_N ("matching subprogram #!", N);
9367 end if;
9368 end if;
9369 end if;
9371 Hom_Id := Homonym (Hom_Id);
9372 end loop;
9374 -- See if we found an entry
9376 if No (Ent) then
9377 if not Ambiguous then
9378 if Is_Generic_Subprogram (Entity (Arg_Internal)) then
9379 Error_Pragma
9380 ("pragma% cannot be given for generic subprogram");
9381 else
9382 Error_Pragma
9383 ("pragma% does not identify local subprogram");
9384 end if;
9385 end if;
9387 return;
9388 end if;
9390 -- Import pragmas must be for imported entities
9392 if Prag_Id = Pragma_Import_Function
9393 or else
9394 Prag_Id = Pragma_Import_Procedure
9395 or else
9396 Prag_Id = Pragma_Import_Valued_Procedure
9397 then
9398 if not Is_Imported (Ent) then
9399 Error_Pragma
9400 ("pragma Import or Interface must precede pragma%");
9401 end if;
9403 -- Here we have the Export case which can set the entity as exported
9405 -- But does not do so if the specified external name is null, since
9406 -- that is taken as a signal in DEC Ada 83 (with which we want to be
9407 -- compatible) to request no external name.
9409 elsif Nkind (Arg_External) = N_String_Literal
9410 and then String_Length (Strval (Arg_External)) = 0
9411 then
9412 null;
9414 -- In all other cases, set entity as exported
9416 else
9417 Set_Exported (Ent, Arg_Internal);
9418 end if;
9420 -- Special processing for Valued_Procedure cases
9422 if Prag_Id = Pragma_Import_Valued_Procedure
9423 or else
9424 Prag_Id = Pragma_Export_Valued_Procedure
9425 then
9426 Formal := First_Formal (Ent);
9428 if No (Formal) then
9429 Error_Pragma ("at least one parameter required for pragma%");
9431 elsif Ekind (Formal) /= E_Out_Parameter then
9432 Error_Pragma ("first parameter must have mode OUT for pragma%");
9434 else
9435 Set_Is_Valued_Procedure (Ent);
9436 end if;
9437 end if;
9439 Set_Extended_Import_Export_External_Name (Ent, Arg_External);
9441 -- Process Result_Mechanism argument if present. We have already
9442 -- checked that this is only allowed for the function case.
9444 if Present (Arg_Result_Mechanism) then
9445 Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
9446 end if;
9448 -- Process Mechanism parameter if present. Note that this parameter
9449 -- is not analyzed, and must not be analyzed since it is semantic
9450 -- nonsense, so we get it in exactly as the parser left it.
9452 if Present (Arg_Mechanism) then
9453 declare
9454 Formal : Entity_Id;
9455 Massoc : Node_Id;
9456 Mname : Node_Id;
9457 Choice : Node_Id;
9459 begin
9460 -- A single mechanism association without a formal parameter
9461 -- name is parsed as a parenthesized expression. All other
9462 -- cases are parsed as aggregates, so we rewrite the single
9463 -- parameter case as an aggregate for consistency.
9465 if Nkind (Arg_Mechanism) /= N_Aggregate
9466 and then Paren_Count (Arg_Mechanism) = 1
9467 then
9468 Rewrite (Arg_Mechanism,
9469 Make_Aggregate (Sloc (Arg_Mechanism),
9470 Expressions => New_List (
9471 Relocate_Node (Arg_Mechanism))));
9472 end if;
9474 -- Case of only mechanism name given, applies to all formals
9476 if Nkind (Arg_Mechanism) /= N_Aggregate then
9477 Formal := First_Formal (Ent);
9478 while Present (Formal) loop
9479 Set_Mechanism_Value (Formal, Arg_Mechanism);
9480 Next_Formal (Formal);
9481 end loop;
9483 -- Case of list of mechanism associations given
9485 else
9486 if Null_Record_Present (Arg_Mechanism) then
9487 Error_Pragma_Arg
9488 ("inappropriate form for Mechanism parameter",
9489 Arg_Mechanism);
9490 end if;
9492 -- Deal with positional ones first
9494 Formal := First_Formal (Ent);
9496 if Present (Expressions (Arg_Mechanism)) then
9497 Mname := First (Expressions (Arg_Mechanism));
9498 while Present (Mname) loop
9499 if No (Formal) then
9500 Error_Pragma_Arg
9501 ("too many mechanism associations", Mname);
9502 end if;
9504 Set_Mechanism_Value (Formal, Mname);
9505 Next_Formal (Formal);
9506 Next (Mname);
9507 end loop;
9508 end if;
9510 -- Deal with named entries
9512 if Present (Component_Associations (Arg_Mechanism)) then
9513 Massoc := First (Component_Associations (Arg_Mechanism));
9514 while Present (Massoc) loop
9515 Choice := First (Choices (Massoc));
9517 if Nkind (Choice) /= N_Identifier
9518 or else Present (Next (Choice))
9519 then
9520 Error_Pragma_Arg
9521 ("incorrect form for mechanism association",
9522 Massoc);
9523 end if;
9525 Formal := First_Formal (Ent);
9526 loop
9527 if No (Formal) then
9528 Error_Pragma_Arg
9529 ("parameter name & not present", Choice);
9530 end if;
9532 if Chars (Choice) = Chars (Formal) then
9533 Set_Mechanism_Value
9534 (Formal, Expression (Massoc));
9536 -- Set entity on identifier for proper tree
9537 -- structure.
9539 Set_Entity (Choice, Formal);
9541 exit;
9542 end if;
9544 Next_Formal (Formal);
9545 end loop;
9547 Next (Massoc);
9548 end loop;
9549 end if;
9550 end if;
9551 end;
9552 end if;
9553 end Process_Extended_Import_Export_Subprogram_Pragma;
9555 --------------------------
9556 -- Process_Generic_List --
9557 --------------------------
9559 procedure Process_Generic_List is
9560 Arg : Node_Id;
9561 Exp : Node_Id;
9563 begin
9564 Check_No_Identifiers;
9565 Check_At_Least_N_Arguments (1);
9567 -- Check all arguments are names of generic units or instances
9569 Arg := Arg1;
9570 while Present (Arg) loop
9571 Exp := Get_Pragma_Arg (Arg);
9572 Analyze (Exp);
9574 if not Is_Entity_Name (Exp)
9575 or else
9576 (not Is_Generic_Instance (Entity (Exp))
9577 and then
9578 not Is_Generic_Unit (Entity (Exp)))
9579 then
9580 Error_Pragma_Arg
9581 ("pragma% argument must be name of generic unit/instance",
9582 Arg);
9583 end if;
9585 Next (Arg);
9586 end loop;
9587 end Process_Generic_List;
9589 ------------------------------------
9590 -- Process_Import_Predefined_Type --
9591 ------------------------------------
9593 procedure Process_Import_Predefined_Type is
9594 Loc : constant Source_Ptr := Sloc (N);
9595 Elmt : Elmt_Id;
9596 Ftyp : Node_Id := Empty;
9597 Decl : Node_Id;
9598 Def : Node_Id;
9599 Nam : Name_Id;
9601 begin
9602 Nam := String_To_Name (Strval (Expression (Arg3)));
9604 Elmt := First_Elmt (Predefined_Float_Types);
9605 while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
9606 Next_Elmt (Elmt);
9607 end loop;
9609 Ftyp := Node (Elmt);
9611 if Present (Ftyp) then
9613 -- Don't build a derived type declaration, because predefined C
9614 -- types have no declaration anywhere, so cannot really be named.
9615 -- Instead build a full type declaration, starting with an
9616 -- appropriate type definition is built
9618 if Is_Floating_Point_Type (Ftyp) then
9619 Def := Make_Floating_Point_Definition (Loc,
9620 Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
9621 Make_Real_Range_Specification (Loc,
9622 Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
9623 Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
9625 -- Should never have a predefined type we cannot handle
9627 else
9628 raise Program_Error;
9629 end if;
9631 -- Build and insert a Full_Type_Declaration, which will be
9632 -- analyzed as soon as this list entry has been analyzed.
9634 Decl := Make_Full_Type_Declaration (Loc,
9635 Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
9636 Type_Definition => Def);
9638 Insert_After (N, Decl);
9639 Mark_Rewrite_Insertion (Decl);
9641 else
9642 Error_Pragma_Arg ("no matching type found for pragma%", Arg2);
9643 end if;
9644 end Process_Import_Predefined_Type;
9646 ---------------------------------
9647 -- Process_Import_Or_Interface --
9648 ---------------------------------
9650 procedure Process_Import_Or_Interface is
9651 C : Convention_Id;
9652 Def_Id : Entity_Id;
9653 Hom_Id : Entity_Id;
9655 begin
9656 -- In Relaxed_RM_Semantics, support old Ada 83 style:
9657 -- pragma Import (Entity, "external name");
9659 if Relaxed_RM_Semantics
9660 and then Arg_Count = 2
9661 and then Prag_Id = Pragma_Import
9662 and then Nkind (Expression (Arg2)) = N_String_Literal
9663 then
9664 C := Convention_C;
9665 Def_Id := Get_Pragma_Arg (Arg1);
9666 Analyze (Def_Id);
9668 if not Is_Entity_Name (Def_Id) then
9669 Error_Pragma_Arg ("entity name required", Arg1);
9670 end if;
9672 Def_Id := Entity (Def_Id);
9673 Kill_Size_Check_Code (Def_Id);
9674 if Ekind (Def_Id) /= E_Constant then
9675 Note_Possible_Modification
9676 (Get_Pragma_Arg (Arg1), Sure => False);
9677 end if;
9679 else
9680 Process_Convention (C, Def_Id);
9682 -- A pragma that applies to a Ghost entity becomes Ghost for the
9683 -- purposes of legality checks and removal of ignored Ghost code.
9685 Mark_Ghost_Pragma (N, Def_Id);
9686 Kill_Size_Check_Code (Def_Id);
9687 if Ekind (Def_Id) /= E_Constant then
9688 Note_Possible_Modification
9689 (Get_Pragma_Arg (Arg2), Sure => False);
9690 end if;
9691 end if;
9693 -- Various error checks
9695 if Ekind (Def_Id) in E_Variable | E_Constant then
9697 -- We do not permit Import to apply to a renaming declaration
9699 if Present (Renamed_Object (Def_Id)) then
9700 Error_Pragma_Arg
9701 ("pragma% not allowed for object renaming", Arg2);
9703 -- User initialization is not allowed for imported object, but
9704 -- the object declaration may contain a default initialization,
9705 -- that will be discarded. Note that an explicit initialization
9706 -- only counts if it comes from source, otherwise it is simply
9707 -- the code generator making an implicit initialization explicit.
9709 elsif Present (Expression (Parent (Def_Id)))
9710 and then Comes_From_Source
9711 (Original_Node (Expression (Parent (Def_Id))))
9712 then
9713 -- Set imported flag to prevent cascaded errors
9715 Set_Is_Imported (Def_Id);
9717 Error_Msg_Sloc := Sloc (Def_Id);
9718 Error_Pragma_Arg
9719 ("no initialization allowed for declaration of& #",
9720 "\imported entities cannot be initialized (RM B.1(24))",
9721 Arg2);
9723 else
9724 -- If the pragma comes from an aspect specification the
9725 -- Is_Imported flag has already been set.
9727 if not From_Aspect_Specification (N) then
9728 Set_Imported (Def_Id);
9729 end if;
9731 Process_Interface_Name (Def_Id, Arg3, Arg4, N);
9733 -- Note that we do not set Is_Public here. That's because we
9734 -- only want to set it if there is no address clause, and we
9735 -- don't know that yet, so we delay that processing till
9736 -- freeze time.
9738 -- pragma Import completes deferred constants
9740 if Ekind (Def_Id) = E_Constant then
9741 Set_Has_Completion (Def_Id);
9742 end if;
9744 -- It is not possible to import a constant of an unconstrained
9745 -- array type (e.g. string) because there is no simple way to
9746 -- write a meaningful subtype for it.
9748 if Is_Array_Type (Etype (Def_Id))
9749 and then not Is_Constrained (Etype (Def_Id))
9750 then
9751 Error_Msg_NE
9752 ("imported constant& must have a constrained subtype",
9753 N, Def_Id);
9754 end if;
9755 end if;
9757 elsif Is_Subprogram_Or_Generic_Subprogram (Def_Id) then
9759 -- If the name is overloaded, pragma applies to all of the denoted
9760 -- entities in the same declarative part, unless the pragma comes
9761 -- from an aspect specification or was generated by the compiler
9762 -- (such as for pragma Provide_Shift_Operators).
9764 Hom_Id := Def_Id;
9765 while Present (Hom_Id) loop
9767 Def_Id := Get_Base_Subprogram (Hom_Id);
9769 -- Ignore inherited subprograms because the pragma will apply
9770 -- to the parent operation, which is the one called.
9772 if Is_Overloadable (Def_Id)
9773 and then Present (Alias (Def_Id))
9774 then
9775 null;
9777 -- If it is not a subprogram, it must be in an outer scope and
9778 -- pragma does not apply.
9780 elsif not Is_Subprogram_Or_Generic_Subprogram (Def_Id) then
9781 null;
9783 -- The pragma does not apply to primitives of interfaces
9785 elsif Is_Dispatching_Operation (Def_Id)
9786 and then Present (Find_Dispatching_Type (Def_Id))
9787 and then Is_Interface (Find_Dispatching_Type (Def_Id))
9788 then
9789 null;
9791 -- Verify that the homonym is in the same declarative part (not
9792 -- just the same scope). If the pragma comes from an aspect
9793 -- specification we know that it is part of the declaration.
9795 elsif (No (Unit_Declaration_Node (Def_Id))
9796 or else Parent (Unit_Declaration_Node (Def_Id)) /=
9797 Parent (N))
9798 and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
9799 and then not From_Aspect_Specification (N)
9800 then
9801 exit;
9803 else
9804 -- If the pragma comes from an aspect specification the
9805 -- Is_Imported flag has already been set.
9807 if not From_Aspect_Specification (N) then
9808 Set_Imported (Def_Id);
9809 end if;
9811 -- Reject an Import applied to an abstract subprogram
9813 if Is_Subprogram (Def_Id)
9814 and then Is_Abstract_Subprogram (Def_Id)
9815 then
9816 Error_Msg_Sloc := Sloc (Def_Id);
9817 Error_Msg_NE
9818 ("cannot import abstract subprogram& declared#",
9819 Arg2, Def_Id);
9820 end if;
9822 -- Special processing for Convention_Intrinsic
9824 if C = Convention_Intrinsic then
9826 -- Link_Name argument not allowed for intrinsic
9828 Check_No_Link_Name;
9830 Set_Is_Intrinsic_Subprogram (Def_Id);
9832 -- If no external name is present, then check that this
9833 -- is a valid intrinsic subprogram. If an external name
9834 -- is present, then this is handled by the back end.
9836 if No (Arg3) then
9837 Check_Intrinsic_Subprogram
9838 (Def_Id, Get_Pragma_Arg (Arg2));
9839 end if;
9840 end if;
9842 -- Verify that the subprogram does not have a completion
9843 -- through a renaming declaration. For other completions the
9844 -- pragma appears as a too late representation.
9846 declare
9847 Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
9849 begin
9850 if Present (Decl)
9851 and then Nkind (Decl) = N_Subprogram_Declaration
9852 and then Present (Corresponding_Body (Decl))
9853 and then Nkind (Unit_Declaration_Node
9854 (Corresponding_Body (Decl))) =
9855 N_Subprogram_Renaming_Declaration
9856 then
9857 Error_Msg_Sloc := Sloc (Def_Id);
9858 Error_Msg_NE
9859 ("cannot import&, renaming already provided for "
9860 & "declaration #", N, Def_Id);
9861 end if;
9862 end;
9864 -- If the pragma comes from an aspect specification, there
9865 -- must be an Import aspect specified as well. In the rare
9866 -- case where Import is set to False, the subprogram needs
9867 -- to have a local completion.
9869 declare
9870 Imp_Aspect : constant Node_Id :=
9871 Find_Aspect (Def_Id, Aspect_Import);
9872 Expr : Node_Id;
9874 begin
9875 if Present (Imp_Aspect)
9876 and then Present (Expression (Imp_Aspect))
9877 then
9878 Expr := Expression (Imp_Aspect);
9879 Analyze_And_Resolve (Expr, Standard_Boolean);
9881 if Is_Entity_Name (Expr)
9882 and then Entity (Expr) = Standard_True
9883 then
9884 Set_Has_Completion (Def_Id);
9885 end if;
9887 -- If there is no expression, the default is True, as for
9888 -- all boolean aspects. Same for the older pragma.
9890 else
9891 Set_Has_Completion (Def_Id);
9892 end if;
9893 end;
9895 Process_Interface_Name (Def_Id, Arg3, Arg4, N);
9896 end if;
9898 if Is_Compilation_Unit (Hom_Id) then
9900 -- Its possible homonyms are not affected by the pragma.
9901 -- Such homonyms might be present in the context of other
9902 -- units being compiled.
9904 exit;
9906 elsif From_Aspect_Specification (N) then
9907 exit;
9909 -- If the pragma was created by the compiler, then we don't
9910 -- want it to apply to other homonyms. This kind of case can
9911 -- occur when using pragma Provide_Shift_Operators, which
9912 -- generates implicit shift and rotate operators with Import
9913 -- pragmas that might apply to earlier explicit or implicit
9914 -- declarations marked with Import (for example, coming from
9915 -- an earlier pragma Provide_Shift_Operators for another type),
9916 -- and we don't generally want other homonyms being treated
9917 -- as imported or the pragma flagged as an illegal duplicate.
9919 elsif not Comes_From_Source (N) then
9920 exit;
9922 else
9923 Hom_Id := Homonym (Hom_Id);
9924 end if;
9925 end loop;
9927 -- Import a CPP class
9929 elsif C = Convention_CPP
9930 and then (Is_Record_Type (Def_Id)
9931 or else Ekind (Def_Id) = E_Incomplete_Type)
9932 then
9933 if Ekind (Def_Id) = E_Incomplete_Type then
9934 if Present (Full_View (Def_Id)) then
9935 Def_Id := Full_View (Def_Id);
9937 else
9938 Error_Msg_N
9939 ("cannot import 'C'P'P type before full declaration seen",
9940 Get_Pragma_Arg (Arg2));
9942 -- Although we have reported the error we decorate it as
9943 -- CPP_Class to avoid reporting spurious errors
9945 Set_Is_CPP_Class (Def_Id);
9946 return;
9947 end if;
9948 end if;
9950 -- Types treated as CPP classes must be declared limited (note:
9951 -- this used to be a warning but there is no real benefit to it
9952 -- since we did effectively intend to treat the type as limited
9953 -- anyway).
9955 if not Is_Limited_Type (Def_Id) then
9956 Error_Msg_N
9957 ("imported 'C'P'P type must be limited",
9958 Get_Pragma_Arg (Arg2));
9959 end if;
9961 if Etype (Def_Id) /= Def_Id
9962 and then not Is_CPP_Class (Root_Type (Def_Id))
9963 then
9964 Error_Msg_N ("root type must be a 'C'P'P type", Arg1);
9965 end if;
9967 Set_Is_CPP_Class (Def_Id);
9969 -- Imported CPP types must not have discriminants (because C++
9970 -- classes do not have discriminants).
9972 if Has_Discriminants (Def_Id) then
9973 Error_Msg_N
9974 ("imported 'C'P'P type cannot have discriminants",
9975 First (Discriminant_Specifications
9976 (Declaration_Node (Def_Id))));
9977 end if;
9979 -- Check that components of imported CPP types do not have default
9980 -- expressions. For private types this check is performed when the
9981 -- full view is analyzed (see Process_Full_View).
9983 if not Is_Private_Type (Def_Id) then
9984 Check_CPP_Type_Has_No_Defaults (Def_Id);
9985 end if;
9987 -- Import a CPP exception
9989 elsif C = Convention_CPP
9990 and then Ekind (Def_Id) = E_Exception
9991 then
9992 if No (Arg3) then
9993 Error_Pragma_Arg
9994 ("'External_'Name arguments is required for 'Cpp exception",
9995 Arg3);
9996 else
9997 -- As only a string is allowed, Check_Arg_Is_External_Name
9998 -- isn't called.
10000 Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
10001 end if;
10003 if Present (Arg4) then
10004 Error_Pragma_Arg
10005 ("Link_Name argument not allowed for imported Cpp exception",
10006 Arg4);
10007 end if;
10009 -- Do not call Set_Interface_Name as the name of the exception
10010 -- shouldn't be modified (and in particular it shouldn't be
10011 -- the External_Name). For exceptions, the External_Name is the
10012 -- name of the RTTI structure.
10014 -- ??? Emit an error if pragma Import/Export_Exception is present
10016 elsif Nkind (Parent (Def_Id)) = N_Incomplete_Type_Declaration then
10017 Check_No_Link_Name;
10018 Check_Arg_Count (3);
10019 Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
10021 Process_Import_Predefined_Type;
10023 -- Emit an error unless Relaxed_RM_Semantics since some legacy Ada
10024 -- compilers may accept more cases, e.g. JGNAT allowed importing
10025 -- a Java package.
10027 elsif not Relaxed_RM_Semantics then
10028 if From_Aspect_Specification (N) then
10029 Error_Pragma_Arg
10030 ("entity for aspect% must be object, subprogram "
10031 & "or incomplete type",
10032 Arg2);
10033 else
10034 Error_Pragma_Arg
10035 ("second argument of pragma% must be object, subprogram "
10036 & "or incomplete type",
10037 Arg2);
10038 end if;
10039 end if;
10041 -- If this pragma applies to a compilation unit, then the unit, which
10042 -- is a subprogram, does not require (or allow) a body. We also do
10043 -- not need to elaborate imported procedures.
10045 if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
10046 declare
10047 Cunit : constant Node_Id := Parent (Parent (N));
10048 begin
10049 Set_Body_Required (Cunit, False);
10050 end;
10051 end if;
10052 end Process_Import_Or_Interface;
10054 --------------------
10055 -- Process_Inline --
10056 --------------------
10058 procedure Process_Inline (Status : Inline_Status) is
10059 Applies : Boolean;
10060 Assoc : Node_Id;
10061 Decl : Node_Id;
10062 Subp : Entity_Id;
10063 Subp_Id : Node_Id;
10065 Ghost_Error_Posted : Boolean := False;
10066 -- Flag set when an error concerning the illegal mix of Ghost and
10067 -- non-Ghost subprograms is emitted.
10069 Ghost_Id : Entity_Id := Empty;
10070 -- The entity of the first Ghost subprogram encountered while
10071 -- processing the arguments of the pragma.
10073 procedure Check_Inline_Always_Placement (Spec_Id : Entity_Id);
10074 -- Verify the placement of pragma Inline_Always with respect to the
10075 -- initial declaration of subprogram Spec_Id.
10077 function Inlining_Not_Possible (Subp : Entity_Id) return Boolean;
10078 -- Returns True if it can be determined at this stage that inlining
10079 -- is not possible, for example if the body is available and contains
10080 -- exception handlers, we prevent inlining, since otherwise we can
10081 -- get undefined symbols at link time. This function also emits a
10082 -- warning if the pragma appears too late.
10084 -- ??? is business with link symbols still valid, or does it relate
10085 -- to front end ZCX which is being phased out ???
10087 procedure Make_Inline (Subp : Entity_Id);
10088 -- Subp is the defining unit name of the subprogram declaration. If
10089 -- the pragma is valid, call Set_Inline_Flags on Subp, as well as on
10090 -- the corresponding body, if there is one present.
10092 procedure Set_Inline_Flags (Subp : Entity_Id);
10093 -- Set Has_Pragma_{No_Inline,Inline,Inline_Always} flag on Subp.
10094 -- Also set or clear Is_Inlined flag on Subp depending on Status.
10096 -----------------------------------
10097 -- Check_Inline_Always_Placement --
10098 -----------------------------------
10100 procedure Check_Inline_Always_Placement (Spec_Id : Entity_Id) is
10101 Spec_Decl : constant Node_Id := Unit_Declaration_Node (Spec_Id);
10103 function Compilation_Unit_OK return Boolean;
10104 pragma Inline (Compilation_Unit_OK);
10105 -- Determine whether pragma Inline_Always applies to a compatible
10106 -- compilation unit denoted by Spec_Id.
10108 function Declarative_List_OK return Boolean;
10109 pragma Inline (Declarative_List_OK);
10110 -- Determine whether the initial declaration of subprogram Spec_Id
10111 -- and the pragma appear in compatible declarative lists.
10113 function Subprogram_Body_OK return Boolean;
10114 pragma Inline (Subprogram_Body_OK);
10115 -- Determine whether pragma Inline_Always applies to a compatible
10116 -- subprogram body denoted by Spec_Id.
10118 -------------------------
10119 -- Compilation_Unit_OK --
10120 -------------------------
10122 function Compilation_Unit_OK return Boolean is
10123 Comp_Unit : constant Node_Id := Parent (Spec_Decl);
10125 begin
10126 -- The pragma appears after the initial declaration of a
10127 -- compilation unit.
10129 -- procedure Comp_Unit;
10130 -- pragma Inline_Always (Comp_Unit);
10132 -- Note that for compatibility reasons, the following case is
10133 -- also accepted.
10135 -- procedure Stand_Alone_Body_Comp_Unit is
10136 -- ...
10137 -- end Stand_Alone_Body_Comp_Unit;
10138 -- pragma Inline_Always (Stand_Alone_Body_Comp_Unit);
10140 return
10141 Nkind (Comp_Unit) = N_Compilation_Unit
10142 and then Present (Aux_Decls_Node (Comp_Unit))
10143 and then Is_List_Member (N)
10144 and then List_Containing (N) =
10145 Pragmas_After (Aux_Decls_Node (Comp_Unit));
10146 end Compilation_Unit_OK;
10148 -------------------------
10149 -- Declarative_List_OK --
10150 -------------------------
10152 function Declarative_List_OK return Boolean is
10153 Context : constant Node_Id := Parent (Spec_Decl);
10155 Init_Decl : Node_Id;
10156 Init_List : List_Id;
10157 Prag_List : List_Id;
10159 begin
10160 -- Determine the proper initial declaration. In general this is
10161 -- the declaration node of the subprogram except when the input
10162 -- denotes a generic instantiation.
10164 -- procedure Inst is new Gen;
10165 -- pragma Inline_Always (Inst);
10167 -- In this case the original subprogram is moved inside an
10168 -- anonymous package while pragma Inline_Always remains at the
10169 -- level of the anonymous package. Use the declaration of the
10170 -- package because it reflects the placement of the original
10171 -- instantiation.
10173 -- package Anon_Pack is
10174 -- procedure Inst is ... end Inst; -- original
10175 -- end Anon_Pack;
10177 -- procedure Inst renames Anon_Pack.Inst;
10178 -- pragma Inline_Always (Inst);
10180 if Is_Generic_Instance (Spec_Id) then
10181 Init_Decl := Parent (Parent (Spec_Decl));
10182 pragma Assert (Nkind (Init_Decl) = N_Package_Declaration);
10183 else
10184 Init_Decl := Spec_Decl;
10185 end if;
10187 if Is_List_Member (Init_Decl) and then Is_List_Member (N) then
10188 Init_List := List_Containing (Init_Decl);
10189 Prag_List := List_Containing (N);
10191 -- The pragma and then initial declaration appear within the
10192 -- same declarative list.
10194 if Init_List = Prag_List then
10195 return True;
10197 -- A special case of the above is when both the pragma and
10198 -- the initial declaration appear in different lists of a
10199 -- package spec, protected definition, or a task definition.
10201 -- package Pack is
10202 -- procedure Proc;
10203 -- private
10204 -- pragma Inline_Always (Proc);
10205 -- end Pack;
10207 elsif Nkind (Context) in N_Package_Specification
10208 | N_Protected_Definition
10209 | N_Task_Definition
10210 and then Init_List = Visible_Declarations (Context)
10211 and then Prag_List = Private_Declarations (Context)
10212 then
10213 return True;
10214 end if;
10215 end if;
10217 return False;
10218 end Declarative_List_OK;
10220 ------------------------
10221 -- Subprogram_Body_OK --
10222 ------------------------
10224 function Subprogram_Body_OK return Boolean is
10225 Body_Decl : Node_Id;
10227 begin
10228 -- The pragma appears within the declarative list of a stand-
10229 -- alone subprogram body.
10231 -- procedure Stand_Alone_Body is
10232 -- pragma Inline_Always (Stand_Alone_Body);
10233 -- begin
10234 -- ...
10235 -- end Stand_Alone_Body;
10237 -- The compiler creates a dummy spec in this case, however the
10238 -- pragma remains within the declarative list of the body.
10240 if Nkind (Spec_Decl) = N_Subprogram_Declaration
10241 and then not Comes_From_Source (Spec_Decl)
10242 and then Present (Corresponding_Body (Spec_Decl))
10243 then
10244 Body_Decl :=
10245 Unit_Declaration_Node (Corresponding_Body (Spec_Decl));
10247 if Present (Declarations (Body_Decl))
10248 and then Is_List_Member (N)
10249 and then List_Containing (N) = Declarations (Body_Decl)
10250 then
10251 return True;
10252 end if;
10253 end if;
10255 return False;
10256 end Subprogram_Body_OK;
10258 -- Start of processing for Check_Inline_Always_Placement
10260 begin
10261 -- This check is relevant only for pragma Inline_Always
10263 if Pname /= Name_Inline_Always then
10264 return;
10266 -- Nothing to do when the pragma is internally generated on the
10267 -- assumption that it is properly placed.
10269 elsif not Comes_From_Source (N) then
10270 return;
10272 -- Nothing to do for internally generated subprograms that act
10273 -- as accidental homonyms of a source subprogram being inlined.
10275 elsif not Comes_From_Source (Spec_Id) then
10276 return;
10278 -- Nothing to do for generic formal subprograms that act as
10279 -- homonyms of another source subprogram being inlined.
10281 elsif Is_Formal_Subprogram (Spec_Id) then
10282 return;
10284 elsif Compilation_Unit_OK
10285 or else Declarative_List_OK
10286 or else Subprogram_Body_OK
10287 then
10288 return;
10289 end if;
10291 -- At this point it is known that the pragma applies to or appears
10292 -- within a completing body, a completing stub, or a subunit.
10294 Error_Msg_Name_1 := Pname;
10295 Error_Msg_Name_2 := Chars (Spec_Id);
10296 Error_Msg_Sloc := Sloc (Spec_Id);
10298 Error_Msg_N
10299 ("pragma % must appear on initial declaration of subprogram "
10300 & "% defined #", N);
10301 end Check_Inline_Always_Placement;
10303 ---------------------------
10304 -- Inlining_Not_Possible --
10305 ---------------------------
10307 function Inlining_Not_Possible (Subp : Entity_Id) return Boolean is
10308 Decl : constant Node_Id := Unit_Declaration_Node (Subp);
10309 Stats : Node_Id;
10311 begin
10312 if Nkind (Decl) = N_Subprogram_Body then
10313 Stats := Handled_Statement_Sequence (Decl);
10314 return Present (Exception_Handlers (Stats))
10315 or else Present (At_End_Proc (Stats));
10317 elsif Nkind (Decl) = N_Subprogram_Declaration
10318 and then Present (Corresponding_Body (Decl))
10319 then
10320 if Analyzed (Corresponding_Body (Decl)) then
10321 Error_Msg_N ("pragma appears too late, ignored??", N);
10322 return True;
10324 -- If the subprogram is a renaming as body, the body is just a
10325 -- call to the renamed subprogram, and inlining is trivially
10326 -- possible.
10328 elsif
10329 Nkind (Unit_Declaration_Node (Corresponding_Body (Decl))) =
10330 N_Subprogram_Renaming_Declaration
10331 then
10332 return False;
10334 else
10335 Stats :=
10336 Handled_Statement_Sequence
10337 (Unit_Declaration_Node (Corresponding_Body (Decl)));
10339 return
10340 Present (Exception_Handlers (Stats))
10341 or else Present (At_End_Proc (Stats));
10342 end if;
10344 else
10345 -- If body is not available, assume the best, the check is
10346 -- performed again when compiling enclosing package bodies.
10348 return False;
10349 end if;
10350 end Inlining_Not_Possible;
10352 -----------------
10353 -- Make_Inline --
10354 -----------------
10356 procedure Make_Inline (Subp : Entity_Id) is
10357 Kind : constant Entity_Kind := Ekind (Subp);
10358 Inner_Subp : Entity_Id := Subp;
10360 begin
10361 -- Ignore if bad type, avoid cascaded error
10363 if Etype (Subp) = Any_Type then
10364 Applies := True;
10365 return;
10367 -- If inlining is not possible, for now do not treat as an error
10369 elsif Status /= Suppressed
10370 and then Front_End_Inlining
10371 and then Inlining_Not_Possible (Subp)
10372 then
10373 Applies := True;
10374 return;
10376 -- Here we have a candidate for inlining, but we must exclude
10377 -- derived operations. Otherwise we would end up trying to inline
10378 -- a phantom declaration, and the result would be to drag in a
10379 -- body which has no direct inlining associated with it. That
10380 -- would not only be inefficient but would also result in the
10381 -- backend doing cross-unit inlining in cases where it was
10382 -- definitely inappropriate to do so.
10384 -- However, a simple Comes_From_Source test is insufficient, since
10385 -- we do want to allow inlining of generic instances which also do
10386 -- not come from source. We also need to recognize specs generated
10387 -- by the front-end for bodies that carry the pragma. Finally,
10388 -- predefined operators do not come from source but are not
10389 -- inlineable either.
10391 elsif Is_Generic_Instance (Subp)
10392 or else Parent_Kind (Parent (Subp)) = N_Subprogram_Declaration
10393 then
10394 null;
10396 elsif not Comes_From_Source (Subp)
10397 and then Scope (Subp) /= Standard_Standard
10398 then
10399 Applies := True;
10400 return;
10401 end if;
10403 -- The referenced entity must either be the enclosing entity, or
10404 -- an entity declared within the current open scope.
10406 if Present (Scope (Subp))
10407 and then Scope (Subp) /= Current_Scope
10408 and then Subp /= Current_Scope
10409 then
10410 Error_Pragma_Arg
10411 ("argument of% must be entity in current scope", Assoc);
10412 end if;
10414 -- Processing for procedure, operator or function. If subprogram
10415 -- is aliased (as for an instance) indicate that the renamed
10416 -- entity (if declared in the same unit) is inlined.
10417 -- If this is the anonymous subprogram created for a subprogram
10418 -- instance, the inlining applies to it directly. Otherwise we
10419 -- retrieve it as the alias of the visible subprogram instance.
10421 if Is_Subprogram (Subp) then
10423 -- Ensure that pragma Inline_Always is associated with the
10424 -- initial declaration of the subprogram.
10426 Check_Inline_Always_Placement (Subp);
10428 if Is_Wrapper_Package (Scope (Subp)) then
10429 Inner_Subp := Subp;
10430 else
10431 Inner_Subp := Ultimate_Alias (Inner_Subp);
10432 end if;
10434 if In_Same_Source_Unit (Subp, Inner_Subp) then
10435 Set_Inline_Flags (Inner_Subp);
10437 if Present (Parent (Inner_Subp)) then
10438 Decl := Parent (Parent (Inner_Subp));
10439 else
10440 Decl := Empty;
10441 end if;
10443 if Nkind (Decl) = N_Subprogram_Declaration
10444 and then Present (Corresponding_Body (Decl))
10445 then
10446 Set_Inline_Flags (Corresponding_Body (Decl));
10448 elsif Is_Generic_Instance (Subp)
10449 and then Comes_From_Source (Subp)
10450 then
10451 -- Indicate that the body needs to be created for
10452 -- inlining subsequent calls. The instantiation node
10453 -- follows the declaration of the wrapper package
10454 -- created for it. The subprogram that requires the
10455 -- body is the anonymous one in the wrapper package.
10457 if Scope (Subp) /= Standard_Standard
10458 and then
10459 Need_Subprogram_Instance_Body
10460 (Next (Unit_Declaration_Node
10461 (Scope (Alias (Subp)))), Subp)
10462 then
10463 null;
10464 end if;
10466 -- Inline is a program unit pragma (RM 10.1.5) and cannot
10467 -- appear in a formal part to apply to a formal subprogram.
10468 -- Do not apply check within an instance or a formal package
10469 -- the test will have been applied to the original generic.
10471 elsif Nkind (Decl) in N_Formal_Subprogram_Declaration
10472 and then In_Same_List (Decl, N)
10473 and then not In_Instance
10474 then
10475 Error_Msg_N
10476 ("Inline cannot apply to a formal subprogram", N);
10477 end if;
10478 end if;
10480 Applies := True;
10482 -- For a generic subprogram set flag as well, for use at the point
10483 -- of instantiation, to determine whether the body should be
10484 -- generated.
10486 elsif Is_Generic_Subprogram (Subp) then
10487 Set_Inline_Flags (Subp);
10488 Applies := True;
10490 -- Literals are by definition inlined
10492 elsif Kind = E_Enumeration_Literal then
10493 null;
10495 -- Anything else is an error
10497 else
10498 Error_Pragma_Arg
10499 ("expect subprogram name for pragma%", Assoc);
10500 end if;
10501 end Make_Inline;
10503 ----------------------
10504 -- Set_Inline_Flags --
10505 ----------------------
10507 procedure Set_Inline_Flags (Subp : Entity_Id) is
10508 begin
10509 -- First set the Has_Pragma_XXX flags and issue the appropriate
10510 -- errors and warnings for suspicious combinations.
10512 if Prag_Id = Pragma_No_Inline then
10513 if Has_Pragma_Inline_Always (Subp) then
10514 Error_Msg_N
10515 ("Inline_Always and No_Inline are mutually exclusive", N);
10516 elsif Has_Pragma_Inline (Subp) then
10517 Error_Msg_NE
10518 ("Inline and No_Inline both specified for& ??",
10519 N, Entity (Subp_Id));
10520 end if;
10522 Set_Has_Pragma_No_Inline (Subp);
10523 else
10524 if Prag_Id = Pragma_Inline_Always then
10525 if Has_Pragma_No_Inline (Subp) then
10526 Error_Msg_N
10527 ("Inline_Always and No_Inline are mutually exclusive",
10529 end if;
10531 Set_Has_Pragma_Inline_Always (Subp);
10532 else
10533 if Has_Pragma_No_Inline (Subp) then
10534 Error_Msg_NE
10535 ("Inline and No_Inline both specified for& ??",
10536 N, Entity (Subp_Id));
10537 end if;
10538 end if;
10540 Set_Has_Pragma_Inline (Subp);
10541 end if;
10543 -- Then adjust the Is_Inlined flag. It can never be set if the
10544 -- subprogram is subject to pragma No_Inline.
10546 case Status is
10547 when Suppressed =>
10548 Set_Is_Inlined (Subp, False);
10550 when Disabled =>
10551 null;
10553 when Enabled =>
10554 if not Has_Pragma_No_Inline (Subp) then
10555 Set_Is_Inlined (Subp, True);
10556 end if;
10557 end case;
10559 -- A pragma that applies to a Ghost entity becomes Ghost for the
10560 -- purposes of legality checks and removal of ignored Ghost code.
10562 Mark_Ghost_Pragma (N, Subp);
10564 -- Capture the entity of the first Ghost subprogram being
10565 -- processed for error detection purposes.
10567 if Is_Ghost_Entity (Subp) then
10568 if No (Ghost_Id) then
10569 Ghost_Id := Subp;
10570 end if;
10572 -- Otherwise the subprogram is non-Ghost. It is illegal to mix
10573 -- references to Ghost and non-Ghost entities (SPARK RM 6.9).
10575 elsif Present (Ghost_Id) and then not Ghost_Error_Posted then
10576 Ghost_Error_Posted := True;
10578 Error_Msg_Name_1 := Pname;
10579 Error_Msg_N
10580 ("pragma % cannot mention ghost and non-ghost subprograms",
10583 Error_Msg_Sloc := Sloc (Ghost_Id);
10584 Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
10586 Error_Msg_Sloc := Sloc (Subp);
10587 Error_Msg_NE ("\& # declared as non-ghost", N, Subp);
10588 end if;
10589 end Set_Inline_Flags;
10591 -- Start of processing for Process_Inline
10593 begin
10594 -- An inlined subprogram may grant access to its private enclosing
10595 -- context depending on the placement of its body. From elaboration
10596 -- point of view, the flow of execution may enter this private
10597 -- context, and then reach an external unit, thus producing a
10598 -- dependency on that external unit. For such a path to be properly
10599 -- discovered and encoded in the ALI file of the main unit, let the
10600 -- ABE mechanism process the body of the main unit, and encode all
10601 -- relevant invocation constructs and the relations between them.
10603 Mark_Save_Invocation_Graph_Of_Body;
10605 Check_No_Identifiers;
10606 Check_At_Least_N_Arguments (1);
10608 if Status = Enabled then
10609 Inline_Processing_Required := True;
10610 end if;
10612 Assoc := Arg1;
10613 while Present (Assoc) loop
10614 Subp_Id := Get_Pragma_Arg (Assoc);
10615 Analyze (Subp_Id);
10616 Applies := False;
10618 if Is_Entity_Name (Subp_Id) then
10619 Subp := Entity (Subp_Id);
10621 if Subp = Any_Id then
10623 -- If previous error, avoid cascaded errors
10625 Check_Error_Detected;
10626 Applies := True;
10628 else
10629 -- Check for RM 13.1(9.2/4): If a [...] aspect_specification
10630 -- is given that directly specifies an aspect of an entity,
10631 -- then it is illegal to give another [...]
10632 -- aspect_specification that directly specifies the same
10633 -- aspect of the entity.
10634 -- We only check Subp directly as per "directly specifies"
10635 -- above and because the case of pragma Inline is really
10636 -- special given its pre aspect usage.
10638 Check_Duplicate_Pragma (Subp);
10639 Record_Rep_Item (Subp, N);
10641 Make_Inline (Subp);
10643 -- For the pragma case, climb homonym chain. This is
10644 -- what implements allowing the pragma in the renaming
10645 -- case, with the result applying to the ancestors, and
10646 -- also allows Inline to apply to all previous homonyms.
10648 if not From_Aspect_Specification (N) then
10649 while Present (Homonym (Subp))
10650 and then Scope (Homonym (Subp)) = Current_Scope
10651 loop
10652 Subp := Homonym (Subp);
10653 Make_Inline (Subp);
10654 end loop;
10655 end if;
10656 end if;
10657 end if;
10659 if not Applies then
10660 Error_Pragma_Arg ("inappropriate argument for pragma%", Assoc);
10661 end if;
10663 Next (Assoc);
10664 end loop;
10666 -- If the context is a package declaration, the pragma indicates
10667 -- that inlining will require the presence of the corresponding
10668 -- body. (this may be further refined).
10670 if not In_Instance
10671 and then Nkind (Unit (Cunit (Current_Sem_Unit))) =
10672 N_Package_Declaration
10673 then
10674 Set_Body_Needed_For_Inlining (Cunit_Entity (Current_Sem_Unit));
10675 end if;
10676 end Process_Inline;
10678 ----------------------------
10679 -- Process_Interface_Name --
10680 ----------------------------
10682 procedure Process_Interface_Name
10683 (Subprogram_Def : Entity_Id;
10684 Ext_Arg : Node_Id;
10685 Link_Arg : Node_Id;
10686 Prag : Node_Id)
10688 Ext_Nam : Node_Id;
10689 Link_Nam : Node_Id;
10690 String_Val : String_Id;
10692 procedure Check_Form_Of_Interface_Name (SN : Node_Id);
10693 -- SN is a string literal node for an interface name. This routine
10694 -- performs some minimal checks that the name is reasonable. In
10695 -- particular that no spaces or other obviously incorrect characters
10696 -- appear. This is only a warning, since any characters are allowed.
10698 ----------------------------------
10699 -- Check_Form_Of_Interface_Name --
10700 ----------------------------------
10702 procedure Check_Form_Of_Interface_Name (SN : Node_Id) is
10703 S : constant String_Id := Strval (Expr_Value_S (SN));
10704 SL : constant Nat := String_Length (S);
10705 C : Char_Code;
10707 begin
10708 if SL = 0 then
10709 Error_Msg_N ("interface name cannot be null string", SN);
10710 end if;
10712 for J in 1 .. SL loop
10713 C := Get_String_Char (S, J);
10715 -- Look for dubious character and issue unconditional warning.
10716 -- Definitely dubious if not in character range.
10718 if not In_Character_Range (C)
10720 -- Commas, spaces and (back)slashes are dubious
10722 or else Get_Character (C) = ','
10723 or else Get_Character (C) = '\'
10724 or else Get_Character (C) = ' '
10725 or else Get_Character (C) = '/'
10726 then
10727 Error_Msg
10728 ("??interface name contains illegal character",
10729 Sloc (SN) + Source_Ptr (J));
10730 end if;
10731 end loop;
10732 end Check_Form_Of_Interface_Name;
10734 -- Start of processing for Process_Interface_Name
10736 begin
10737 -- If we are looking at a pragma that comes from an aspect then it
10738 -- needs to have its corresponding aspect argument expressions
10739 -- analyzed in addition to the generated pragma so that aspects
10740 -- within generic units get properly resolved.
10742 if Present (Prag) and then From_Aspect_Specification (Prag) then
10743 declare
10744 Asp : constant Node_Id := Corresponding_Aspect (Prag);
10745 Dummy_1 : Node_Id;
10746 Dummy_2 : Node_Id;
10747 Dummy_3 : Node_Id;
10748 EN : Node_Id;
10749 LN : Node_Id;
10751 begin
10752 -- Obtain all interfacing aspects used to construct the pragma
10754 Get_Interfacing_Aspects
10755 (Asp, Dummy_1, EN, Dummy_2, Dummy_3, LN);
10757 -- Analyze the expression of aspect External_Name
10759 if Present (EN) then
10760 Analyze (Expression (EN));
10761 end if;
10763 -- Analyze the expressio of aspect Link_Name
10765 if Present (LN) then
10766 Analyze (Expression (LN));
10767 end if;
10768 end;
10769 end if;
10771 if No (Link_Arg) then
10772 if No (Ext_Arg) then
10773 return;
10775 elsif Chars (Ext_Arg) = Name_Link_Name then
10776 Ext_Nam := Empty;
10777 Link_Nam := Expression (Ext_Arg);
10779 else
10780 Check_Optional_Identifier (Ext_Arg, Name_External_Name);
10781 Ext_Nam := Expression (Ext_Arg);
10782 Link_Nam := Empty;
10783 end if;
10785 else
10786 Check_Optional_Identifier (Ext_Arg, Name_External_Name);
10787 Check_Optional_Identifier (Link_Arg, Name_Link_Name);
10788 Ext_Nam := Expression (Ext_Arg);
10789 Link_Nam := Expression (Link_Arg);
10790 end if;
10792 -- Check expressions for external name and link name are static
10794 if Present (Ext_Nam) then
10795 Check_Arg_Is_OK_Static_Expression (Ext_Nam, Standard_String);
10796 Check_Form_Of_Interface_Name (Ext_Nam);
10798 -- Verify that external name is not the name of a local entity,
10799 -- which would hide the imported one and could lead to run-time
10800 -- surprises. The problem can only arise for entities declared in
10801 -- a package body (otherwise the external name is fully qualified
10802 -- and will not conflict).
10804 declare
10805 Nam : Name_Id;
10806 E : Entity_Id;
10807 Par : Node_Id;
10809 begin
10810 if Prag_Id = Pragma_Import then
10811 Nam := String_To_Name (Strval (Expr_Value_S (Ext_Nam)));
10812 E := Entity_Id (Get_Name_Table_Int (Nam));
10814 if Nam /= Chars (Subprogram_Def)
10815 and then Present (E)
10816 and then not Is_Overloadable (E)
10817 and then Is_Immediately_Visible (E)
10818 and then not Is_Imported (E)
10819 and then Ekind (Scope (E)) = E_Package
10820 then
10821 Par := Parent (E);
10822 while Present (Par) loop
10823 if Nkind (Par) = N_Package_Body then
10824 Error_Msg_Sloc := Sloc (E);
10825 Error_Msg_NE
10826 ("imported entity is hidden by & declared#",
10827 Ext_Arg, E);
10828 exit;
10829 end if;
10831 Par := Parent (Par);
10832 end loop;
10833 end if;
10834 end if;
10835 end;
10836 end if;
10838 if Present (Link_Nam) then
10839 Check_Arg_Is_OK_Static_Expression (Link_Nam, Standard_String);
10840 Check_Form_Of_Interface_Name (Link_Nam);
10841 end if;
10843 -- If there is no link name, just set the external name
10845 if No (Link_Nam) then
10846 Link_Nam := Adjust_External_Name_Case (Expr_Value_S (Ext_Nam));
10848 -- For the Link_Name case, the given literal is preceded by an
10849 -- asterisk, which indicates to GCC that the given name should be
10850 -- taken literally, and in particular that no prepending of
10851 -- underlines should occur, even in systems where this is the
10852 -- normal default.
10854 else
10855 Start_String;
10856 Store_String_Char (Get_Char_Code ('*'));
10857 String_Val := Strval (Expr_Value_S (Link_Nam));
10858 Store_String_Chars (String_Val);
10859 Link_Nam :=
10860 Make_String_Literal (Sloc (Link_Nam),
10861 Strval => End_String);
10862 end if;
10864 -- Set the interface name. If the entity is a generic instance, use
10865 -- its alias, which is the callable entity.
10867 if Is_Generic_Instance (Subprogram_Def) then
10868 Set_Encoded_Interface_Name
10869 (Alias (Get_Base_Subprogram (Subprogram_Def)), Link_Nam);
10870 else
10871 Set_Encoded_Interface_Name
10872 (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
10873 end if;
10875 Check_Duplicated_Export_Name (Link_Nam);
10876 end Process_Interface_Name;
10878 -----------------------------------------
10879 -- Process_Interrupt_Or_Attach_Handler --
10880 -----------------------------------------
10882 procedure Process_Interrupt_Or_Attach_Handler is
10883 Handler : constant Entity_Id := Entity (Get_Pragma_Arg (Arg1));
10884 Prot_Typ : constant Entity_Id := Scope (Handler);
10886 begin
10887 -- A pragma that applies to a Ghost entity becomes Ghost for the
10888 -- purposes of legality checks and removal of ignored Ghost code.
10890 Mark_Ghost_Pragma (N, Handler);
10891 Set_Is_Interrupt_Handler (Handler);
10893 pragma Assert (Ekind (Prot_Typ) = E_Protected_Type);
10895 Record_Rep_Item (Prot_Typ, N);
10897 -- Chain the pragma on the contract for completeness
10899 Add_Contract_Item (N, Handler);
10900 end Process_Interrupt_Or_Attach_Handler;
10902 --------------------------------------------------
10903 -- Process_Restrictions_Or_Restriction_Warnings --
10904 --------------------------------------------------
10906 -- Note: some of the simple identifier cases were handled in par-prag,
10907 -- but it is harmless (and more straightforward) to simply handle all
10908 -- cases here, even if it means we repeat a bit of work in some cases.
10910 procedure Process_Restrictions_Or_Restriction_Warnings
10911 (Warn : Boolean)
10913 Arg : Node_Id;
10914 R_Id : Restriction_Id;
10915 Id : Name_Id;
10916 Expr : Node_Id;
10917 Val : Uint;
10919 procedure Process_No_Specification_of_Aspect;
10920 -- Process the No_Specification_of_Aspect restriction
10922 procedure Process_No_Use_Of_Attribute;
10923 -- Process the No_Use_Of_Attribute restriction
10925 ----------------------------------------
10926 -- Process_No_Specification_of_Aspect --
10927 ----------------------------------------
10929 procedure Process_No_Specification_of_Aspect is
10930 Name : constant Name_Id := Chars (Expr);
10931 begin
10932 if Nkind (Expr) = N_Identifier
10933 and then Is_Aspect_Id (Name)
10934 then
10935 Set_Restriction_No_Specification_Of_Aspect (Expr, Warn);
10936 else
10937 Bad_Aspect (Expr, Name, Warn => True);
10939 raise Pragma_Exit;
10940 end if;
10941 end Process_No_Specification_of_Aspect;
10943 ---------------------------------
10944 -- Process_No_Use_Of_Attribute --
10945 ---------------------------------
10947 procedure Process_No_Use_Of_Attribute is
10948 Name : constant Name_Id := Chars (Expr);
10949 begin
10950 if Nkind (Expr) = N_Identifier
10951 and then Is_Attribute_Name (Name)
10952 then
10953 Set_Restriction_No_Use_Of_Attribute (Expr, Warn);
10954 else
10955 Bad_Attribute (Expr, Name, Warn => True);
10956 end if;
10958 end Process_No_Use_Of_Attribute;
10960 -- Start of processing for Process_Restrictions_Or_Restriction_Warnings
10962 begin
10963 -- Ignore all Restrictions pragmas in CodePeer mode
10965 if CodePeer_Mode then
10966 return;
10967 end if;
10969 Check_Ada_83_Warning;
10970 Check_At_Least_N_Arguments (1);
10971 Check_Valid_Configuration_Pragma;
10973 Arg := Arg1;
10974 while Present (Arg) loop
10975 Id := Chars (Arg);
10976 Expr := Get_Pragma_Arg (Arg);
10978 -- Case of no restriction identifier present
10980 if Id = No_Name then
10981 if Nkind (Expr) /= N_Identifier then
10982 Error_Pragma_Arg
10983 ("invalid form for restriction", Arg);
10984 end if;
10986 R_Id :=
10987 Get_Restriction_Id
10988 (Process_Restriction_Synonyms (Expr));
10990 if R_Id not in All_Boolean_Restrictions then
10991 Error_Msg_Name_1 := Pname;
10992 Error_Msg_N
10993 ("invalid restriction identifier&", Get_Pragma_Arg (Arg));
10995 -- Check for possible misspelling
10997 for J in All_Restrictions loop
10998 declare
10999 Rnm : constant String := Restriction_Id'Image (J);
11001 begin
11002 Name_Buffer (1 .. Rnm'Length) := Rnm;
11003 Name_Len := Rnm'Length;
11004 Set_Casing (All_Lower_Case);
11006 if Is_Bad_Spelling_Of (Chars (Expr), Name_Enter) then
11007 Set_Casing
11008 (Identifier_Casing
11009 (Source_Index (Current_Sem_Unit)));
11010 Error_Msg_String (1 .. Rnm'Length) :=
11011 Name_Buffer (1 .. Name_Len);
11012 Error_Msg_Strlen := Rnm'Length;
11013 Error_Msg_N -- CODEFIX
11014 ("\possible misspelling of ""~""",
11015 Get_Pragma_Arg (Arg));
11016 exit;
11017 end if;
11018 end;
11019 end loop;
11021 raise Pragma_Exit;
11022 end if;
11024 if Implementation_Restriction (R_Id) then
11025 Check_Restriction (No_Implementation_Restrictions, Arg);
11026 end if;
11028 -- Special processing for No_Elaboration_Code restriction
11030 if R_Id = No_Elaboration_Code then
11032 -- Restriction is only recognized within a configuration
11033 -- pragma file, or within a unit of the main extended
11034 -- program. Note: the test for Main_Unit is needed to
11035 -- properly include the case of configuration pragma files.
11037 if not (Current_Sem_Unit = Main_Unit
11038 or else In_Extended_Main_Source_Unit (N))
11039 then
11040 return;
11042 -- Don't allow in a subunit unless already specified in
11043 -- body or spec.
11045 elsif Nkind (Parent (N)) = N_Compilation_Unit
11046 and then Nkind (Unit (Parent (N))) = N_Subunit
11047 and then not Restriction_Active (No_Elaboration_Code)
11048 then
11049 Error_Msg_N
11050 ("invalid specification of ""No_Elaboration_Code""",
11052 Error_Msg_N
11053 ("\restriction cannot be specified in a subunit", N);
11054 Error_Msg_N
11055 ("\unless also specified in body or spec", N);
11056 return;
11058 -- If we accept a No_Elaboration_Code restriction, then it
11059 -- needs to be added to the configuration restriction set so
11060 -- that we get proper application to other units in the main
11061 -- extended source as required.
11063 else
11064 Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
11065 end if;
11067 -- Special processing for No_Dynamic_Accessibility_Checks to
11068 -- disallow exclusive specification in a body or subunit.
11070 elsif R_Id = No_Dynamic_Accessibility_Checks
11071 -- Check if the restriction is within configuration pragma
11072 -- in a similar way to No_Elaboration_Code.
11074 and then not (Current_Sem_Unit = Main_Unit
11075 or else In_Extended_Main_Source_Unit (N))
11077 and then Nkind (Unit (Parent (N))) = N_Compilation_Unit
11079 and then (Nkind (Unit (Parent (N))) = N_Package_Body
11080 or else Nkind (Unit (Parent (N))) = N_Subunit)
11082 and then not Restriction_Active
11083 (No_Dynamic_Accessibility_Checks)
11084 then
11085 Error_Msg_N
11086 ("invalid specification of " &
11087 """No_Dynamic_Accessibility_Checks""", N);
11089 if Nkind (Unit (Parent (N))) = N_Package_Body then
11090 Error_Msg_N
11091 ("\restriction cannot be specified in a package " &
11092 "body", N);
11094 elsif Nkind (Unit (Parent (N))) = N_Subunit then
11095 Error_Msg_N
11096 ("\restriction cannot be specified in a subunit", N);
11097 end if;
11099 Error_Msg_N
11100 ("\unless also specified in spec", N);
11102 -- Special processing for No_Tasking restriction (not just a
11103 -- warning) when it appears as a configuration pragma.
11105 elsif R_Id = No_Tasking
11106 and then No (Cunit (Main_Unit))
11107 and then not Warn
11108 then
11109 Set_Global_No_Tasking;
11110 end if;
11112 Set_Restriction (R_Id, N, Warn);
11114 if R_Id = No_Dynamic_CPU_Assignment
11115 or else R_Id = No_Tasks_Unassigned_To_CPU
11116 then
11117 -- These imply No_Dependence =>
11118 -- "System.Multiprocessors.Dispatching_Domains".
11119 -- This is not strictly what the AI says, but it eliminates
11120 -- the need for run-time checks, which are undesirable in
11121 -- this context.
11123 Set_Restriction_No_Dependence
11124 (Sel_Comp
11125 (Sel_Comp ("system", "multiprocessors", Loc),
11126 "dispatching_domains"),
11127 Warn);
11128 end if;
11130 if R_Id = No_Tasks_Unassigned_To_CPU then
11131 -- Likewise, imply No_Dynamic_CPU_Assignment
11133 Set_Restriction (No_Dynamic_CPU_Assignment, N, Warn);
11134 end if;
11136 -- Check for obsolescent restrictions in Ada 2005 mode
11138 if not Warn
11139 and then Ada_Version >= Ada_2005
11140 and then (R_Id = No_Asynchronous_Control
11141 or else
11142 R_Id = No_Unchecked_Deallocation
11143 or else
11144 R_Id = No_Unchecked_Conversion)
11145 then
11146 Check_Restriction (No_Obsolescent_Features, N);
11147 end if;
11149 -- A very special case that must be processed here: pragma
11150 -- Restrictions (No_Exceptions) turns off all run-time
11151 -- checking. This is a bit dubious in terms of the formal
11152 -- language definition, but it is what is intended by RM
11153 -- H.4(12). Restriction_Warnings never affects generated code
11154 -- so this is done only in the real restriction case.
11156 -- Atomic_Synchronization is not a real check, so it is not
11157 -- affected by this processing).
11159 -- Ignore the effect of pragma Restrictions (No_Exceptions) on
11160 -- run-time checks in CodePeer and GNATprove modes: we want to
11161 -- generate checks for analysis purposes, as set respectively
11162 -- by -gnatC and -gnatd.F
11164 if not Warn
11165 and then not (CodePeer_Mode or GNATprove_Mode)
11166 and then R_Id = No_Exceptions
11167 then
11168 for J in Scope_Suppress.Suppress'Range loop
11169 if J /= Atomic_Synchronization then
11170 Scope_Suppress.Suppress (J) := True;
11171 end if;
11172 end loop;
11173 end if;
11175 -- Case of No_Dependence => unit-name. Note that the parser
11176 -- already made the necessary entry in the No_Dependence table.
11178 elsif Id = Name_No_Dependence then
11179 if not OK_No_Dependence_Unit_Name (Expr) then
11180 raise Pragma_Exit;
11181 end if;
11183 -- Case of No_Specification_Of_Aspect => aspect-identifier
11185 elsif Id = Name_No_Specification_Of_Aspect then
11186 Process_No_Specification_of_Aspect;
11188 -- Case of No_Use_Of_Attribute => attribute-identifier
11190 elsif Id = Name_No_Use_Of_Attribute then
11191 Process_No_Use_Of_Attribute;
11193 -- Case of No_Use_Of_Entity => fully-qualified-name
11195 elsif Id = Name_No_Use_Of_Entity then
11197 -- Restriction is only recognized within a configuration
11198 -- pragma file, or within a unit of the main extended
11199 -- program. Note: the test for Main_Unit is needed to
11200 -- properly include the case of configuration pragma files.
11202 if Current_Sem_Unit = Main_Unit
11203 or else In_Extended_Main_Source_Unit (N)
11204 then
11205 if not OK_No_Dependence_Unit_Name (Expr) then
11206 Error_Msg_N ("wrong form for entity name", Expr);
11207 else
11208 Set_Restriction_No_Use_Of_Entity
11209 (Expr, Warn, No_Profile);
11210 end if;
11211 end if;
11213 -- Case of No_Use_Of_Pragma => pragma-identifier
11215 elsif Id = Name_No_Use_Of_Pragma then
11216 if Nkind (Expr) /= N_Identifier
11217 or else not Is_Pragma_Name (Chars (Expr))
11218 then
11219 Error_Msg_N ("unknown pragma name??", Expr);
11220 else
11221 Set_Restriction_No_Use_Of_Pragma (Expr, Warn);
11222 end if;
11224 -- All other cases of restriction identifier present
11226 else
11227 R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
11229 if R_Id not in All_Parameter_Restrictions then
11230 Error_Pragma_Arg
11231 ("invalid restriction parameter identifier", Arg);
11232 end if;
11234 Analyze_And_Resolve (Expr, Any_Integer);
11236 if not Is_OK_Static_Expression (Expr) then
11237 Flag_Non_Static_Expr
11238 ("value must be static expression!", Expr);
11239 raise Pragma_Exit;
11241 elsif not Is_Integer_Type (Etype (Expr))
11242 or else Expr_Value (Expr) < 0
11243 then
11244 Error_Pragma_Arg
11245 ("value must be non-negative integer", Arg);
11246 end if;
11248 -- Restriction pragma is active
11250 Val := Expr_Value (Expr);
11252 if not UI_Is_In_Int_Range (Val) then
11253 Error_Pragma_Arg
11254 ("pragma ignored, value too large??", Arg);
11255 end if;
11257 Set_Restriction (R_Id, N, Warn, Integer (UI_To_Int (Val)));
11258 end if;
11260 Next (Arg);
11261 end loop;
11262 end Process_Restrictions_Or_Restriction_Warnings;
11264 ---------------------------------
11265 -- Process_Suppress_Unsuppress --
11266 ---------------------------------
11268 -- Note: this procedure makes entries in the check suppress data
11269 -- structures managed by Sem. See spec of package Sem for full
11270 -- details on how we handle recording of check suppression.
11272 procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
11273 C : Check_Id;
11274 E : Entity_Id;
11275 E_Id : Node_Id;
11277 In_Package_Spec : constant Boolean :=
11278 Is_Package_Or_Generic_Package (Current_Scope)
11279 and then not In_Package_Body (Current_Scope);
11281 procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
11282 -- Used to suppress a single check on the given entity
11284 --------------------------------
11285 -- Suppress_Unsuppress_Echeck --
11286 --------------------------------
11288 procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
11289 begin
11290 -- Check for error of trying to set atomic synchronization for
11291 -- a non-atomic variable.
11293 if C = Atomic_Synchronization
11294 and then not (Is_Atomic (E) or else Has_Atomic_Components (E))
11295 then
11296 Error_Msg_N
11297 ("pragma & requires atomic type or variable",
11298 Pragma_Identifier (Original_Node (N)));
11299 end if;
11301 Set_Checks_May_Be_Suppressed (E);
11303 if In_Package_Spec then
11304 Push_Global_Suppress_Stack_Entry
11305 (Entity => E,
11306 Check => C,
11307 Suppress => Suppress_Case);
11308 else
11309 Push_Local_Suppress_Stack_Entry
11310 (Entity => E,
11311 Check => C,
11312 Suppress => Suppress_Case);
11313 end if;
11315 -- If this is a first subtype, and the base type is distinct,
11316 -- then also set the suppress flags on the base type.
11318 if Is_First_Subtype (E) and then Etype (E) /= E then
11319 Suppress_Unsuppress_Echeck (Etype (E), C);
11320 end if;
11321 end Suppress_Unsuppress_Echeck;
11323 -- Start of processing for Process_Suppress_Unsuppress
11325 begin
11326 -- Ignore pragma Suppress/Unsuppress in CodePeer and GNATprove modes
11327 -- on user code: we want to generate checks for analysis purposes, as
11328 -- set respectively by -gnatC and -gnatd.F
11330 if Comes_From_Source (N)
11331 and then (CodePeer_Mode or GNATprove_Mode)
11332 then
11333 return;
11334 end if;
11336 -- Suppress/Unsuppress can appear as a configuration pragma, or in a
11337 -- declarative part or a package spec (RM 11.5(5)).
11339 if not Is_Configuration_Pragma then
11340 Check_Is_In_Decl_Part_Or_Package_Spec;
11341 end if;
11343 Check_At_Least_N_Arguments (1);
11344 Check_At_Most_N_Arguments (2);
11345 Check_No_Identifier (Arg1);
11346 Check_Arg_Is_Identifier (Arg1);
11348 C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
11350 if C = No_Check_Id then
11351 Error_Pragma_Arg
11352 ("argument of pragma% is not valid check name", Arg1);
11353 end if;
11355 -- Warn that suppress of Elaboration_Check has no effect in SPARK
11357 if C = Elaboration_Check
11358 and then Suppress_Case
11359 and then SPARK_Mode = On
11360 then
11361 Error_Pragma_Arg
11362 ("Suppress of Elaboration_Check ignored in SPARK??",
11363 "\elaboration checking rules are statically enforced "
11364 & "(SPARK RM 7.7)", Arg1);
11365 end if;
11367 -- One-argument case
11369 if Arg_Count = 1 then
11371 -- Make an entry in the local scope suppress table. This is the
11372 -- table that directly shows the current value of the scope
11373 -- suppress check for any check id value.
11375 if C = All_Checks then
11377 -- For All_Checks, we set all specific predefined checks with
11378 -- the exception of Elaboration_Check, which is handled
11379 -- specially because of not wanting All_Checks to have the
11380 -- effect of deactivating static elaboration order processing.
11381 -- Atomic_Synchronization is also not affected, since this is
11382 -- not a real check.
11384 for J in Scope_Suppress.Suppress'Range loop
11385 if J /= Elaboration_Check
11386 and then
11387 J /= Atomic_Synchronization
11388 then
11389 Scope_Suppress.Suppress (J) := Suppress_Case;
11390 end if;
11391 end loop;
11393 -- If not All_Checks, and predefined check, then set appropriate
11394 -- scope entry. Note that we will set Elaboration_Check if this
11395 -- is explicitly specified. Atomic_Synchronization is allowed
11396 -- only if internally generated and entity is atomic.
11398 elsif C in Predefined_Check_Id
11399 and then (not Comes_From_Source (N)
11400 or else C /= Atomic_Synchronization)
11401 then
11402 Scope_Suppress.Suppress (C) := Suppress_Case;
11403 end if;
11405 -- Also push an entry in the local suppress stack
11407 Push_Local_Suppress_Stack_Entry
11408 (Entity => Empty,
11409 Check => C,
11410 Suppress => Suppress_Case);
11412 -- Case of two arguments present, where the check is suppressed for
11413 -- a specified entity (given as the second argument of the pragma)
11415 else
11416 -- This is obsolescent in Ada 2005 mode
11418 if Ada_Version >= Ada_2005 then
11419 Check_Restriction (No_Obsolescent_Features, Arg2);
11420 end if;
11422 Check_Optional_Identifier (Arg2, Name_On);
11423 E_Id := Get_Pragma_Arg (Arg2);
11424 Analyze (E_Id);
11426 if not Is_Entity_Name (E_Id) then
11427 Error_Pragma_Arg
11428 ("second argument of pragma% must be entity name", Arg2);
11429 end if;
11431 E := Entity (E_Id);
11433 if E = Any_Id then
11434 return;
11435 end if;
11437 -- A pragma that applies to a Ghost entity becomes Ghost for the
11438 -- purposes of legality checks and removal of ignored Ghost code.
11440 Mark_Ghost_Pragma (N, E);
11442 -- Enforce RM 11.5(7) which requires that for a pragma that
11443 -- appears within a package spec, the named entity must be
11444 -- within the package spec. We allow the package name itself
11445 -- to be mentioned since that makes sense, although it is not
11446 -- strictly allowed by 11.5(7).
11448 if In_Package_Spec
11449 and then E /= Current_Scope
11450 and then Scope (E) /= Current_Scope
11451 then
11452 Error_Pragma_Arg
11453 ("entity in pragma% is not in package spec (RM 11.5(7))",
11454 Arg2);
11455 end if;
11457 -- Loop through homonyms. As noted below, in the case of a package
11458 -- spec, only homonyms within the package spec are considered.
11460 loop
11461 Suppress_Unsuppress_Echeck (E, C);
11463 if Is_Generic_Instance (E)
11464 and then Is_Subprogram (E)
11465 and then Present (Alias (E))
11466 then
11467 Suppress_Unsuppress_Echeck (Alias (E), C);
11468 end if;
11470 -- Move to next homonym if not aspect spec case
11472 exit when From_Aspect_Specification (N);
11473 E := Homonym (E);
11474 exit when No (E);
11476 -- If we are within a package specification, the pragma only
11477 -- applies to homonyms in the same scope.
11479 exit when In_Package_Spec
11480 and then Scope (E) /= Current_Scope;
11481 end loop;
11482 end if;
11483 end Process_Suppress_Unsuppress;
11485 -------------------------------
11486 -- Record_Independence_Check --
11487 -------------------------------
11489 procedure Record_Independence_Check (N : Node_Id; E : Entity_Id) is
11490 pragma Unreferenced (N, E);
11491 begin
11492 -- For GCC back ends the validation is done a priori. This code is
11493 -- dead, but might be useful in the future.
11495 -- if not AAMP_On_Target then
11496 -- return;
11497 -- end if;
11499 -- Independence_Checks.Append ((N, E));
11501 return;
11502 end Record_Independence_Check;
11504 ------------------
11505 -- Set_Exported --
11506 ------------------
11508 procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
11509 begin
11510 if Is_Imported (E) then
11511 Error_Pragma_Arg
11512 ("cannot export entity& that was previously imported", Arg);
11514 elsif Present (Address_Clause (E))
11515 and then not Relaxed_RM_Semantics
11516 then
11517 Error_Pragma_Arg
11518 ("cannot export entity& that has an address clause", Arg);
11519 end if;
11521 Set_Is_Exported (E);
11523 -- Generate a reference for entity explicitly, because the
11524 -- identifier may be overloaded and name resolution will not
11525 -- generate one.
11527 Generate_Reference (E, Arg);
11529 -- Deal with exporting non-library level entity
11531 if not Is_Library_Level_Entity (E) then
11533 -- Not allowed at all for subprograms
11535 if Is_Subprogram (E) then
11536 Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
11538 -- Otherwise set public and statically allocated
11540 else
11541 Set_Is_Public (E);
11542 Set_Is_Statically_Allocated (E);
11544 -- Warn if the corresponding W flag is set
11546 if Warn_On_Export_Import
11548 -- Only do this for something that was in the source. Not
11549 -- clear if this can be False now (there used for sure to be
11550 -- cases on some systems where it was False), but anyway the
11551 -- test is harmless if not needed, so it is retained.
11553 and then Comes_From_Source (Arg)
11554 then
11555 Error_Msg_NE
11556 ("?x?& has been made static as a result of Export",
11557 Arg, E);
11558 Error_Msg_N
11559 ("\?x?this usage is non-standard and non-portable",
11560 Arg);
11561 end if;
11562 end if;
11563 end if;
11565 if Warn_On_Export_Import and Inside_A_Generic then
11566 Error_Msg_NE
11567 ("all instances of& will have the same external name?x?",
11568 Arg, E);
11569 end if;
11570 end Set_Exported;
11572 ----------------------------------------------
11573 -- Set_Extended_Import_Export_External_Name --
11574 ----------------------------------------------
11576 procedure Set_Extended_Import_Export_External_Name
11577 (Internal_Ent : Entity_Id;
11578 Arg_External : Node_Id)
11580 Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
11581 New_Name : Node_Id;
11583 begin
11584 if No (Arg_External) then
11585 return;
11586 end if;
11588 Check_Arg_Is_External_Name (Arg_External);
11590 if Nkind (Arg_External) = N_String_Literal then
11591 if String_Length (Strval (Arg_External)) = 0 then
11592 return;
11593 else
11594 New_Name := Adjust_External_Name_Case (Arg_External);
11595 end if;
11597 elsif Nkind (Arg_External) = N_Identifier then
11598 New_Name := Get_Default_External_Name (Arg_External);
11600 -- Check_Arg_Is_External_Name should let through only identifiers and
11601 -- string literals or static string expressions (which are folded to
11602 -- string literals).
11604 else
11605 raise Program_Error;
11606 end if;
11608 -- If we already have an external name set (by a prior normal Import
11609 -- or Export pragma), then the external names must match
11611 if Present (Interface_Name (Internal_Ent)) then
11613 -- Ignore mismatching names in CodePeer mode, to support some
11614 -- old compilers which would export the same procedure under
11615 -- different names, e.g:
11616 -- procedure P;
11617 -- pragma Export_Procedure (P, "a");
11618 -- pragma Export_Procedure (P, "b");
11620 if CodePeer_Mode then
11621 return;
11622 end if;
11624 Check_Matching_Internal_Names : declare
11625 S1 : constant String_Id := Strval (Old_Name);
11626 S2 : constant String_Id := Strval (New_Name);
11628 procedure Mismatch;
11629 pragma No_Return (Mismatch);
11630 -- Called if names do not match
11632 --------------
11633 -- Mismatch --
11634 --------------
11636 procedure Mismatch is
11637 begin
11638 Error_Msg_Sloc := Sloc (Old_Name);
11639 Error_Pragma_Arg
11640 ("external name does not match that given #",
11641 Arg_External);
11642 end Mismatch;
11644 -- Start of processing for Check_Matching_Internal_Names
11646 begin
11647 if String_Length (S1) /= String_Length (S2) then
11648 Mismatch;
11650 else
11651 for J in 1 .. String_Length (S1) loop
11652 if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
11653 Mismatch;
11654 end if;
11655 end loop;
11656 end if;
11657 end Check_Matching_Internal_Names;
11659 -- Otherwise set the given name
11661 else
11662 Set_Encoded_Interface_Name (Internal_Ent, New_Name);
11663 Check_Duplicated_Export_Name (New_Name);
11664 end if;
11665 end Set_Extended_Import_Export_External_Name;
11667 ------------------
11668 -- Set_Imported --
11669 ------------------
11671 procedure Set_Imported (E : Entity_Id) is
11672 begin
11673 -- Error message if already imported or exported
11675 if Is_Exported (E) or else Is_Imported (E) then
11677 -- Error if being set Exported twice
11679 if Is_Exported (E) then
11680 Error_Msg_NE ("entity& was previously exported", N, E);
11682 -- Ignore error in CodePeer mode where we treat all imported
11683 -- subprograms as unknown.
11685 elsif CodePeer_Mode then
11686 goto OK;
11688 -- OK if Import/Interface case
11690 elsif Import_Interface_Present (N) then
11691 goto OK;
11693 -- Error if being set Imported twice
11695 else
11696 Error_Msg_NE ("entity& was previously imported", N, E);
11697 end if;
11699 Error_Msg_Name_1 := Pname;
11700 Error_Msg_N
11701 ("\(pragma% applies to all previous entities)", N);
11703 Error_Msg_Sloc := Sloc (E);
11704 Error_Msg_NE ("\import not allowed for& declared#", N, E);
11706 -- Here if not previously imported or exported, OK to import
11708 else
11709 Set_Is_Imported (E);
11711 -- For subprogram, set Import_Pragma field
11713 if Is_Subprogram (E) then
11714 Set_Import_Pragma (E, N);
11715 end if;
11717 -- If the entity is an object that is not at the library level,
11718 -- then it is statically allocated. We do not worry about objects
11719 -- with address clauses in this context since they are not really
11720 -- imported in the linker sense.
11722 if Is_Object (E)
11723 and then not Is_Library_Level_Entity (E)
11724 and then No (Address_Clause (E))
11725 then
11726 Set_Is_Statically_Allocated (E);
11727 end if;
11728 end if;
11730 <<OK>> null;
11731 end Set_Imported;
11733 -------------------------
11734 -- Set_Mechanism_Value --
11735 -------------------------
11737 -- Note: the mechanism name has not been analyzed (and cannot indeed be
11738 -- analyzed, since it is semantic nonsense), so we get it in the exact
11739 -- form created by the parser.
11741 procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
11742 procedure Bad_Mechanism;
11743 pragma No_Return (Bad_Mechanism);
11744 -- Signal bad mechanism name
11746 -------------------
11747 -- Bad_Mechanism --
11748 -------------------
11750 procedure Bad_Mechanism is
11751 begin
11752 Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
11753 end Bad_Mechanism;
11755 -- Start of processing for Set_Mechanism_Value
11757 begin
11758 if Mechanism (Ent) /= Default_Mechanism then
11759 Error_Msg_NE
11760 ("mechanism for & has already been set", Mech_Name, Ent);
11761 end if;
11763 -- MECHANISM_NAME ::= value | reference
11765 if Nkind (Mech_Name) = N_Identifier then
11766 if Chars (Mech_Name) = Name_Value then
11767 Set_Mechanism (Ent, By_Copy);
11768 return;
11770 elsif Chars (Mech_Name) = Name_Reference then
11771 Set_Mechanism (Ent, By_Reference);
11772 return;
11774 elsif Chars (Mech_Name) = Name_Copy then
11775 Error_Pragma_Arg
11776 ("bad mechanism name, Value assumed", Mech_Name);
11778 else
11779 Bad_Mechanism;
11780 end if;
11782 else
11783 Bad_Mechanism;
11784 end if;
11785 end Set_Mechanism_Value;
11787 --------------------------
11788 -- Set_Rational_Profile --
11789 --------------------------
11791 -- The Rational profile includes Implicit_Packing, Use_Vads_Size, and
11792 -- extension to the semantics of renaming declarations.
11794 procedure Set_Rational_Profile is
11795 begin
11796 Implicit_Packing := True;
11797 Overriding_Renamings := True;
11798 Use_VADS_Size := True;
11799 end Set_Rational_Profile;
11801 ---------------------------
11802 -- Set_Ravenscar_Profile --
11803 ---------------------------
11805 -- The tasks to be done here are
11807 -- Set required policies
11809 -- pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
11810 -- (For Ravenscar, Jorvik, and GNAT_Extended_Ravenscar profiles)
11811 -- pragma Task_Dispatching_Policy (EDF_Across_Priorities)
11812 -- (For GNAT_Ravenscar_EDF profile)
11813 -- pragma Locking_Policy (Ceiling_Locking)
11815 -- Set Detect_Blocking mode
11817 -- Set required restrictions (see System.Rident for detailed list)
11819 -- Set the No_Dependence rules
11820 -- No_Dependence => Ada.Asynchronous_Task_Control
11821 -- No_Dependence => Ada.Calendar
11822 -- No_Dependence => Ada.Execution_Time.Group_Budget
11823 -- No_Dependence => Ada.Execution_Time.Timers
11824 -- No_Dependence => Ada.Task_Attributes
11825 -- No_Dependence => System.Multiprocessors.Dispatching_Domains
11827 procedure Set_Ravenscar_Profile (Profile : Profile_Name; N : Node_Id) is
11828 procedure Set_Error_Msg_To_Profile_Name;
11829 -- Set Error_Msg_String and Error_Msg_Strlen to the name of the
11830 -- profile.
11832 -----------------------------------
11833 -- Set_Error_Msg_To_Profile_Name --
11834 -----------------------------------
11836 procedure Set_Error_Msg_To_Profile_Name is
11837 Prof_Nam : constant Node_Id :=
11838 Get_Pragma_Arg
11839 (First (Pragma_Argument_Associations (N)));
11841 begin
11842 Get_Name_String (Chars (Prof_Nam));
11843 Adjust_Name_Case (Global_Name_Buffer, Sloc (Prof_Nam));
11844 Error_Msg_Strlen := Name_Len;
11845 Error_Msg_String (1 .. Name_Len) := Name_Buffer (1 .. Name_Len);
11846 end Set_Error_Msg_To_Profile_Name;
11848 Profile_Dispatching_Policy : Character;
11850 -- Start of processing for Set_Ravenscar_Profile
11852 begin
11853 -- pragma Task_Dispatching_Policy (EDF_Across_Priorities)
11855 if Profile = GNAT_Ravenscar_EDF then
11856 Profile_Dispatching_Policy := 'E';
11858 -- pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
11860 else
11861 Profile_Dispatching_Policy := 'F';
11862 end if;
11864 if Task_Dispatching_Policy /= ' '
11865 and then Task_Dispatching_Policy /= Profile_Dispatching_Policy
11866 then
11867 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
11868 Set_Error_Msg_To_Profile_Name;
11869 Error_Pragma ("Profile (~) incompatible with policy#");
11871 -- Set the FIFO_Within_Priorities policy, but always preserve
11872 -- System_Location since we like the error message with the run time
11873 -- name.
11875 else
11876 Task_Dispatching_Policy := Profile_Dispatching_Policy;
11878 if Task_Dispatching_Policy_Sloc /= System_Location then
11879 Task_Dispatching_Policy_Sloc := Loc;
11880 end if;
11881 end if;
11883 -- pragma Locking_Policy (Ceiling_Locking)
11885 if Locking_Policy /= ' '
11886 and then Locking_Policy /= 'C'
11887 then
11888 Error_Msg_Sloc := Locking_Policy_Sloc;
11889 Set_Error_Msg_To_Profile_Name;
11890 Error_Pragma ("Profile (~) incompatible with policy#");
11892 -- Set the Ceiling_Locking policy, but preserve System_Location since
11893 -- we like the error message with the run time name.
11895 else
11896 Locking_Policy := 'C';
11898 if Locking_Policy_Sloc /= System_Location then
11899 Locking_Policy_Sloc := Loc;
11900 end if;
11901 end if;
11903 -- pragma Detect_Blocking
11905 Detect_Blocking := True;
11907 -- Set the corresponding restrictions
11909 Set_Profile_Restrictions
11910 (Profile, N, Warn => Treat_Restrictions_As_Warnings);
11912 -- Set the No_Dependence restrictions
11914 -- The following No_Dependence restrictions:
11915 -- No_Dependence => Ada.Asynchronous_Task_Control
11916 -- No_Dependence => Ada.Calendar
11917 -- No_Dependence => Ada.Task_Attributes
11918 -- are already set by previous call to Set_Profile_Restrictions.
11919 -- Really???
11921 -- Set the following restrictions which were added to Ada 2005:
11922 -- No_Dependence => Ada.Execution_Time.Group_Budget
11923 -- No_Dependence => Ada.Execution_Time.Timers
11925 if Ada_Version >= Ada_2005 then
11926 declare
11927 Execution_Time : constant Node_Id :=
11928 Sel_Comp ("ada", "execution_time", Loc);
11929 Group_Budgets : constant Node_Id :=
11930 Sel_Comp (Execution_Time, "group_budgets");
11931 Timers : constant Node_Id :=
11932 Sel_Comp (Execution_Time, "timers");
11933 begin
11934 Set_Restriction_No_Dependence
11935 (Unit => Group_Budgets,
11936 Warn => Treat_Restrictions_As_Warnings,
11937 Profile => Ravenscar);
11938 Set_Restriction_No_Dependence
11939 (Unit => Timers,
11940 Warn => Treat_Restrictions_As_Warnings,
11941 Profile => Ravenscar);
11942 end;
11943 end if;
11945 -- Set the following restriction which was added to Ada 2012 (see
11946 -- AI05-0171):
11947 -- No_Dependence => System.Multiprocessors.Dispatching_Domains
11949 if Ada_Version >= Ada_2012 then
11950 Set_Restriction_No_Dependence
11951 (Sel_Comp
11952 (Sel_Comp ("system", "multiprocessors", Loc),
11953 "dispatching_domains"),
11954 Warn => Treat_Restrictions_As_Warnings,
11955 Profile => Ravenscar);
11957 -- Set the following restriction which was added to Ada 2022,
11958 -- but as a binding interpretation:
11959 -- No_Dependence => Ada.Synchronous_Barriers
11960 -- for Ravenscar (and therefore for Ravenscar variants) but not
11961 -- for Jorvik. The unit Ada.Synchronous_Barriers was introduced
11962 -- in Ada2012 (AI05-0174).
11964 if Profile /= Jorvik then
11965 Set_Restriction_No_Dependence
11966 (Sel_Comp ("ada", "synchronous_barriers", Loc),
11967 Warn => Treat_Restrictions_As_Warnings,
11968 Profile => Ravenscar);
11969 end if;
11970 end if;
11972 end Set_Ravenscar_Profile;
11974 -- Start of processing for Analyze_Pragma
11976 begin
11977 -- The following code is a defense against recursion. Not clear that
11978 -- this can happen legitimately, but perhaps some error situations can
11979 -- cause it, and we did see this recursion during testing.
11981 if Analyzed (N) then
11982 return;
11983 else
11984 Set_Analyzed (N);
11985 end if;
11987 Check_Restriction_No_Use_Of_Pragma (N);
11989 if Is_Aspect_Id (Chars (Pragma_Identifier (N))) then
11990 -- 6.1/3 No_Specification_of_Aspect: Identifies an aspect for which
11991 -- no aspect_specification, attribute_definition_clause, or pragma
11992 -- is given.
11993 Check_Restriction_No_Specification_Of_Aspect (N);
11994 end if;
11996 -- Ignore pragma if Ignore_Pragma applies. Also ignore pragma
11997 -- Default_Scalar_Storage_Order if the -gnatI switch was given.
11999 if Should_Ignore_Pragma_Sem (N)
12000 or else (Prag_Id = Pragma_Default_Scalar_Storage_Order
12001 and then Ignore_Rep_Clauses)
12002 then
12003 return;
12004 end if;
12006 -- Deal with unrecognized pragma
12008 if not Is_Pragma_Name (Pname) then
12009 declare
12010 Msg_Issued : Boolean := False;
12011 begin
12012 Check_Restriction
12013 (Msg_Issued, No_Unrecognized_Pragmas, Pragma_Identifier (N));
12014 if not Msg_Issued and then Warn_On_Unrecognized_Pragma then
12015 Error_Msg_Name_1 := Pname;
12016 Error_Msg_N ("?g?unrecognized pragma%!", Pragma_Identifier (N));
12018 for PN in First_Pragma_Name .. Last_Pragma_Name loop
12019 if Is_Bad_Spelling_Of (Pname, PN) then
12020 Error_Msg_Name_1 := PN;
12021 Error_Msg_N -- CODEFIX
12022 ("\?g?possible misspelling of %!",
12023 Pragma_Identifier (N));
12024 exit;
12025 end if;
12026 end loop;
12027 end if;
12028 end;
12030 return;
12031 end if;
12033 -- Here to start processing for recognized pragma
12035 Pname := Original_Aspect_Pragma_Name (N);
12037 -- Capture setting of Opt.Uneval_Old
12039 case Opt.Uneval_Old is
12040 when 'A' =>
12041 Set_Uneval_Old_Accept (N);
12043 when 'E' =>
12044 null;
12046 when 'W' =>
12047 Set_Uneval_Old_Warn (N);
12049 when others =>
12050 raise Program_Error;
12051 end case;
12053 -- Check applicable policy. We skip this if Is_Checked or Is_Ignored
12054 -- is already set, indicating that we have already checked the policy
12055 -- at the right point. This happens for example in the case of a pragma
12056 -- that is derived from an Aspect.
12058 if Is_Ignored (N) or else Is_Checked (N) then
12059 null;
12061 -- For a pragma that is a rewriting of another pragma, copy the
12062 -- Is_Checked/Is_Ignored status from the rewritten pragma.
12064 elsif Is_Rewrite_Substitution (N)
12065 and then Nkind (Original_Node (N)) = N_Pragma
12066 then
12067 Set_Is_Ignored (N, Is_Ignored (Original_Node (N)));
12068 Set_Is_Checked (N, Is_Checked (Original_Node (N)));
12070 -- Otherwise query the applicable policy at this point
12072 else
12073 Check_Applicable_Policy (N);
12075 -- If pragma is disabled, rewrite as NULL and skip analysis
12077 if Is_Disabled (N) then
12078 Rewrite (N, Make_Null_Statement (Loc));
12079 Analyze (N);
12080 raise Pragma_Exit;
12081 end if;
12082 end if;
12084 -- Mark assertion pragmas as Ghost depending on their enclosing context
12086 if Assertion_Expression_Pragma (Prag_Id) then
12087 Mark_Ghost_Pragma (N, Current_Scope);
12088 end if;
12090 -- Preset arguments
12092 Arg_Count := List_Length (Pragma_Argument_Associations (N));
12093 Arg1 := First (Pragma_Argument_Associations (N));
12094 Arg2 := Empty;
12095 Arg3 := Empty;
12096 Arg4 := Empty;
12097 Arg5 := Empty;
12099 if Present (Arg1) then
12100 Arg2 := Next (Arg1);
12102 if Present (Arg2) then
12103 Arg3 := Next (Arg2);
12105 if Present (Arg3) then
12106 Arg4 := Next (Arg3);
12108 if Present (Arg4) then
12109 Arg5 := Next (Arg4);
12110 end if;
12111 end if;
12112 end if;
12113 end if;
12115 -- An enumeration type defines the pragmas that are supported by the
12116 -- implementation. Get_Pragma_Id (in package Prag) transforms a name
12117 -- into the corresponding enumeration value for the following case.
12119 case Prag_Id is
12121 -----------------
12122 -- Abort_Defer --
12123 -----------------
12125 -- pragma Abort_Defer;
12127 when Pragma_Abort_Defer =>
12128 GNAT_Pragma;
12129 Check_Arg_Count (0);
12131 -- The only required semantic processing is to check the
12132 -- placement. This pragma must appear at the start of the
12133 -- statement sequence of a handled sequence of statements.
12135 if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
12136 or else N /= First (Statements (Parent (N)))
12137 then
12138 Pragma_Misplaced;
12139 end if;
12141 --------------------
12142 -- Abstract_State --
12143 --------------------
12145 -- pragma Abstract_State (ABSTRACT_STATE_LIST);
12147 -- ABSTRACT_STATE_LIST ::=
12148 -- null
12149 -- | STATE_NAME_WITH_OPTIONS
12150 -- | (STATE_NAME_WITH_OPTIONS {, STATE_NAME_WITH_OPTIONS})
12152 -- STATE_NAME_WITH_OPTIONS ::=
12153 -- STATE_NAME
12154 -- | (STATE_NAME with OPTION_LIST)
12156 -- OPTION_LIST ::= OPTION {, OPTION}
12158 -- OPTION ::=
12159 -- SIMPLE_OPTION
12160 -- | NAME_VALUE_OPTION
12162 -- SIMPLE_OPTION ::= Ghost | Relaxed_Initialization | Synchronous
12164 -- NAME_VALUE_OPTION ::=
12165 -- Part_Of => ABSTRACT_STATE
12166 -- | External [=> EXTERNAL_PROPERTY_LIST]
12168 -- EXTERNAL_PROPERTY_LIST ::=
12169 -- EXTERNAL_PROPERTY
12170 -- | (EXTERNAL_PROPERTY {, EXTERNAL_PROPERTY})
12172 -- EXTERNAL_PROPERTY ::=
12173 -- Async_Readers [=> boolean_EXPRESSION]
12174 -- | Async_Writers [=> boolean_EXPRESSION]
12175 -- | Effective_Reads [=> boolean_EXPRESSION]
12176 -- | Effective_Writes [=> boolean_EXPRESSION]
12177 -- others => boolean_EXPRESSION
12179 -- STATE_NAME ::= defining_identifier
12181 -- ABSTRACT_STATE ::= name
12183 -- Characteristics:
12185 -- * Analysis - The annotation is fully analyzed immediately upon
12186 -- elaboration as it cannot forward reference entities.
12188 -- * Expansion - None.
12190 -- * Template - The annotation utilizes the generic template of the
12191 -- related package declaration.
12193 -- * Globals - The annotation cannot reference global entities.
12195 -- * Instance - The annotation is instantiated automatically when
12196 -- the related generic package is instantiated.
12198 when Pragma_Abstract_State => Abstract_State : declare
12199 Missing_Parentheses : Boolean := False;
12200 -- Flag set when a state declaration with options is not properly
12201 -- parenthesized.
12203 -- Flags used to verify the consistency of states
12205 Non_Null_Seen : Boolean := False;
12206 Null_Seen : Boolean := False;
12208 procedure Analyze_Abstract_State
12209 (State : Node_Id;
12210 Pack_Id : Entity_Id);
12211 -- Verify the legality of a single state declaration. Create and
12212 -- decorate a state abstraction entity and introduce it into the
12213 -- visibility chain. Pack_Id denotes the entity or the related
12214 -- package where pragma Abstract_State appears.
12216 procedure Malformed_State_Error (State : Node_Id);
12217 -- Emit an error concerning the illegal declaration of abstract
12218 -- state State. This routine diagnoses syntax errors that lead to
12219 -- a different parse tree. The error is issued regardless of the
12220 -- SPARK mode in effect.
12222 ----------------------------
12223 -- Analyze_Abstract_State --
12224 ----------------------------
12226 procedure Analyze_Abstract_State
12227 (State : Node_Id;
12228 Pack_Id : Entity_Id)
12230 -- Flags used to verify the consistency of options
12232 AR_Seen : Boolean := False;
12233 AW_Seen : Boolean := False;
12234 ER_Seen : Boolean := False;
12235 EW_Seen : Boolean := False;
12236 External_Seen : Boolean := False;
12237 Ghost_Seen : Boolean := False;
12238 Others_Seen : Boolean := False;
12239 Part_Of_Seen : Boolean := False;
12240 Relaxed_Initialization_Seen : Boolean := False;
12241 Synchronous_Seen : Boolean := False;
12243 -- Flags used to store the static value of all external states'
12244 -- expressions.
12246 AR_Val : Boolean := False;
12247 AW_Val : Boolean := False;
12248 ER_Val : Boolean := False;
12249 EW_Val : Boolean := False;
12251 State_Id : Entity_Id := Empty;
12252 -- The entity to be generated for the current state declaration
12254 procedure Analyze_External_Option (Opt : Node_Id);
12255 -- Verify the legality of option External
12257 procedure Analyze_External_Property
12258 (Prop : Node_Id;
12259 Expr : Node_Id := Empty);
12260 -- Verify the legailty of a single external property. Prop
12261 -- denotes the external property. Expr is the expression used
12262 -- to set the property.
12264 procedure Analyze_Part_Of_Option (Opt : Node_Id);
12265 -- Verify the legality of option Part_Of
12267 procedure Check_Duplicate_Option
12268 (Opt : Node_Id;
12269 Status : in out Boolean);
12270 -- Flag Status denotes whether a particular option has been
12271 -- seen while processing a state. This routine verifies that
12272 -- Opt is not a duplicate option and sets the flag Status
12273 -- (SPARK RM 7.1.4(1)).
12275 procedure Check_Duplicate_Property
12276 (Prop : Node_Id;
12277 Status : in out Boolean);
12278 -- Flag Status denotes whether a particular property has been
12279 -- seen while processing option External. This routine verifies
12280 -- that Prop is not a duplicate property and sets flag Status.
12281 -- Opt is not a duplicate property and sets the flag Status.
12282 -- (SPARK RM 7.1.4(2))
12284 procedure Check_Ghost_Synchronous;
12285 -- Ensure that the abstract state is not subject to both Ghost
12286 -- and Synchronous simple options. Emit an error if this is the
12287 -- case.
12289 procedure Create_Abstract_State
12290 (Nam : Name_Id;
12291 Decl : Node_Id;
12292 Loc : Source_Ptr;
12293 Is_Null : Boolean);
12294 -- Generate an abstract state entity with name Nam and enter it
12295 -- into visibility. Decl is the "declaration" of the state as
12296 -- it appears in pragma Abstract_State. Loc is the location of
12297 -- the related state "declaration". Flag Is_Null should be set
12298 -- when the associated Abstract_State pragma defines a null
12299 -- state.
12301 -----------------------------
12302 -- Analyze_External_Option --
12303 -----------------------------
12305 procedure Analyze_External_Option (Opt : Node_Id) is
12306 Errors : constant Nat := Serious_Errors_Detected;
12307 Prop : Node_Id;
12308 Props : Node_Id := Empty;
12310 begin
12311 if Nkind (Opt) = N_Component_Association then
12312 Props := Expression (Opt);
12313 end if;
12315 -- External state with properties
12317 if Present (Props) then
12319 -- Multiple properties appear as an aggregate
12321 if Nkind (Props) = N_Aggregate then
12323 -- Simple property form
12325 Prop := First (Expressions (Props));
12326 while Present (Prop) loop
12327 Analyze_External_Property (Prop);
12328 Next (Prop);
12329 end loop;
12331 -- Property with expression form
12333 Prop := First (Component_Associations (Props));
12334 while Present (Prop) loop
12335 Analyze_External_Property
12336 (Prop => First (Choices (Prop)),
12337 Expr => Expression (Prop));
12339 Next (Prop);
12340 end loop;
12342 -- Single property
12344 else
12345 Analyze_External_Property (Props);
12346 end if;
12348 -- An external state defined without any properties defaults
12349 -- all properties to True.
12351 else
12352 AR_Val := True;
12353 AW_Val := True;
12354 ER_Val := True;
12355 EW_Val := True;
12356 end if;
12358 -- Once all external properties have been processed, verify
12359 -- their mutual interaction. Do not perform the check when
12360 -- at least one of the properties is illegal as this will
12361 -- produce a bogus error.
12363 if Errors = Serious_Errors_Detected then
12364 Check_External_Properties
12365 (State, AR_Val, AW_Val, ER_Val, EW_Val);
12366 end if;
12367 end Analyze_External_Option;
12369 -------------------------------
12370 -- Analyze_External_Property --
12371 -------------------------------
12373 procedure Analyze_External_Property
12374 (Prop : Node_Id;
12375 Expr : Node_Id := Empty)
12377 Expr_Val : Boolean;
12379 begin
12380 -- Check the placement of "others" (if available)
12382 if Nkind (Prop) = N_Others_Choice then
12383 if Others_Seen then
12384 SPARK_Msg_N
12385 ("only one OTHERS choice allowed in option External",
12386 Prop);
12387 else
12388 Others_Seen := True;
12389 end if;
12391 elsif Others_Seen then
12392 SPARK_Msg_N
12393 ("OTHERS must be the last property in option External",
12394 Prop);
12396 -- The only remaining legal options are the four predefined
12397 -- external properties.
12399 elsif Nkind (Prop) = N_Identifier
12400 and then Chars (Prop) in Name_Async_Readers
12401 | Name_Async_Writers
12402 | Name_Effective_Reads
12403 | Name_Effective_Writes
12404 then
12405 null;
12407 -- Otherwise the construct is not a valid property
12409 else
12410 SPARK_Msg_N ("invalid external state property", Prop);
12411 return;
12412 end if;
12414 -- Ensure that the expression of the external state property
12415 -- is static Boolean (if applicable) (SPARK RM 7.1.2(5)).
12417 if Present (Expr) then
12418 Analyze_And_Resolve (Expr, Standard_Boolean);
12420 if Is_OK_Static_Expression (Expr) then
12421 Expr_Val := Is_True (Expr_Value (Expr));
12422 else
12423 SPARK_Msg_N
12424 ("expression of external state property must be "
12425 & "static", Expr);
12426 return;
12427 end if;
12429 -- The lack of expression defaults the property to True
12431 else
12432 Expr_Val := True;
12433 end if;
12435 -- Named properties
12437 if Nkind (Prop) = N_Identifier then
12438 if Chars (Prop) = Name_Async_Readers then
12439 Check_Duplicate_Property (Prop, AR_Seen);
12440 AR_Val := Expr_Val;
12442 elsif Chars (Prop) = Name_Async_Writers then
12443 Check_Duplicate_Property (Prop, AW_Seen);
12444 AW_Val := Expr_Val;
12446 elsif Chars (Prop) = Name_Effective_Reads then
12447 Check_Duplicate_Property (Prop, ER_Seen);
12448 ER_Val := Expr_Val;
12450 else
12451 Check_Duplicate_Property (Prop, EW_Seen);
12452 EW_Val := Expr_Val;
12453 end if;
12455 -- The handling of property "others" must take into account
12456 -- all other named properties that have been encountered so
12457 -- far. Only those that have not been seen are affected by
12458 -- "others".
12460 else
12461 if not AR_Seen then
12462 AR_Val := Expr_Val;
12463 end if;
12465 if not AW_Seen then
12466 AW_Val := Expr_Val;
12467 end if;
12469 if not ER_Seen then
12470 ER_Val := Expr_Val;
12471 end if;
12473 if not EW_Seen then
12474 EW_Val := Expr_Val;
12475 end if;
12476 end if;
12477 end Analyze_External_Property;
12479 ----------------------------
12480 -- Analyze_Part_Of_Option --
12481 ----------------------------
12483 procedure Analyze_Part_Of_Option (Opt : Node_Id) is
12484 Encap : constant Node_Id := Expression (Opt);
12485 Constits : Elist_Id;
12486 Encap_Id : Entity_Id;
12487 Legal : Boolean;
12489 begin
12490 Check_Duplicate_Option (Opt, Part_Of_Seen);
12492 Analyze_Part_Of
12493 (Indic => First (Choices (Opt)),
12494 Item_Id => State_Id,
12495 Encap => Encap,
12496 Encap_Id => Encap_Id,
12497 Legal => Legal);
12499 -- The Part_Of indicator transforms the abstract state into
12500 -- a constituent of the encapsulating state or single
12501 -- concurrent type.
12503 if Legal then
12504 pragma Assert (Present (Encap_Id));
12505 Constits := Part_Of_Constituents (Encap_Id);
12507 if No (Constits) then
12508 Constits := New_Elmt_List;
12509 Set_Part_Of_Constituents (Encap_Id, Constits);
12510 end if;
12512 Append_Elmt (State_Id, Constits);
12513 Set_Encapsulating_State (State_Id, Encap_Id);
12514 end if;
12515 end Analyze_Part_Of_Option;
12517 ----------------------------
12518 -- Check_Duplicate_Option --
12519 ----------------------------
12521 procedure Check_Duplicate_Option
12522 (Opt : Node_Id;
12523 Status : in out Boolean)
12525 begin
12526 if Status then
12527 SPARK_Msg_N ("duplicate state option", Opt);
12528 end if;
12530 Status := True;
12531 end Check_Duplicate_Option;
12533 ------------------------------
12534 -- Check_Duplicate_Property --
12535 ------------------------------
12537 procedure Check_Duplicate_Property
12538 (Prop : Node_Id;
12539 Status : in out Boolean)
12541 begin
12542 if Status then
12543 SPARK_Msg_N ("duplicate external property", Prop);
12544 end if;
12546 Status := True;
12547 end Check_Duplicate_Property;
12549 -----------------------------
12550 -- Check_Ghost_Synchronous --
12551 -----------------------------
12553 procedure Check_Ghost_Synchronous is
12554 begin
12555 -- A synchronized abstract state cannot be Ghost and vice
12556 -- versa (SPARK RM 6.9(19)).
12558 if Ghost_Seen and Synchronous_Seen then
12559 SPARK_Msg_N ("synchronized state cannot be ghost", State);
12560 end if;
12561 end Check_Ghost_Synchronous;
12563 ---------------------------
12564 -- Create_Abstract_State --
12565 ---------------------------
12567 procedure Create_Abstract_State
12568 (Nam : Name_Id;
12569 Decl : Node_Id;
12570 Loc : Source_Ptr;
12571 Is_Null : Boolean)
12573 begin
12574 -- The abstract state may be semi-declared when the related
12575 -- package was withed through a limited with clause. In that
12576 -- case reuse the entity to fully declare the state.
12578 if Present (Decl) and then Present (Entity (Decl)) then
12579 State_Id := Entity (Decl);
12581 -- Otherwise the elaboration of pragma Abstract_State
12582 -- declares the state.
12584 else
12585 State_Id := Make_Defining_Identifier (Loc, Nam);
12587 if Present (Decl) then
12588 Set_Entity (Decl, State_Id);
12589 end if;
12590 end if;
12592 -- Null states never come from source
12594 Set_Comes_From_Source (State_Id, not Is_Null);
12595 Set_Parent (State_Id, State);
12596 Mutate_Ekind (State_Id, E_Abstract_State);
12597 Set_Is_Not_Self_Hidden (State_Id);
12598 Set_Etype (State_Id, Standard_Void_Type);
12599 Set_Encapsulating_State (State_Id, Empty);
12601 -- Set the SPARK mode from the current context
12603 Set_SPARK_Pragma (State_Id, SPARK_Mode_Pragma);
12604 Set_SPARK_Pragma_Inherited (State_Id);
12606 -- An abstract state declared within a Ghost region becomes
12607 -- Ghost (SPARK RM 6.9(2)).
12609 if Ghost_Mode > None or else Is_Ghost_Entity (Pack_Id) then
12610 Set_Is_Ghost_Entity (State_Id);
12611 end if;
12613 -- Establish a link between the state declaration and the
12614 -- abstract state entity. Note that a null state remains as
12615 -- N_Null and does not carry any linkages.
12617 if not Is_Null then
12618 if Present (Decl) then
12619 Set_Entity (Decl, State_Id);
12620 Set_Etype (Decl, Standard_Void_Type);
12621 end if;
12623 -- Every non-null state must be defined, nameable and
12624 -- resolvable.
12626 Push_Scope (Pack_Id);
12627 Generate_Definition (State_Id);
12628 Enter_Name (State_Id);
12629 Pop_Scope;
12630 end if;
12631 end Create_Abstract_State;
12633 -- Local variables
12635 Opt : Node_Id;
12636 Opt_Nam : Node_Id;
12638 -- Start of processing for Analyze_Abstract_State
12640 begin
12641 -- A package with a null abstract state is not allowed to
12642 -- declare additional states.
12644 if Null_Seen then
12645 SPARK_Msg_NE
12646 ("package & has null abstract state", State, Pack_Id);
12648 -- Null states appear as internally generated entities
12650 elsif Nkind (State) = N_Null then
12651 Create_Abstract_State
12652 (Nam => New_Internal_Name ('S'),
12653 Decl => Empty,
12654 Loc => Sloc (State),
12655 Is_Null => True);
12656 Null_Seen := True;
12658 -- Catch a case where a null state appears in a list of
12659 -- non-null states.
12661 if Non_Null_Seen then
12662 SPARK_Msg_NE
12663 ("package & has non-null abstract state",
12664 State, Pack_Id);
12665 end if;
12667 -- Simple state declaration
12669 elsif Nkind (State) = N_Identifier then
12670 Create_Abstract_State
12671 (Nam => Chars (State),
12672 Decl => State,
12673 Loc => Sloc (State),
12674 Is_Null => False);
12675 Non_Null_Seen := True;
12677 -- State declaration with various options. This construct
12678 -- appears as an extension aggregate in the tree.
12680 elsif Nkind (State) = N_Extension_Aggregate then
12681 if Nkind (Ancestor_Part (State)) = N_Identifier then
12682 Create_Abstract_State
12683 (Nam => Chars (Ancestor_Part (State)),
12684 Decl => Ancestor_Part (State),
12685 Loc => Sloc (Ancestor_Part (State)),
12686 Is_Null => False);
12687 Non_Null_Seen := True;
12688 else
12689 SPARK_Msg_N
12690 ("state name must be an identifier",
12691 Ancestor_Part (State));
12692 end if;
12694 -- Options External, Ghost and Synchronous appear as
12695 -- expressions.
12697 Opt := First (Expressions (State));
12698 while Present (Opt) loop
12699 if Nkind (Opt) = N_Identifier then
12701 -- External
12703 if Chars (Opt) = Name_External then
12704 Check_Duplicate_Option (Opt, External_Seen);
12705 Analyze_External_Option (Opt);
12707 -- Ghost
12709 elsif Chars (Opt) = Name_Ghost then
12710 Check_Duplicate_Option (Opt, Ghost_Seen);
12711 Check_Ghost_Synchronous;
12713 if Present (State_Id) then
12714 Set_Is_Ghost_Entity (State_Id);
12715 end if;
12717 -- Synchronous
12719 elsif Chars (Opt) = Name_Synchronous then
12720 Check_Duplicate_Option (Opt, Synchronous_Seen);
12721 Check_Ghost_Synchronous;
12723 -- Relaxed_Initialization
12725 elsif Chars (Opt) = Name_Relaxed_Initialization then
12726 Check_Duplicate_Option
12727 (Opt, Relaxed_Initialization_Seen);
12729 -- Option Part_Of without an encapsulating state is
12730 -- illegal (SPARK RM 7.1.4(8)).
12732 elsif Chars (Opt) = Name_Part_Of then
12733 SPARK_Msg_N
12734 ("indicator Part_Of must denote abstract state, "
12735 & "single protected type or single task type",
12736 Opt);
12738 -- Do not emit an error message when a previous state
12739 -- declaration with options was not parenthesized as
12740 -- the option is actually another state declaration.
12742 -- with Abstract_State
12743 -- (State_1 with ..., -- missing parentheses
12744 -- (State_2 with ...),
12745 -- State_3) -- ok state declaration
12747 elsif Missing_Parentheses then
12748 null;
12750 -- Otherwise the option is not allowed. Note that it
12751 -- is not possible to distinguish between an option
12752 -- and a state declaration when a previous state with
12753 -- options not properly parentheses.
12755 -- with Abstract_State
12756 -- (State_1 with ..., -- missing parentheses
12757 -- State_2); -- could be an option
12759 else
12760 SPARK_Msg_N
12761 ("simple option not allowed in state declaration",
12762 Opt);
12763 end if;
12765 -- Catch a case where missing parentheses around a state
12766 -- declaration with options cause a subsequent state
12767 -- declaration with options to be treated as an option.
12769 -- with Abstract_State
12770 -- (State_1 with ..., -- missing parentheses
12771 -- (State_2 with ...))
12773 elsif Nkind (Opt) = N_Extension_Aggregate then
12774 Missing_Parentheses := True;
12775 SPARK_Msg_N
12776 ("state declaration must be parenthesized",
12777 Ancestor_Part (State));
12779 -- Otherwise the option is malformed
12781 else
12782 SPARK_Msg_N ("malformed option", Opt);
12783 end if;
12785 Next (Opt);
12786 end loop;
12788 -- Options External and Part_Of appear as component
12789 -- associations.
12791 Opt := First (Component_Associations (State));
12792 while Present (Opt) loop
12793 Opt_Nam := First (Choices (Opt));
12795 if Nkind (Opt_Nam) = N_Identifier then
12796 if Chars (Opt_Nam) = Name_External then
12797 Analyze_External_Option (Opt);
12799 elsif Chars (Opt_Nam) = Name_Part_Of then
12800 Analyze_Part_Of_Option (Opt);
12802 else
12803 SPARK_Msg_N ("invalid state option", Opt);
12804 end if;
12805 else
12806 SPARK_Msg_N ("invalid state option", Opt);
12807 end if;
12809 Next (Opt);
12810 end loop;
12812 -- Any other attempt to declare a state is illegal
12814 else
12815 Malformed_State_Error (State);
12816 return;
12817 end if;
12819 -- Guard against a junk state. In such cases no entity is
12820 -- generated and the subsequent checks cannot be applied.
12822 if Present (State_Id) then
12824 -- Verify whether the state does not introduce an illegal
12825 -- hidden state within a package subject to a null abstract
12826 -- state.
12828 Check_No_Hidden_State (State_Id);
12830 -- Check whether the lack of option Part_Of agrees with the
12831 -- placement of the abstract state with respect to the state
12832 -- space.
12834 if not Part_Of_Seen then
12835 Check_Missing_Part_Of (State_Id);
12836 end if;
12838 -- Associate the state with its related package
12840 if No (Abstract_States (Pack_Id)) then
12841 Set_Abstract_States (Pack_Id, New_Elmt_List);
12842 end if;
12844 Append_Elmt (State_Id, Abstract_States (Pack_Id));
12845 end if;
12846 end Analyze_Abstract_State;
12848 ---------------------------
12849 -- Malformed_State_Error --
12850 ---------------------------
12852 procedure Malformed_State_Error (State : Node_Id) is
12853 begin
12854 Error_Msg_N ("malformed abstract state declaration", State);
12856 -- An abstract state with a simple option is being declared
12857 -- with "=>" rather than the legal "with". The state appears
12858 -- as a component association.
12860 if Nkind (State) = N_Component_Association then
12861 Error_Msg_N ("\use WITH to specify simple option", State);
12862 end if;
12863 end Malformed_State_Error;
12865 -- Local variables
12867 Pack_Decl : Node_Id;
12868 Pack_Id : Entity_Id;
12869 State : Node_Id;
12870 States : Node_Id;
12872 -- Start of processing for Abstract_State
12874 begin
12875 GNAT_Pragma;
12876 Check_No_Identifiers;
12877 Check_Arg_Count (1);
12879 Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
12881 if Nkind (Pack_Decl) not in
12882 N_Generic_Package_Declaration | N_Package_Declaration
12883 then
12884 Pragma_Misplaced;
12885 end if;
12887 Pack_Id := Defining_Entity (Pack_Decl);
12889 -- A pragma that applies to a Ghost entity becomes Ghost for the
12890 -- purposes of legality checks and removal of ignored Ghost code.
12892 Mark_Ghost_Pragma (N, Pack_Id);
12893 Ensure_Aggregate_Form (Get_Argument (N, Pack_Id));
12895 -- Chain the pragma on the contract for completeness
12897 Add_Contract_Item (N, Pack_Id);
12899 -- The legality checks of pragmas Abstract_State, Initializes, and
12900 -- Initial_Condition are affected by the SPARK mode in effect. In
12901 -- addition, these three pragmas are subject to an inherent order:
12903 -- 1) Abstract_State
12904 -- 2) Initializes
12905 -- 3) Initial_Condition
12907 -- Analyze all these pragmas in the order outlined above
12909 Analyze_If_Present (Pragma_SPARK_Mode);
12910 States := Expression (Get_Argument (N, Pack_Id));
12912 -- Multiple non-null abstract states appear as an aggregate
12914 if Nkind (States) = N_Aggregate then
12915 State := First (Expressions (States));
12916 while Present (State) loop
12917 Analyze_Abstract_State (State, Pack_Id);
12918 Next (State);
12919 end loop;
12921 -- An abstract state with a simple option is being illegaly
12922 -- declared with "=>" rather than "with". In this case the
12923 -- state declaration appears as a component association.
12925 if Present (Component_Associations (States)) then
12926 State := First (Component_Associations (States));
12927 while Present (State) loop
12928 Malformed_State_Error (State);
12929 Next (State);
12930 end loop;
12931 end if;
12933 -- Various forms of a single abstract state. Note that these may
12934 -- include malformed state declarations.
12936 else
12937 Analyze_Abstract_State (States, Pack_Id);
12938 end if;
12940 Analyze_If_Present (Pragma_Initializes);
12941 Analyze_If_Present (Pragma_Initial_Condition);
12942 end Abstract_State;
12944 ------------
12945 -- Ada_83 --
12946 ------------
12948 -- pragma Ada_83;
12950 -- Note: this pragma also has some specific processing in Par.Prag
12951 -- because we want to set the Ada version mode during parsing.
12953 when Pragma_Ada_83 =>
12954 GNAT_Pragma;
12955 Check_Arg_Count (0);
12957 -- We really should check unconditionally for proper configuration
12958 -- pragma placement, since we really don't want mixed Ada modes
12959 -- within a single unit, and the GNAT reference manual has always
12960 -- said this was a configuration pragma, but we did not check and
12961 -- are hesitant to add the check now.
12963 -- However, we really cannot tolerate mixing Ada 2005 or Ada 2012
12964 -- with Ada 83 or Ada 95, so we must check if we are in Ada 2005
12965 -- or Ada 2012 mode.
12967 if Ada_Version >= Ada_2005 then
12968 Check_Valid_Configuration_Pragma;
12969 end if;
12971 -- Now set Ada 83 mode
12973 if Latest_Ada_Only then
12974 Error_Pragma ("??pragma% ignored");
12975 else
12976 Ada_Version := Ada_83;
12977 Ada_Version_Explicit := Ada_83;
12978 Ada_Version_Pragma := N;
12979 end if;
12981 ------------
12982 -- Ada_95 --
12983 ------------
12985 -- pragma Ada_95;
12987 -- Note: this pragma also has some specific processing in Par.Prag
12988 -- because we want to set the Ada 83 version mode during parsing.
12990 when Pragma_Ada_95 =>
12991 GNAT_Pragma;
12992 Check_Arg_Count (0);
12994 -- We really should check unconditionally for proper configuration
12995 -- pragma placement, since we really don't want mixed Ada modes
12996 -- within a single unit, and the GNAT reference manual has always
12997 -- said this was a configuration pragma, but we did not check and
12998 -- are hesitant to add the check now.
13000 -- However, we really cannot tolerate mixing Ada 2005 with Ada 83
13001 -- or Ada 95, so we must check if we are in Ada 2005 mode.
13003 if Ada_Version >= Ada_2005 then
13004 Check_Valid_Configuration_Pragma;
13005 end if;
13007 -- Now set Ada 95 mode
13009 if Latest_Ada_Only then
13010 Error_Pragma ("??pragma% ignored");
13011 else
13012 Ada_Version := Ada_95;
13013 Ada_Version_Explicit := Ada_95;
13014 Ada_Version_Pragma := N;
13015 end if;
13017 ---------------------
13018 -- Ada_05/Ada_2005 --
13019 ---------------------
13021 -- pragma Ada_05;
13022 -- pragma Ada_05 (LOCAL_NAME);
13024 -- pragma Ada_2005;
13025 -- pragma Ada_2005 (LOCAL_NAME):
13027 -- Note: these pragmas also have some specific processing in Par.Prag
13028 -- because we want to set the Ada 2005 version mode during parsing.
13030 -- The one argument form is used for managing the transition from
13031 -- Ada 95 to Ada 2005 in the run-time library. If an entity is marked
13032 -- as Ada_2005 only, then referencing the entity in Ada_83 or Ada_95
13033 -- mode will generate a warning. In addition, in Ada_83 or Ada_95
13034 -- mode, a preference rule is established which does not choose
13035 -- such an entity unless it is unambiguously specified. This avoids
13036 -- extra subprograms marked this way from generating ambiguities in
13037 -- otherwise legal pre-Ada_2005 programs. The one argument form is
13038 -- intended for exclusive use in the GNAT run-time library.
13040 when Pragma_Ada_05
13041 | Pragma_Ada_2005
13043 declare
13044 E_Id : Node_Id;
13046 begin
13047 GNAT_Pragma;
13049 if Arg_Count = 1 then
13050 Check_Arg_Is_Local_Name (Arg1);
13051 E_Id := Get_Pragma_Arg (Arg1);
13053 if Etype (E_Id) = Any_Type then
13054 return;
13055 end if;
13057 Set_Is_Ada_2005_Only (Entity (E_Id));
13058 Record_Rep_Item (Entity (E_Id), N);
13060 else
13061 Check_Arg_Count (0);
13063 -- For Ada_2005 we unconditionally enforce the documented
13064 -- configuration pragma placement, since we do not want to
13065 -- tolerate mixed modes in a unit involving Ada 2005. That
13066 -- would cause real difficulties for those cases where there
13067 -- are incompatibilities between Ada 95 and Ada 2005.
13069 Check_Valid_Configuration_Pragma;
13071 -- Now set appropriate Ada mode
13073 if Latest_Ada_Only then
13074 Error_Pragma ("??pragma% ignored");
13075 else
13076 Ada_Version := Ada_2005;
13077 Ada_Version_Explicit := Ada_2005;
13078 Ada_Version_Pragma := N;
13079 end if;
13080 end if;
13081 end;
13083 ---------------------
13084 -- Ada_12/Ada_2012 --
13085 ---------------------
13087 -- pragma Ada_12;
13088 -- pragma Ada_12 (LOCAL_NAME);
13090 -- pragma Ada_2012;
13091 -- pragma Ada_2012 (LOCAL_NAME):
13093 -- Note: these pragmas also have some specific processing in Par.Prag
13094 -- because we want to set the Ada 2012 version mode during parsing.
13096 -- The one argument form is used for managing the transition from Ada
13097 -- 2005 to Ada 2012 in the run-time library. If an entity is marked
13098 -- as Ada_2012 only, then referencing the entity in any pre-Ada_2012
13099 -- mode will generate a warning. In addition, in any pre-Ada_2012
13100 -- mode, a preference rule is established which does not choose
13101 -- such an entity unless it is unambiguously specified. This avoids
13102 -- extra subprograms marked this way from generating ambiguities in
13103 -- otherwise legal pre-Ada_2012 programs. The one argument form is
13104 -- intended for exclusive use in the GNAT run-time library.
13106 when Pragma_Ada_12
13107 | Pragma_Ada_2012
13109 declare
13110 E_Id : Node_Id;
13112 begin
13113 GNAT_Pragma;
13115 if Arg_Count = 1 then
13116 Check_Arg_Is_Local_Name (Arg1);
13117 E_Id := Get_Pragma_Arg (Arg1);
13119 if Etype (E_Id) = Any_Type then
13120 return;
13121 end if;
13123 Set_Is_Ada_2012_Only (Entity (E_Id));
13124 Record_Rep_Item (Entity (E_Id), N);
13126 else
13127 Check_Arg_Count (0);
13129 -- For Ada_2012 we unconditionally enforce the documented
13130 -- configuration pragma placement, since we do not want to
13131 -- tolerate mixed modes in a unit involving Ada 2012. That
13132 -- would cause real difficulties for those cases where there
13133 -- are incompatibilities between Ada 95 and Ada 2012. We could
13134 -- allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
13136 Check_Valid_Configuration_Pragma;
13138 -- Now set appropriate Ada mode
13140 Ada_Version := Ada_2012;
13141 Ada_Version_Explicit := Ada_2012;
13142 Ada_Version_Pragma := N;
13143 end if;
13144 end;
13146 --------------
13147 -- Ada_2022 --
13148 --------------
13150 -- pragma Ada_2022;
13151 -- pragma Ada_2022 (LOCAL_NAME):
13153 -- Note: this pragma also has some specific processing in Par.Prag
13154 -- because we want to set the Ada 2022 version mode during parsing.
13156 -- The one argument form is used for managing the transition from Ada
13157 -- 2012 to Ada 2022 in the run-time library. If an entity is marked
13158 -- as Ada_2022 only, then referencing the entity in any pre-Ada_2022
13159 -- mode will generate a warning;for calls to Ada_2022 only primitives
13160 -- that require overriding an error will be reported. In addition, in
13161 -- any pre-Ada_2022 mode, a preference rule is established which does
13162 -- not choose such an entity unless it is unambiguously specified.
13163 -- This avoids extra subprograms marked this way from generating
13164 -- ambiguities in otherwise legal pre-Ada 2022 programs. The one
13165 -- argument form is intended for exclusive use in the GNAT run-time
13166 -- library.
13168 when Pragma_Ada_2022 =>
13169 declare
13170 E_Id : Node_Id;
13172 begin
13173 GNAT_Pragma;
13175 if Arg_Count = 1 then
13176 Check_Arg_Is_Local_Name (Arg1);
13177 E_Id := Get_Pragma_Arg (Arg1);
13179 if Etype (E_Id) = Any_Type then
13180 return;
13181 end if;
13183 Set_Is_Ada_2022_Only (Entity (E_Id));
13184 Record_Rep_Item (Entity (E_Id), N);
13186 else
13187 Check_Arg_Count (0);
13189 -- For Ada_2022 we unconditionally enforce the documented
13190 -- configuration pragma placement, since we do not want to
13191 -- tolerate mixed modes in a unit involving Ada 2022. That
13192 -- would cause real difficulties for those cases where there
13193 -- are incompatibilities between Ada 2012 and Ada 2022. We
13194 -- could allow mixing of Ada 2012 and Ada 2022 but it's not
13195 -- worth it.
13197 Check_Valid_Configuration_Pragma;
13199 -- Now set appropriate Ada mode
13201 Ada_Version := Ada_2022;
13202 Ada_Version_Explicit := Ada_2022;
13203 Ada_Version_Pragma := N;
13204 end if;
13205 end;
13207 -------------------------------------
13208 -- Aggregate_Individually_Assign --
13209 -------------------------------------
13211 -- pragma Aggregate_Individually_Assign;
13213 when Pragma_Aggregate_Individually_Assign =>
13214 GNAT_Pragma;
13215 Check_Arg_Count (0);
13216 Check_Valid_Configuration_Pragma;
13217 Aggregate_Individually_Assign := True;
13219 ----------------------
13220 -- All_Calls_Remote --
13221 ----------------------
13223 -- pragma All_Calls_Remote [(library_package_NAME)];
13225 when Pragma_All_Calls_Remote => All_Calls_Remote : declare
13226 Lib_Entity : Entity_Id;
13228 begin
13229 Check_Ada_83_Warning;
13230 Check_Valid_Library_Unit_Pragma;
13232 -- If N was rewritten as a null statement there is nothing more
13233 -- to do.
13235 if Nkind (N) = N_Null_Statement then
13236 return;
13237 end if;
13239 Lib_Entity := Find_Lib_Unit_Name;
13241 -- A pragma that applies to a Ghost entity becomes Ghost for the
13242 -- purposes of legality checks and removal of ignored Ghost code.
13244 Mark_Ghost_Pragma (N, Lib_Entity);
13246 -- This pragma should only apply to a RCI unit (RM E.2.3(23))
13248 if Present (Lib_Entity) and then not Debug_Flag_U then
13249 if not Is_Remote_Call_Interface (Lib_Entity) then
13250 Error_Pragma ("pragma% only apply to rci unit");
13252 -- Set flag for entity of the library unit
13254 else
13255 Set_Has_All_Calls_Remote (Lib_Entity);
13256 end if;
13257 end if;
13258 end All_Calls_Remote;
13260 ---------------------------
13261 -- Allow_Integer_Address --
13262 ---------------------------
13264 -- pragma Allow_Integer_Address;
13266 when Pragma_Allow_Integer_Address =>
13267 GNAT_Pragma;
13268 Check_Valid_Configuration_Pragma;
13269 Check_Arg_Count (0);
13271 -- If Address is a private type, then set the flag to allow
13272 -- integer address values. If Address is not private, then this
13273 -- pragma has no purpose, so it is simply ignored. Not clear if
13274 -- there are any such targets now.
13276 if Opt.Address_Is_Private then
13277 Opt.Allow_Integer_Address := True;
13278 end if;
13280 -----------------------
13281 -- Always_Terminates --
13282 -----------------------
13284 -- pragma Always_Terminates [ (boolean_EXPRESSION) ];
13286 -- Characteristics:
13288 -- * Analysis - The annotation undergoes initial checks to verify
13289 -- the legal placement and context. Secondary checks preanalyze the
13290 -- expressions in:
13292 -- Analyze_Always_Terminates_Cases_In_Decl_Part
13294 -- * Expansion - The annotation is expanded during the expansion of
13295 -- the related subprogram [body] contract as performed in:
13297 -- Expand_Subprogram_Contract
13299 -- * Template - The annotation utilizes the generic template of the
13300 -- related subprogram [body] when it is:
13302 -- aspect on subprogram declaration
13303 -- aspect on stand-alone subprogram body
13304 -- pragma on stand-alone subprogram body
13306 -- The annotation must prepare its own template when it is:
13308 -- pragma on subprogram declaration
13310 -- * Globals - Capture of global references must occur after full
13311 -- analysis.
13313 -- * Instance - The annotation is instantiated automatically when
13314 -- the related generic subprogram [body] is instantiated except for
13315 -- the "pragma on subprogram declaration" case. In that scenario
13316 -- the annotation must instantiate itself.
13318 when Pragma_Always_Terminates => Always_Terminates : declare
13319 Spec_Id : Entity_Id;
13320 Subp_Decl : Node_Id;
13321 Subp_Spec : Node_Id;
13323 begin
13324 GNAT_Pragma;
13325 Check_No_Identifiers;
13326 Check_At_Most_N_Arguments (1);
13328 -- Ensure the proper placement of the pragma. Exceptional_Cases
13329 -- must be associated with a subprogram declaration or a body that
13330 -- acts as a spec.
13332 Subp_Decl :=
13333 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
13335 -- Generic subprogram and package declaration
13337 if Nkind (Subp_Decl) in N_Generic_Declaration then
13338 null;
13340 -- Package declaration
13342 elsif Nkind (Subp_Decl) = N_Package_Declaration then
13343 null;
13345 -- Body acts as spec
13347 elsif Nkind (Subp_Decl) = N_Subprogram_Body
13348 and then No (Corresponding_Spec (Subp_Decl))
13349 then
13350 null;
13352 -- Body stub acts as spec
13354 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
13355 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
13356 then
13357 null;
13359 -- Subprogram
13361 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
13362 Subp_Spec := Specification (Subp_Decl);
13364 -- Pragma Always_Terminates is forbidden on null procedures,
13365 -- as this may lead to potential ambiguities in behavior
13366 -- when interface null procedures are involved. Also, it
13367 -- just wouldn't make sense, because null procedures always
13368 -- terminate anyway.
13370 if Nkind (Subp_Spec) = N_Procedure_Specification
13371 and then Null_Present (Subp_Spec)
13372 then
13373 Error_Msg_N (Fix_Error
13374 ("pragma % cannot apply to null procedure"), N);
13375 return;
13376 end if;
13378 -- Entry
13380 elsif Nkind (Subp_Decl) = N_Entry_Declaration then
13381 null;
13383 else
13384 Pragma_Misplaced;
13385 end if;
13387 Spec_Id := Unique_Defining_Entity (Subp_Decl);
13389 -- Pragma Always_Terminates is not allowed on functions
13391 if Ekind (Spec_Id) = E_Function then
13392 Error_Msg_N (Fix_Error
13393 ("pragma % cannot apply to function"), N);
13394 return;
13396 elsif Ekind (Spec_Id) = E_Generic_Function then
13397 Error_Msg_N (Fix_Error
13398 ("pragma % cannot apply to generic function"), N);
13399 return;
13400 end if;
13402 -- Pragma Always_Terminates applied to packages doesn't allow any
13403 -- expression.
13405 if Is_Package_Or_Generic_Package (Spec_Id)
13406 and then Arg_Count /= 0
13407 then
13408 Error_Msg_N (Fix_Error
13409 ("pragma % applied to package cannot have arguments"), N);
13410 return;
13411 end if;
13413 -- A pragma that applies to a Ghost entity becomes Ghost for the
13414 -- purposes of legality checks and removal of ignored Ghost code.
13416 Mark_Ghost_Pragma (N, Spec_Id);
13418 -- Chain the pragma on the contract for further processing by
13419 -- Analyze_Always_Terminates_In_Decl_Part.
13421 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
13423 -- Fully analyze the pragma when it appears inside a subprogram
13424 -- body because it cannot benefit from forward references.
13426 if Nkind (Subp_Decl) in N_Subprogram_Body
13427 | N_Subprogram_Body_Stub
13428 then
13429 -- The legality checks of pragma Always_Terminates are affected
13430 -- by the SPARK mode in effect and the volatility of the
13431 -- context. Analyze all pragmas in a specific order.
13433 Analyze_If_Present (Pragma_SPARK_Mode);
13434 Analyze_If_Present (Pragma_Volatile_Function);
13435 Analyze_Always_Terminates_In_Decl_Part (N);
13436 end if;
13437 end Always_Terminates;
13439 --------------
13440 -- Annotate --
13441 --------------
13443 -- pragma Annotate
13444 -- (IDENTIFIER [, IDENTIFIER {, ARG}] [,Entity => local_NAME]);
13445 -- ARG ::= NAME | EXPRESSION
13447 -- The first two arguments are by convention intended to refer to an
13448 -- external tool and a tool-specific function. These arguments are
13449 -- not analyzed.
13451 when Pragma_Annotate | Pragma_GNAT_Annotate => Annotate : declare
13452 Arg : Node_Id;
13453 Expr : Node_Id;
13454 Nam_Arg : Node_Id;
13456 --------------------------
13457 -- Inferred_String_Type --
13458 --------------------------
13460 function Preferred_String_Type (Expr : Node_Id) return Entity_Id;
13461 -- Infer the type to use for a string literal or a concatentation
13462 -- of operands whose types can be inferred. For such expressions,
13463 -- returns the "narrowest" of the three predefined string types
13464 -- that can represent the characters occurring in the expression.
13465 -- For other expressions, returns Empty.
13467 function Preferred_String_Type (Expr : Node_Id) return Entity_Id is
13468 begin
13469 case Nkind (Expr) is
13470 when N_String_Literal =>
13471 if Has_Wide_Wide_Character (Expr) then
13472 return Standard_Wide_Wide_String;
13473 elsif Has_Wide_Character (Expr) then
13474 return Standard_Wide_String;
13475 else
13476 return Standard_String;
13477 end if;
13479 when N_Op_Concat =>
13480 declare
13481 L_Type : constant Entity_Id
13482 := Preferred_String_Type (Left_Opnd (Expr));
13483 R_Type : constant Entity_Id
13484 := Preferred_String_Type (Right_Opnd (Expr));
13486 Type_Table : constant array (1 .. 4) of Entity_Id
13487 := (Empty,
13488 Standard_Wide_Wide_String,
13489 Standard_Wide_String,
13490 Standard_String);
13491 begin
13492 for Idx in Type_Table'Range loop
13493 if L_Type = Type_Table (Idx) or
13494 R_Type = Type_Table (Idx)
13495 then
13496 return Type_Table (Idx);
13497 end if;
13498 end loop;
13499 raise Program_Error;
13500 end;
13502 when others =>
13503 return Empty;
13504 end case;
13505 end Preferred_String_Type;
13506 begin
13507 GNAT_Pragma;
13508 Check_At_Least_N_Arguments (1);
13510 Nam_Arg := Last (Pragma_Argument_Associations (N));
13512 -- Determine whether the last argument is "Entity => local_NAME"
13513 -- and if it is, perform the required semantic checks. Remove the
13514 -- argument from further processing.
13516 if Nkind (Nam_Arg) = N_Pragma_Argument_Association
13517 and then Chars (Nam_Arg) = Name_Entity
13518 then
13519 Check_Arg_Is_Local_Name (Nam_Arg);
13520 Arg_Count := Arg_Count - 1;
13522 -- A pragma that applies to a Ghost entity becomes Ghost for
13523 -- the purposes of legality checks and removal of ignored Ghost
13524 -- code.
13526 if Is_Entity_Name (Get_Pragma_Arg (Nam_Arg))
13527 and then Present (Entity (Get_Pragma_Arg (Nam_Arg)))
13528 then
13529 Mark_Ghost_Pragma (N, Entity (Get_Pragma_Arg (Nam_Arg)));
13530 end if;
13531 end if;
13533 -- Continue the processing with last argument removed for now
13535 Check_Arg_Is_Identifier (Arg1);
13536 Check_No_Identifiers;
13537 Store_Note (N);
13539 -- The second parameter is optional, it is never analyzed
13541 if No (Arg2) then
13542 null;
13544 -- Otherwise there is a second parameter
13546 else
13547 -- The second parameter must be an identifier
13549 Check_Arg_Is_Identifier (Arg2);
13551 -- Process the remaining parameters (if any)
13553 Arg := Next (Arg2);
13554 while Present (Arg) loop
13555 Expr := Get_Pragma_Arg (Arg);
13556 Analyze (Expr);
13558 if Is_Entity_Name (Expr) then
13559 null;
13561 -- For string literals and concatenations of string literals
13562 -- we assume Standard_String as the type, unless the string
13563 -- contains wide or wide_wide characters.
13565 elsif Present (Preferred_String_Type (Expr)) then
13566 Resolve (Expr, Preferred_String_Type (Expr));
13568 elsif Is_Overloaded (Expr) then
13569 Error_Pragma_Arg ("ambiguous argument for pragma%", Expr);
13571 else
13572 Resolve (Expr);
13573 end if;
13575 Next (Arg);
13576 end loop;
13577 end if;
13578 end Annotate;
13580 -------------------------------------------------
13581 -- Assert/Assert_And_Cut/Assume/Loop_Invariant --
13582 -------------------------------------------------
13584 -- pragma Assert
13585 -- ( [Check => ] Boolean_EXPRESSION
13586 -- [, [Message =>] Static_String_EXPRESSION]);
13588 -- pragma Assert_And_Cut
13589 -- ( [Check => ] Boolean_EXPRESSION
13590 -- [, [Message =>] Static_String_EXPRESSION]);
13592 -- pragma Assume
13593 -- ( [Check => ] Boolean_EXPRESSION
13594 -- [, [Message =>] Static_String_EXPRESSION]);
13596 -- pragma Loop_Invariant
13597 -- ( [Check => ] Boolean_EXPRESSION
13598 -- [, [Message =>] Static_String_EXPRESSION]);
13600 when Pragma_Assert
13601 | Pragma_Assert_And_Cut
13602 | Pragma_Assume
13603 | Pragma_Loop_Invariant
13605 Assert : declare
13606 function Contains_Loop_Entry (Expr : Node_Id) return Boolean;
13607 -- Determine whether expression Expr contains a Loop_Entry
13608 -- attribute reference.
13610 -------------------------
13611 -- Contains_Loop_Entry --
13612 -------------------------
13614 function Contains_Loop_Entry (Expr : Node_Id) return Boolean is
13615 Has_Loop_Entry : Boolean := False;
13617 function Process (N : Node_Id) return Traverse_Result;
13618 -- Process function for traversal to look for Loop_Entry
13620 -------------
13621 -- Process --
13622 -------------
13624 function Process (N : Node_Id) return Traverse_Result is
13625 begin
13626 if Nkind (N) = N_Attribute_Reference
13627 and then Attribute_Name (N) = Name_Loop_Entry
13628 then
13629 Has_Loop_Entry := True;
13630 return Abandon;
13631 else
13632 return OK;
13633 end if;
13634 end Process;
13636 procedure Traverse is new Traverse_Proc (Process);
13638 -- Start of processing for Contains_Loop_Entry
13640 begin
13641 Traverse (Expr);
13642 return Has_Loop_Entry;
13643 end Contains_Loop_Entry;
13645 -- Local variables
13647 Expr : Node_Id;
13648 New_Args : List_Id;
13650 -- Start of processing for Assert
13652 begin
13653 -- Assert is an Ada 2005 RM-defined pragma
13655 if Prag_Id = Pragma_Assert then
13656 Ada_2005_Pragma;
13658 -- The remaining ones are GNAT pragmas
13660 else
13661 GNAT_Pragma;
13662 end if;
13664 Check_At_Least_N_Arguments (1);
13665 Check_At_Most_N_Arguments (2);
13666 Check_Arg_Order ((Name_Check, Name_Message));
13667 Check_Optional_Identifier (Arg1, Name_Check);
13668 Expr := Get_Pragma_Arg (Arg1);
13670 -- Special processing for Loop_Invariant, Loop_Variant or for
13671 -- other cases where a Loop_Entry attribute is present. If the
13672 -- assertion pragma contains attribute Loop_Entry, ensure that
13673 -- the related pragma is within a loop.
13675 if Prag_Id = Pragma_Loop_Invariant
13676 or else Prag_Id = Pragma_Loop_Variant
13677 or else Contains_Loop_Entry (Expr)
13678 then
13679 Check_Loop_Pragma_Placement;
13681 -- Perform preanalysis to deal with embedded Loop_Entry
13682 -- attributes.
13684 Preanalyze_Assert_Expression (Expr, Any_Boolean);
13685 end if;
13687 -- Implement Assert[_And_Cut]/Assume/Loop_Invariant by generating
13688 -- a corresponding Check pragma:
13690 -- pragma Check (name, condition [, msg]);
13692 -- Where name is the identifier matching the pragma name. So
13693 -- rewrite pragma in this manner, transfer the message argument
13694 -- if present, and analyze the result
13696 -- Note: When dealing with a semantically analyzed tree, the
13697 -- information that a Check node N corresponds to a source Assert,
13698 -- Assume, or Assert_And_Cut pragma can be retrieved from the
13699 -- pragma kind of Original_Node(N).
13701 New_Args := New_List (
13702 Make_Pragma_Argument_Association (Loc,
13703 Expression => Make_Identifier (Loc, Pname)),
13704 Make_Pragma_Argument_Association (Sloc (Expr),
13705 Expression => Expr));
13707 if Arg_Count > 1 then
13708 Check_Optional_Identifier (Arg2, Name_Message);
13710 -- Provide semantic annotations for optional argument, for
13711 -- ASIS use, before rewriting.
13712 -- Is this still needed???
13714 Preanalyze_And_Resolve (Expression (Arg2), Standard_String);
13715 Append_To (New_Args, New_Copy_Tree (Arg2));
13716 end if;
13718 -- Rewrite as Check pragma
13720 Rewrite (N,
13721 Make_Pragma (Loc,
13722 Chars => Name_Check,
13723 Pragma_Argument_Associations => New_Args));
13725 Analyze (N);
13726 end Assert;
13728 ----------------------
13729 -- Assertion_Policy --
13730 ----------------------
13732 -- pragma Assertion_Policy (POLICY_IDENTIFIER);
13734 -- The following form is Ada 2012 only, but we allow it in all modes
13736 -- Pragma Assertion_Policy (
13737 -- ASSERTION_KIND => POLICY_IDENTIFIER
13738 -- {, ASSERTION_KIND => POLICY_IDENTIFIER});
13740 -- ASSERTION_KIND ::= RM_ASSERTION_KIND | ID_ASSERTION_KIND
13742 -- RM_ASSERTION_KIND ::= Assert |
13743 -- Static_Predicate |
13744 -- Dynamic_Predicate |
13745 -- Pre |
13746 -- Pre'Class |
13747 -- Post |
13748 -- Post'Class |
13749 -- Type_Invariant |
13750 -- Type_Invariant'Class |
13751 -- Default_Initial_Condition
13753 -- ID_ASSERTION_KIND ::= Assert_And_Cut |
13754 -- Assume |
13755 -- Contract_Cases |
13756 -- Debug |
13757 -- Ghost |
13758 -- Initial_Condition |
13759 -- Loop_Invariant |
13760 -- Loop_Variant |
13761 -- Postcondition |
13762 -- Precondition |
13763 -- Predicate |
13764 -- Refined_Post |
13765 -- Statement_Assertions |
13766 -- Subprogram_Variant
13768 -- Note: The RM_ASSERTION_KIND list is language-defined, and the
13769 -- ID_ASSERTION_KIND list contains implementation-defined additions
13770 -- recognized by GNAT. The effect is to control the behavior of
13771 -- identically named aspects and pragmas, depending on the specified
13772 -- policy identifier:
13774 -- POLICY_IDENTIFIER ::= Check | Disable | Ignore | Suppressible
13776 -- Note: Check and Ignore are language-defined. Disable is a GNAT
13777 -- implementation-defined addition that results in totally ignoring
13778 -- the corresponding assertion. If Disable is specified, then the
13779 -- argument of the assertion is not even analyzed. This is useful
13780 -- when the aspect/pragma argument references entities in a with'ed
13781 -- package that is replaced by a dummy package in the final build.
13783 -- Note: the attribute forms Pre'Class, Post'Class, Invariant'Class,
13784 -- and Type_Invariant'Class were recognized by the parser and
13785 -- transformed into references to the special internal identifiers
13786 -- _Pre, _Post, _Invariant, and _Type_Invariant, so no special
13787 -- processing is required here.
13789 when Pragma_Assertion_Policy => Assertion_Policy : declare
13790 procedure Resolve_Suppressible (Policy : Node_Id);
13791 -- Converts the assertion policy 'Suppressible' to either Check or
13792 -- Ignore based on whether checks are suppressed via -gnatp.
13794 --------------------------
13795 -- Resolve_Suppressible --
13796 --------------------------
13798 procedure Resolve_Suppressible (Policy : Node_Id) is
13799 Arg : constant Node_Id := Get_Pragma_Arg (Policy);
13800 Nam : Name_Id;
13802 begin
13803 -- Transform policy argument Suppressible into either Ignore or
13804 -- Check depending on whether checks are enabled or suppressed.
13806 if Chars (Arg) = Name_Suppressible then
13807 if Suppress_Checks then
13808 Nam := Name_Ignore;
13809 else
13810 Nam := Name_Check;
13811 end if;
13813 Rewrite (Arg, Make_Identifier (Sloc (Arg), Nam));
13814 end if;
13815 end Resolve_Suppressible;
13817 -- Local variables
13819 Arg : Node_Id;
13820 Kind : Name_Id;
13821 LocP : Source_Ptr;
13822 Policy : Node_Id;
13824 begin
13825 Ada_2005_Pragma;
13827 -- This can always appear as a configuration pragma
13829 if Is_Configuration_Pragma then
13830 null;
13832 -- It can also appear in a declarative part or package spec in Ada
13833 -- 2012 mode. We allow this in other modes, but in that case we
13834 -- consider that we have an Ada 2012 pragma on our hands.
13836 else
13837 Check_Is_In_Decl_Part_Or_Package_Spec;
13838 Ada_2012_Pragma;
13839 end if;
13841 -- One argument case with no identifier (first form above)
13843 if Arg_Count = 1
13844 and then (Nkind (Arg1) /= N_Pragma_Argument_Association
13845 or else Chars (Arg1) = No_Name)
13846 then
13847 Check_Arg_Is_One_Of (Arg1,
13848 Name_Check, Name_Disable, Name_Ignore, Name_Suppressible);
13850 Resolve_Suppressible (Arg1);
13852 -- Treat one argument Assertion_Policy as equivalent to:
13854 -- pragma Check_Policy (Assertion, policy)
13856 -- So rewrite pragma in that manner and link on to the chain
13857 -- of Check_Policy pragmas, marking the pragma as analyzed.
13859 Policy := Get_Pragma_Arg (Arg1);
13861 Rewrite (N,
13862 Make_Pragma (Loc,
13863 Chars => Name_Check_Policy,
13864 Pragma_Argument_Associations => New_List (
13865 Make_Pragma_Argument_Association (Loc,
13866 Expression => Make_Identifier (Loc, Name_Assertion)),
13868 Make_Pragma_Argument_Association (Loc,
13869 Expression =>
13870 Make_Identifier (Sloc (Policy), Chars (Policy))))));
13871 Analyze (N);
13873 -- Here if we have two or more arguments
13875 else
13876 Check_At_Least_N_Arguments (1);
13877 Ada_2012_Pragma;
13879 -- Loop through arguments
13881 Arg := Arg1;
13882 while Present (Arg) loop
13883 LocP := Sloc (Arg);
13885 -- Kind must be specified
13887 if Nkind (Arg) /= N_Pragma_Argument_Association
13888 or else Chars (Arg) = No_Name
13889 then
13890 Error_Pragma_Arg
13891 ("missing assertion kind for pragma%", Arg);
13892 end if;
13894 -- Check Kind and Policy have allowed forms
13896 Kind := Chars (Arg);
13897 Policy := Get_Pragma_Arg (Arg);
13899 if not Is_Valid_Assertion_Kind (Kind) then
13900 Error_Pragma_Arg
13901 ("invalid assertion kind for pragma%", Arg);
13902 end if;
13904 Check_Arg_Is_One_Of (Arg,
13905 Name_Check, Name_Disable, Name_Ignore, Name_Suppressible);
13907 Resolve_Suppressible (Arg);
13909 if Kind = Name_Ghost then
13911 -- The Ghost policy must be either Check or Ignore
13912 -- (SPARK RM 6.9(6)).
13914 if Chars (Policy) not in Name_Check | Name_Ignore then
13915 Error_Pragma_Arg
13916 ("argument of pragma % Ghost must be Check or "
13917 & "Ignore", Policy);
13918 end if;
13920 -- Pragma Assertion_Policy specifying a Ghost policy
13921 -- cannot occur within a Ghost subprogram or package
13922 -- (SPARK RM 6.9(14)).
13924 if Ghost_Mode > None then
13925 Error_Pragma
13926 ("pragma % cannot appear within ghost subprogram or "
13927 & "package");
13928 end if;
13929 end if;
13931 -- Rewrite the Assertion_Policy pragma as a series of
13932 -- Check_Policy pragmas of the form:
13934 -- Check_Policy (Kind, Policy);
13936 -- Note: the insertion of the pragmas cannot be done with
13937 -- Insert_Action because in the configuration case, there
13938 -- are no scopes on the scope stack and the mechanism will
13939 -- fail.
13941 Insert_Before_And_Analyze (N,
13942 Make_Pragma (LocP,
13943 Chars => Name_Check_Policy,
13944 Pragma_Argument_Associations => New_List (
13945 Make_Pragma_Argument_Association (LocP,
13946 Expression => Make_Identifier (LocP, Kind)),
13947 Make_Pragma_Argument_Association (LocP,
13948 Expression => Policy))));
13950 Arg := Next (Arg);
13951 end loop;
13953 -- Rewrite the Assertion_Policy pragma as null since we have
13954 -- now inserted all the equivalent Check pragmas.
13956 Rewrite (N, Make_Null_Statement (Loc));
13957 Analyze (N);
13958 end if;
13959 end Assertion_Policy;
13961 ------------------------------
13962 -- Assume_No_Invalid_Values --
13963 ------------------------------
13965 -- pragma Assume_No_Invalid_Values (On | Off);
13967 when Pragma_Assume_No_Invalid_Values =>
13968 GNAT_Pragma;
13969 Check_Valid_Configuration_Pragma;
13970 Check_Arg_Count (1);
13971 Check_No_Identifiers;
13972 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
13974 if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
13975 Assume_No_Invalid_Values := True;
13976 else
13977 Assume_No_Invalid_Values := False;
13978 end if;
13980 --------------------------
13981 -- Attribute_Definition --
13982 --------------------------
13984 -- pragma Attribute_Definition
13985 -- ([Attribute =>] ATTRIBUTE_DESIGNATOR,
13986 -- [Entity =>] LOCAL_NAME,
13987 -- [Expression =>] EXPRESSION | NAME);
13989 when Pragma_Attribute_Definition => Attribute_Definition : declare
13990 Attribute_Designator : constant Node_Id := Get_Pragma_Arg (Arg1);
13991 Aname : Name_Id;
13993 begin
13994 GNAT_Pragma;
13995 Check_Arg_Count (3);
13996 Check_Optional_Identifier (Arg1, "attribute");
13997 Check_Optional_Identifier (Arg2, "entity");
13998 Check_Optional_Identifier (Arg3, "expression");
14000 if Nkind (Attribute_Designator) /= N_Identifier then
14001 Error_Msg_N ("attribute name expected", Attribute_Designator);
14002 return;
14003 end if;
14005 Check_Arg_Is_Local_Name (Arg2);
14007 -- If the attribute is not recognized, then issue a warning (not
14008 -- an error), and ignore the pragma.
14010 Aname := Chars (Attribute_Designator);
14012 if not Is_Attribute_Name (Aname) then
14013 Bad_Attribute (Attribute_Designator, Aname, Warn => True);
14014 return;
14015 end if;
14017 -- Otherwise, rewrite the pragma as an attribute definition clause
14019 Rewrite (N,
14020 Make_Attribute_Definition_Clause (Loc,
14021 Name => Get_Pragma_Arg (Arg2),
14022 Chars => Aname,
14023 Expression => Get_Pragma_Arg (Arg3)));
14024 Analyze (N);
14025 end Attribute_Definition;
14027 ------------------------------------------------------------------
14028 -- Async_Readers/Async_Writers/Effective_Reads/Effective_Writes --
14029 -- No_Caching --
14030 ------------------------------------------------------------------
14032 -- pragma Async_Readers [ (boolean_EXPRESSION) ];
14033 -- pragma Async_Writers [ (boolean_EXPRESSION) ];
14034 -- pragma Effective_Reads [ (boolean_EXPRESSION) ];
14035 -- pragma Effective_Writes [ (boolean_EXPRESSION) ];
14036 -- pragma No_Caching [ (boolean_EXPRESSION) ];
14038 when Pragma_Async_Readers
14039 | Pragma_Async_Writers
14040 | Pragma_Effective_Reads
14041 | Pragma_Effective_Writes
14042 | Pragma_No_Caching
14044 Async_Effective : declare
14045 Obj_Or_Type_Decl : Node_Id;
14046 Obj_Or_Type_Id : Entity_Id;
14047 begin
14048 GNAT_Pragma;
14049 Check_No_Identifiers;
14050 Check_At_Most_N_Arguments (1);
14052 Obj_Or_Type_Decl := Find_Related_Context (N, Do_Checks => True);
14054 -- Pragma must apply to a object declaration or to a type
14055 -- declaration. Original_Node is necessary to account for
14056 -- untagged derived types that are rewritten as subtypes of
14057 -- their respective root types.
14059 if Nkind (Obj_Or_Type_Decl) /= N_Object_Declaration
14060 and then Nkind (Original_Node (Obj_Or_Type_Decl)) not in
14061 N_Full_Type_Declaration |
14062 N_Private_Type_Declaration |
14063 N_Formal_Type_Declaration |
14064 N_Task_Type_Declaration |
14065 N_Protected_Type_Declaration
14066 then
14067 Pragma_Misplaced;
14068 end if;
14070 Obj_Or_Type_Id := Defining_Entity (Obj_Or_Type_Decl);
14072 -- Perform minimal verification to ensure that the argument is at
14073 -- least an object or a type. Subsequent finer grained checks will
14074 -- be done at the end of the declarative region that contains the
14075 -- pragma.
14077 if Ekind (Obj_Or_Type_Id) in E_Constant | E_Variable
14078 or else Is_Type (Obj_Or_Type_Id)
14079 then
14081 -- In the case of a type, pragma is a type-related
14082 -- representation item and so requires checks common to
14083 -- all type-related representation items.
14085 if Is_Type (Obj_Or_Type_Id)
14086 and then Rep_Item_Too_Late (Obj_Or_Type_Id, N)
14087 then
14088 return;
14089 end if;
14091 -- A pragma that applies to a Ghost entity becomes Ghost for
14092 -- the purposes of legality checks and removal of ignored Ghost
14093 -- code.
14095 Mark_Ghost_Pragma (N, Obj_Or_Type_Id);
14097 -- Chain the pragma on the contract for further processing by
14098 -- Analyze_External_Property_In_Decl_Part.
14100 Add_Contract_Item (N, Obj_Or_Type_Id);
14102 -- Analyze the Boolean expression (if any)
14104 if Present (Arg1) then
14105 Check_Static_Boolean_Expression (Get_Pragma_Arg (Arg1));
14106 end if;
14108 -- Otherwise the external property applies to a constant
14110 else
14111 Error_Pragma
14112 ("pragma % must apply to a volatile type or object");
14113 end if;
14114 end Async_Effective;
14116 ------------------
14117 -- Asynchronous --
14118 ------------------
14120 -- pragma Asynchronous (LOCAL_NAME);
14122 when Pragma_Asynchronous => Asynchronous : declare
14123 C_Ent : Entity_Id;
14124 Decl : Node_Id;
14125 Formal : Entity_Id;
14126 L : List_Id;
14127 Nm : Entity_Id;
14128 S : Node_Id;
14130 procedure Process_Async_Pragma;
14131 -- Common processing for procedure and access-to-procedure case
14133 --------------------------
14134 -- Process_Async_Pragma --
14135 --------------------------
14137 procedure Process_Async_Pragma is
14138 begin
14139 if No (L) then
14140 Set_Is_Asynchronous (Nm);
14141 return;
14142 end if;
14144 -- The formals should be of mode IN (RM E.4.1(6))
14146 S := First (L);
14147 while Present (S) loop
14148 Formal := Defining_Identifier (S);
14150 if Nkind (Formal) = N_Defining_Identifier
14151 and then Ekind (Formal) /= E_In_Parameter
14152 then
14153 Error_Pragma_Arg
14154 ("pragma% procedure can only have IN parameter",
14155 Arg1);
14156 end if;
14158 Next (S);
14159 end loop;
14161 Set_Is_Asynchronous (Nm);
14162 end Process_Async_Pragma;
14164 -- Start of processing for pragma Asynchronous
14166 begin
14167 Check_Ada_83_Warning;
14168 Check_No_Identifiers;
14169 Check_Arg_Count (1);
14170 Check_Arg_Is_Local_Name (Arg1);
14172 if Debug_Flag_U then
14173 return;
14174 end if;
14176 C_Ent := Cunit_Entity (Current_Sem_Unit);
14177 Analyze (Get_Pragma_Arg (Arg1));
14178 Nm := Entity (Get_Pragma_Arg (Arg1));
14180 -- A pragma that applies to a Ghost entity becomes Ghost for the
14181 -- purposes of legality checks and removal of ignored Ghost code.
14183 Mark_Ghost_Pragma (N, Nm);
14185 if not Is_Remote_Call_Interface (C_Ent)
14186 and then not Is_Remote_Types (C_Ent)
14187 then
14188 -- This pragma should only appear in an RCI or Remote Types
14189 -- unit (RM E.4.1(4)).
14191 Error_Pragma
14192 ("pragma% not in Remote_Call_Interface or Remote_Types unit");
14193 end if;
14195 if Ekind (Nm) = E_Procedure
14196 and then Nkind (Parent (Nm)) = N_Procedure_Specification
14197 then
14198 if not Is_Remote_Call_Interface (Nm) then
14199 Error_Pragma_Arg
14200 ("pragma% cannot be applied on non-remote procedure",
14201 Arg1);
14202 end if;
14204 L := Parameter_Specifications (Parent (Nm));
14205 Process_Async_Pragma;
14206 return;
14208 elsif Ekind (Nm) = E_Function then
14209 Error_Pragma_Arg
14210 ("pragma% cannot be applied to function", Arg1);
14212 elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
14213 if Is_Record_Type (Nm) then
14215 -- A record type that is the Equivalent_Type for a remote
14216 -- access-to-subprogram type.
14218 Decl := Declaration_Node (Corresponding_Remote_Type (Nm));
14220 else
14221 -- A non-expanded RAS type (distribution is not enabled)
14223 Decl := Declaration_Node (Nm);
14224 end if;
14226 if Nkind (Decl) = N_Full_Type_Declaration
14227 and then Nkind (Type_Definition (Decl)) =
14228 N_Access_Procedure_Definition
14229 then
14230 L := Parameter_Specifications (Type_Definition (Decl));
14231 Process_Async_Pragma;
14233 if Is_Asynchronous (Nm)
14234 and then Expander_Active
14235 and then Get_PCS_Name /= Name_No_DSA
14236 then
14237 RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
14238 end if;
14240 else
14241 Error_Pragma_Arg
14242 ("pragma% cannot reference access-to-function type",
14243 Arg1);
14244 end if;
14246 -- Only other possibility is access-to-class-wide type
14248 elsif Is_Access_Type (Nm)
14249 and then Is_Class_Wide_Type (Designated_Type (Nm))
14250 then
14251 Check_First_Subtype (Arg1);
14252 Set_Is_Asynchronous (Nm);
14253 if Expander_Active then
14254 RACW_Type_Is_Asynchronous (Nm);
14255 end if;
14257 else
14258 Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
14259 end if;
14260 end Asynchronous;
14262 ------------
14263 -- Atomic --
14264 ------------
14266 -- pragma Atomic (LOCAL_NAME);
14268 when Pragma_Atomic =>
14269 Process_Atomic_Independent_Shared_Volatile;
14271 -----------------------
14272 -- Atomic_Components --
14273 -----------------------
14275 -- pragma Atomic_Components (array_LOCAL_NAME);
14277 -- This processing is shared by Volatile_Components
14279 when Pragma_Atomic_Components
14280 | Pragma_Volatile_Components
14282 Atomic_Components : declare
14283 D : Node_Id;
14284 E : Entity_Id;
14285 E_Id : Node_Id;
14287 begin
14288 Check_Ada_83_Warning;
14289 Check_No_Identifiers;
14290 Check_Arg_Count (1);
14291 Check_Arg_Is_Local_Name (Arg1);
14292 E_Id := Get_Pragma_Arg (Arg1);
14294 if Etype (E_Id) = Any_Type then
14295 return;
14296 end if;
14298 E := Entity (E_Id);
14300 -- A pragma that applies to a Ghost entity becomes Ghost for the
14301 -- purposes of legality checks and removal of ignored Ghost code.
14303 Mark_Ghost_Pragma (N, E);
14304 Check_Duplicate_Pragma (E);
14306 if Rep_Item_Too_Early (E, N)
14307 or else
14308 Rep_Item_Too_Late (E, N)
14309 then
14310 return;
14311 end if;
14313 D := Declaration_Node (E);
14315 if (Nkind (D) = N_Full_Type_Declaration and then Is_Array_Type (E))
14316 or else
14317 (Nkind (D) = N_Object_Declaration
14318 and then Ekind (E) in E_Constant | E_Variable
14319 and then Nkind (Object_Definition (D)) =
14320 N_Constrained_Array_Definition)
14321 or else
14322 (Ada_Version >= Ada_2022
14323 and then Nkind (D) = N_Formal_Type_Declaration)
14324 then
14325 -- The flag is set on the base type, or on the object
14327 if Nkind (D) = N_Full_Type_Declaration then
14328 E := Base_Type (E);
14329 end if;
14331 -- Atomic implies both Independent and Volatile
14333 if Prag_Id = Pragma_Atomic_Components then
14334 Set_Has_Atomic_Components (E);
14335 Set_Has_Independent_Components (E);
14336 end if;
14338 Set_Has_Volatile_Components (E);
14340 else
14341 Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
14342 end if;
14343 end Atomic_Components;
14345 --------------------
14346 -- Attach_Handler --
14347 --------------------
14349 -- pragma Attach_Handler (handler_NAME, EXPRESSION);
14351 when Pragma_Attach_Handler =>
14352 Check_Ada_83_Warning;
14353 Check_No_Identifiers;
14354 Check_Arg_Count (2);
14356 if No_Run_Time_Mode then
14357 Error_Msg_CRT ("Attach_Handler pragma", N);
14358 else
14359 Check_Interrupt_Or_Attach_Handler;
14361 -- The expression that designates the attribute may depend on a
14362 -- discriminant, and is therefore a per-object expression, to
14363 -- be expanded in the init proc. If expansion is enabled, then
14364 -- perform semantic checks on a copy only.
14366 declare
14367 Temp : Node_Id;
14368 Typ : Node_Id;
14369 Parg2 : constant Node_Id := Get_Pragma_Arg (Arg2);
14371 begin
14372 -- In Relaxed_RM_Semantics mode, we allow any static
14373 -- integer value, for compatibility with other compilers.
14375 if Relaxed_RM_Semantics
14376 and then Nkind (Parg2) = N_Integer_Literal
14377 then
14378 Typ := Standard_Integer;
14379 else
14380 Typ := RTE (RE_Interrupt_ID);
14381 end if;
14383 if Expander_Active then
14384 Temp := New_Copy_Tree (Parg2);
14385 Set_Parent (Temp, N);
14386 Preanalyze_And_Resolve (Temp, Typ);
14387 else
14388 Analyze (Parg2);
14389 Resolve (Parg2, Typ);
14390 end if;
14391 end;
14393 Process_Interrupt_Or_Attach_Handler;
14394 end if;
14396 --------------------
14397 -- C_Pass_By_Copy --
14398 --------------------
14400 -- pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
14402 when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
14403 Arg : Node_Id;
14404 Val : Uint;
14406 begin
14407 GNAT_Pragma;
14408 Check_Valid_Configuration_Pragma;
14409 Check_Arg_Count (1);
14410 Check_Optional_Identifier (Arg1, "max_size");
14412 Arg := Get_Pragma_Arg (Arg1);
14413 Check_Arg_Is_OK_Static_Expression (Arg, Any_Integer);
14415 Val := Expr_Value (Arg);
14417 if Val <= 0 then
14418 Error_Pragma_Arg
14419 ("maximum size for pragma% must be positive", Arg1);
14421 elsif UI_Is_In_Int_Range (Val) then
14422 Default_C_Record_Mechanism := UI_To_Int (Val);
14424 -- If a giant value is given, Int'Last will do well enough.
14425 -- If sometime someone complains that a record larger than
14426 -- two gigabytes is not copied, we will worry about it then.
14428 else
14429 Default_C_Record_Mechanism := Mechanism_Type'Last;
14430 end if;
14431 end C_Pass_By_Copy;
14433 -----------
14434 -- Check --
14435 -----------
14437 -- pragma Check ([Name =>] CHECK_KIND,
14438 -- [Check =>] Boolean_EXPRESSION
14439 -- [,[Message =>] String_EXPRESSION]);
14441 -- CHECK_KIND ::= IDENTIFIER |
14442 -- Pre'Class |
14443 -- Post'Class |
14444 -- Invariant'Class |
14445 -- Type_Invariant'Class
14447 -- The identifiers Assertions and Statement_Assertions are not
14448 -- allowed, since they have special meaning for Check_Policy.
14450 -- WARNING: The code below manages Ghost regions. Return statements
14451 -- must be replaced by gotos which jump to the end of the code and
14452 -- restore the Ghost mode.
14454 when Pragma_Check => Check : declare
14455 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
14456 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
14457 -- Save the Ghost-related attributes to restore on exit
14459 Cname : Name_Id;
14460 Eloc : Source_Ptr;
14461 Expr : Node_Id;
14462 Str : Node_Id;
14463 pragma Warnings (Off, Str);
14465 begin
14466 -- Pragma Check is Ghost when it applies to a Ghost entity. Set
14467 -- the mode now to ensure that any nodes generated during analysis
14468 -- and expansion are marked as Ghost.
14470 Set_Ghost_Mode (N);
14472 GNAT_Pragma;
14473 Check_At_Least_N_Arguments (2);
14474 Check_At_Most_N_Arguments (3);
14475 Check_Optional_Identifier (Arg1, Name_Name);
14476 Check_Optional_Identifier (Arg2, Name_Check);
14478 if Arg_Count = 3 then
14479 Check_Optional_Identifier (Arg3, Name_Message);
14480 Str := Get_Pragma_Arg (Arg3);
14481 end if;
14483 Rewrite_Assertion_Kind (Get_Pragma_Arg (Arg1));
14484 Check_Arg_Is_Identifier (Arg1);
14485 Cname := Chars (Get_Pragma_Arg (Arg1));
14487 -- Check forbidden name Assertions or Statement_Assertions
14489 case Cname is
14490 when Name_Assertions =>
14491 Error_Pragma_Arg
14492 ("""Assertions"" is not allowed as a check kind for "
14493 & "pragma%", Arg1);
14495 when Name_Statement_Assertions =>
14496 Error_Pragma_Arg
14497 ("""Statement_Assertions"" is not allowed as a check kind "
14498 & "for pragma%", Arg1);
14500 when others =>
14501 null;
14502 end case;
14504 -- Check applicable policy. We skip this if Checked/Ignored status
14505 -- is already set (e.g. in the case of a pragma from an aspect).
14507 if Is_Checked (N) or else Is_Ignored (N) then
14508 null;
14510 -- For a non-source pragma that is a rewriting of another pragma,
14511 -- copy the Is_Checked/Ignored status from the rewritten pragma.
14513 elsif Is_Rewrite_Substitution (N)
14514 and then Nkind (Original_Node (N)) = N_Pragma
14515 then
14516 Set_Is_Ignored (N, Is_Ignored (Original_Node (N)));
14517 Set_Is_Checked (N, Is_Checked (Original_Node (N)));
14519 -- Otherwise query the applicable policy at this point
14521 else
14522 case Check_Kind (Cname) is
14523 when Name_Ignore =>
14524 Set_Is_Ignored (N, True);
14525 Set_Is_Checked (N, False);
14527 when Name_Check =>
14528 Set_Is_Ignored (N, False);
14529 Set_Is_Checked (N, True);
14531 -- For disable, rewrite pragma as null statement and skip
14532 -- rest of the analysis of the pragma.
14534 when Name_Disable =>
14535 Rewrite (N, Make_Null_Statement (Loc));
14536 Analyze (N);
14537 raise Pragma_Exit;
14539 -- No other possibilities
14541 when others =>
14542 raise Program_Error;
14543 end case;
14544 end if;
14546 -- If check kind was not Disable, then continue pragma analysis
14548 Expr := Get_Pragma_Arg (Arg2);
14550 -- Mark the pragma (or, if rewritten from an aspect, the original
14551 -- aspect) as enabled. Nothing to do for an internally generated
14552 -- check for a dynamic predicate.
14554 if Is_Checked (N)
14555 and then not Split_PPC (N)
14556 and then Cname /= Name_Dynamic_Predicate
14557 then
14558 Set_SCO_Pragma_Enabled (Loc);
14559 end if;
14561 -- Deal with analyzing the string argument. If checks are not
14562 -- on we don't want any expansion (since such expansion would
14563 -- not get properly deleted) but we do want to analyze (to get
14564 -- proper references). The Preanalyze_And_Resolve routine does
14565 -- just what we want. Ditto if pragma is active, because it will
14566 -- be rewritten as an if-statement whose analysis will complete
14567 -- analysis and expansion of the string message. This makes a
14568 -- difference in the unusual case where the expression for the
14569 -- string may have a side effect, such as raising an exception.
14570 -- This is mandated by RM 11.4.2, which specifies that the string
14571 -- expression is only evaluated if the check fails and
14572 -- Assertion_Error is to be raised.
14574 if Arg_Count = 3 then
14575 Preanalyze_And_Resolve (Str, Standard_String);
14576 end if;
14578 -- Now you might think we could just do the same with the Boolean
14579 -- expression if checks are off (and expansion is on) and then
14580 -- rewrite the check as a null statement. This would work but we
14581 -- would lose the useful warnings about an assertion being bound
14582 -- to fail even if assertions are turned off.
14584 -- So instead we wrap the boolean expression in an if statement
14585 -- that looks like:
14587 -- if False and then condition then
14588 -- null;
14589 -- end if;
14591 -- The reason we do this rewriting during semantic analysis rather
14592 -- than as part of normal expansion is that we cannot analyze and
14593 -- expand the code for the boolean expression directly, or it may
14594 -- cause insertion of actions that would escape the attempt to
14595 -- suppress the check code.
14597 -- Note that the Sloc for the if statement corresponds to the
14598 -- argument condition, not the pragma itself. The reason for
14599 -- this is that we may generate a warning if the condition is
14600 -- False at compile time, and we do not want to delete this
14601 -- warning when we delete the if statement.
14603 if Expander_Active and Is_Ignored (N) then
14604 Eloc := Sloc (Expr);
14606 Rewrite (N,
14607 Make_If_Statement (Eloc,
14608 Condition =>
14609 Make_And_Then (Eloc,
14610 Left_Opnd => Make_Identifier (Eloc, Name_False),
14611 Right_Opnd => Expr),
14612 Then_Statements => New_List (
14613 Make_Null_Statement (Eloc))));
14615 -- Now go ahead and analyze the if statement
14617 In_Assertion_Expr := In_Assertion_Expr + 1;
14619 -- One rather special treatment. If we are now in Eliminated
14620 -- overflow mode, then suppress overflow checking since we do
14621 -- not want to drag in the bignum stuff if we are in Ignore
14622 -- mode anyway. This is particularly important if we are using
14623 -- a configurable run time that does not support bignum ops.
14625 if Scope_Suppress.Overflow_Mode_Assertions = Eliminated then
14626 declare
14627 Svo : constant Boolean :=
14628 Scope_Suppress.Suppress (Overflow_Check);
14629 begin
14630 Scope_Suppress.Overflow_Mode_Assertions := Strict;
14631 Scope_Suppress.Suppress (Overflow_Check) := True;
14632 Analyze (N);
14633 Scope_Suppress.Suppress (Overflow_Check) := Svo;
14634 Scope_Suppress.Overflow_Mode_Assertions := Eliminated;
14635 end;
14637 -- Not that special case
14639 else
14640 Analyze (N);
14641 end if;
14643 -- All done with this check
14645 In_Assertion_Expr := In_Assertion_Expr - 1;
14647 -- Check is active or expansion not active. In these cases we can
14648 -- just go ahead and analyze the boolean with no worries.
14650 else
14651 In_Assertion_Expr := In_Assertion_Expr + 1;
14652 Analyze_And_Resolve (Expr, Any_Boolean);
14653 In_Assertion_Expr := In_Assertion_Expr - 1;
14654 end if;
14656 Restore_Ghost_Region (Saved_GM, Saved_IGR);
14657 end Check;
14659 --------------------------
14660 -- Check_Float_Overflow --
14661 --------------------------
14663 -- pragma Check_Float_Overflow;
14665 when Pragma_Check_Float_Overflow =>
14666 GNAT_Pragma;
14667 Check_Valid_Configuration_Pragma;
14668 Check_Arg_Count (0);
14669 Check_Float_Overflow := not Machine_Overflows_On_Target;
14671 ----------------
14672 -- Check_Name --
14673 ----------------
14675 -- pragma Check_Name (check_IDENTIFIER);
14677 when Pragma_Check_Name =>
14678 GNAT_Pragma;
14679 Check_No_Identifiers;
14680 Check_Valid_Configuration_Pragma;
14681 Check_Arg_Count (1);
14682 Check_Arg_Is_Identifier (Arg1);
14684 declare
14685 Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
14687 begin
14688 for J in Check_Names.First .. Check_Names.Last loop
14689 if Check_Names.Table (J) = Nam then
14690 return;
14691 end if;
14692 end loop;
14694 Check_Names.Append (Nam);
14695 end;
14697 ------------------
14698 -- Check_Policy --
14699 ------------------
14701 -- This is the old style syntax, which is still allowed in all modes:
14703 -- pragma Check_Policy ([Name =>] CHECK_KIND
14704 -- [Policy =>] POLICY_IDENTIFIER);
14706 -- POLICY_IDENTIFIER ::= On | Off | Check | Disable | Ignore
14708 -- CHECK_KIND ::= IDENTIFIER |
14709 -- Pre'Class |
14710 -- Post'Class |
14711 -- Type_Invariant'Class |
14712 -- Invariant'Class
14714 -- This is the new style syntax, compatible with Assertion_Policy
14715 -- and also allowed in all modes.
14717 -- Pragma Check_Policy (
14718 -- CHECK_KIND => POLICY_IDENTIFIER
14719 -- {, CHECK_KIND => POLICY_IDENTIFIER});
14721 -- Note: the identifiers Name and Policy are not allowed as
14722 -- Check_Kind values. This avoids ambiguities between the old and
14723 -- new form syntax.
14725 when Pragma_Check_Policy => Check_Policy : declare
14726 Kind : Node_Id;
14728 begin
14729 GNAT_Pragma;
14730 Check_At_Least_N_Arguments (1);
14732 -- A Check_Policy pragma can appear either as a configuration
14733 -- pragma, or in a declarative part or a package spec (see RM
14734 -- 11.5(5) for rules for Suppress/Unsuppress which are also
14735 -- followed for Check_Policy).
14737 if not Is_Configuration_Pragma then
14738 Check_Is_In_Decl_Part_Or_Package_Spec;
14739 end if;
14741 -- Figure out if we have the old or new syntax. We have the
14742 -- old syntax if the first argument has no identifier, or the
14743 -- identifier is Name.
14745 if Nkind (Arg1) /= N_Pragma_Argument_Association
14746 or else Chars (Arg1) in No_Name | Name_Name
14747 then
14748 -- Old syntax
14750 Check_Arg_Count (2);
14751 Check_Optional_Identifier (Arg1, Name_Name);
14752 Kind := Get_Pragma_Arg (Arg1);
14753 Rewrite_Assertion_Kind (Kind,
14754 From_Policy => Comes_From_Source (N));
14755 Check_Arg_Is_Identifier (Arg1);
14757 -- Check forbidden check kind
14759 if Chars (Kind) in Name_Name | Name_Policy then
14760 Error_Msg_Name_2 := Chars (Kind);
14761 Error_Pragma_Arg
14762 ("pragma% does not allow% as check name", Arg1);
14763 end if;
14765 -- Check policy
14767 Check_Optional_Identifier (Arg2, Name_Policy);
14768 Check_Arg_Is_One_Of
14769 (Arg2,
14770 Name_On, Name_Off, Name_Check, Name_Disable, Name_Ignore);
14772 -- And chain pragma on the Check_Policy_List for search
14774 Set_Next_Pragma (N, Opt.Check_Policy_List);
14775 Opt.Check_Policy_List := N;
14777 -- For the new syntax, what we do is to convert each argument to
14778 -- an old syntax equivalent. We do that because we want to chain
14779 -- old style Check_Policy pragmas for the search (we don't want
14780 -- to have to deal with multiple arguments in the search).
14782 else
14783 declare
14784 Arg : Node_Id;
14785 Argx : Node_Id;
14786 LocP : Source_Ptr;
14787 New_P : Node_Id;
14789 begin
14790 Arg := Arg1;
14791 while Present (Arg) loop
14792 LocP := Sloc (Arg);
14793 Argx := Get_Pragma_Arg (Arg);
14795 -- Kind must be specified
14797 if Nkind (Arg) /= N_Pragma_Argument_Association
14798 or else Chars (Arg) = No_Name
14799 then
14800 Error_Pragma_Arg
14801 ("missing assertion kind for pragma%", Arg);
14802 end if;
14804 -- Construct equivalent old form syntax Check_Policy
14805 -- pragma and insert it to get remaining checks.
14807 New_P :=
14808 Make_Pragma (LocP,
14809 Chars => Name_Check_Policy,
14810 Pragma_Argument_Associations => New_List (
14811 Make_Pragma_Argument_Association (LocP,
14812 Expression =>
14813 Make_Identifier (LocP, Chars (Arg))),
14814 Make_Pragma_Argument_Association (Sloc (Argx),
14815 Expression => Argx)));
14817 Arg := Next (Arg);
14819 -- For a configuration pragma, insert old form in
14820 -- the corresponding file.
14822 if Is_Configuration_Pragma then
14823 Insert_After (N, New_P);
14824 Analyze (New_P);
14826 else
14827 Insert_Action (N, New_P);
14828 end if;
14829 end loop;
14831 -- Rewrite original Check_Policy pragma to null, since we
14832 -- have converted it into a series of old syntax pragmas.
14834 Rewrite (N, Make_Null_Statement (Loc));
14835 Analyze (N);
14836 end;
14837 end if;
14838 end Check_Policy;
14840 -------------
14841 -- Comment --
14842 -------------
14844 -- pragma Comment (static_string_EXPRESSION)
14846 -- Processing for pragma Comment shares the circuitry for pragma
14847 -- Ident. The only differences are that Ident enforces a limit of 31
14848 -- characters on its argument, and also enforces limitations on
14849 -- placement for DEC compatibility. Pragma Comment shares neither of
14850 -- these restrictions.
14852 -------------------
14853 -- Common_Object --
14854 -------------------
14856 -- pragma Common_Object (
14857 -- [Internal =>] LOCAL_NAME
14858 -- [, [External =>] EXTERNAL_SYMBOL]
14859 -- [, [Size =>] EXTERNAL_SYMBOL]);
14861 -- Processing for this pragma is shared with Psect_Object
14863 ----------------------------------------------
14864 -- Compile_Time_Error, Compile_Time_Warning --
14865 ----------------------------------------------
14867 -- pragma Compile_Time_Error
14868 -- (boolean_EXPRESSION, static_string_EXPRESSION);
14870 -- pragma Compile_Time_Warning
14871 -- (boolean_EXPRESSION, static_string_EXPRESSION);
14873 when Pragma_Compile_Time_Error | Pragma_Compile_Time_Warning =>
14874 GNAT_Pragma;
14876 Process_Compile_Time_Warning_Or_Error;
14878 -----------------------------
14879 -- Complete_Representation --
14880 -----------------------------
14882 -- pragma Complete_Representation;
14884 when Pragma_Complete_Representation =>
14885 GNAT_Pragma;
14886 Check_Arg_Count (0);
14888 if Nkind (Parent (N)) /= N_Record_Representation_Clause then
14889 Error_Pragma
14890 ("pragma & must appear within record representation clause");
14891 end if;
14893 ----------------------------
14894 -- Complex_Representation --
14895 ----------------------------
14897 -- pragma Complex_Representation ([Entity =>] LOCAL_NAME);
14899 when Pragma_Complex_Representation => Complex_Representation : declare
14900 E_Id : Node_Id;
14901 E : Entity_Id;
14902 Ent : Entity_Id;
14904 begin
14905 GNAT_Pragma;
14906 Check_Arg_Count (1);
14907 Check_Optional_Identifier (Arg1, Name_Entity);
14908 Check_Arg_Is_Local_Name (Arg1);
14909 E_Id := Get_Pragma_Arg (Arg1);
14911 if Etype (E_Id) = Any_Type then
14912 return;
14913 end if;
14915 E := Entity (E_Id);
14917 if not Is_Record_Type (E) then
14918 Error_Pragma_Arg
14919 ("argument for pragma% must be record type", Arg1);
14920 end if;
14922 Ent := First_Entity (E);
14924 if No (Ent)
14925 or else No (Next_Entity (Ent))
14926 or else Present (Next_Entity (Next_Entity (Ent)))
14927 or else not Is_Floating_Point_Type (Etype (Ent))
14928 or else Etype (Ent) /= Etype (Next_Entity (Ent))
14929 then
14930 Error_Pragma_Arg
14931 ("record for pragma% must have two fields of the same "
14932 & "floating-point type", Arg1);
14934 else
14935 Set_Has_Complex_Representation (Base_Type (E));
14937 -- We need to treat the type has having a non-standard
14938 -- representation, for back-end purposes, even though in
14939 -- general a complex will have the default representation
14940 -- of a record with two real components.
14942 Set_Has_Non_Standard_Rep (Base_Type (E));
14943 end if;
14944 end Complex_Representation;
14946 -------------------------
14947 -- Component_Alignment --
14948 -------------------------
14950 -- pragma Component_Alignment (
14951 -- [Form =>] ALIGNMENT_CHOICE
14952 -- [, [Name =>] type_LOCAL_NAME]);
14954 -- ALIGNMENT_CHOICE ::=
14955 -- Component_Size
14956 -- | Component_Size_4
14957 -- | Storage_Unit
14958 -- | Default
14960 when Pragma_Component_Alignment => Component_AlignmentP : declare
14961 Args : Args_List (1 .. 2);
14962 Names : constant Name_List (1 .. 2) := (
14963 Name_Form,
14964 Name_Name);
14966 Form : Node_Id renames Args (1);
14967 Name : Node_Id renames Args (2);
14969 Atype : Component_Alignment_Kind;
14970 Typ : Entity_Id;
14972 begin
14973 GNAT_Pragma;
14974 Gather_Associations (Names, Args);
14976 if No (Form) then
14977 Error_Pragma ("missing Form argument for pragma%");
14978 end if;
14980 Check_Arg_Is_Identifier (Form);
14982 -- Get proper alignment, note that Default = Component_Size on all
14983 -- machines we have so far, and we want to set this value rather
14984 -- than the default value to indicate that it has been explicitly
14985 -- set (and thus will not get overridden by the default component
14986 -- alignment for the current scope)
14988 if Chars (Form) = Name_Component_Size then
14989 Atype := Calign_Component_Size;
14991 elsif Chars (Form) = Name_Component_Size_4 then
14992 Atype := Calign_Component_Size_4;
14994 elsif Chars (Form) = Name_Default then
14995 Atype := Calign_Component_Size;
14997 elsif Chars (Form) = Name_Storage_Unit then
14998 Atype := Calign_Storage_Unit;
15000 else
15001 Error_Pragma_Arg
15002 ("invalid Form parameter for pragma%", Form);
15003 end if;
15005 -- The pragma appears in a configuration file
15007 if No (Parent (N)) then
15008 Check_Valid_Configuration_Pragma;
15010 -- Capture the component alignment in a global variable when
15011 -- the pragma appears in a configuration file. Note that the
15012 -- scope stack is empty at this point and cannot be used to
15013 -- store the alignment value.
15015 Configuration_Component_Alignment := Atype;
15017 -- Case with no name, supplied, affects scope table entry
15019 elsif No (Name) then
15020 Scope_Stack.Table
15021 (Scope_Stack.Last).Component_Alignment_Default := Atype;
15023 -- Case of name supplied
15025 else
15026 Check_Arg_Is_Local_Name (Name);
15027 Find_Type (Name);
15028 Typ := Entity (Name);
15030 if Typ = Any_Type
15031 or else Rep_Item_Too_Early (Typ, N)
15032 then
15033 return;
15034 else
15035 Typ := Underlying_Type (Typ);
15036 end if;
15038 if not Is_Record_Type (Typ)
15039 and then not Is_Array_Type (Typ)
15040 then
15041 Error_Pragma_Arg
15042 ("Name parameter of pragma% must identify record or "
15043 & "array type", Name);
15044 end if;
15046 -- An explicit Component_Alignment pragma overrides an
15047 -- implicit pragma Pack, but not an explicit one.
15049 if not Has_Pragma_Pack (Base_Type (Typ)) then
15050 Set_Is_Packed (Base_Type (Typ), False);
15051 Set_Component_Alignment (Base_Type (Typ), Atype);
15052 end if;
15053 end if;
15054 end Component_AlignmentP;
15056 --------------------------------
15057 -- Constant_After_Elaboration --
15058 --------------------------------
15060 -- pragma Constant_After_Elaboration [ (boolean_EXPRESSION) ];
15062 when Pragma_Constant_After_Elaboration => Constant_After_Elaboration :
15063 declare
15064 Obj_Decl : Node_Id;
15065 Obj_Id : Entity_Id;
15067 begin
15068 GNAT_Pragma;
15069 Check_No_Identifiers;
15070 Check_At_Most_N_Arguments (1);
15072 Obj_Decl := Find_Related_Context (N, Do_Checks => True);
15074 if Nkind (Obj_Decl) /= N_Object_Declaration then
15075 Pragma_Misplaced;
15076 end if;
15078 Obj_Id := Defining_Entity (Obj_Decl);
15080 -- The object declaration must be a library-level variable which
15081 -- is either explicitly initialized or obtains a value during the
15082 -- elaboration of a package body (SPARK RM 3.3.1).
15084 if Ekind (Obj_Id) = E_Variable then
15085 if not Is_Library_Level_Entity (Obj_Id) then
15086 Error_Pragma
15087 ("pragma % must apply to a library level variable");
15088 end if;
15090 -- Otherwise the pragma applies to a constant, which is illegal
15092 else
15093 Error_Pragma ("pragma % must apply to a variable declaration");
15094 end if;
15096 -- A pragma that applies to a Ghost entity becomes Ghost for the
15097 -- purposes of legality checks and removal of ignored Ghost code.
15099 Mark_Ghost_Pragma (N, Obj_Id);
15101 -- Chain the pragma on the contract for completeness
15103 Add_Contract_Item (N, Obj_Id);
15105 -- Analyze the Boolean expression (if any)
15107 if Present (Arg1) then
15108 Check_Static_Boolean_Expression (Get_Pragma_Arg (Arg1));
15109 end if;
15110 end Constant_After_Elaboration;
15112 --------------------
15113 -- Contract_Cases --
15114 --------------------
15116 -- pragma Contract_Cases ((CONTRACT_CASE {, CONTRACT_CASE));
15118 -- CONTRACT_CASE ::= CASE_GUARD => CONSEQUENCE
15120 -- CASE_GUARD ::= boolean_EXPRESSION | others
15122 -- CONSEQUENCE ::= boolean_EXPRESSION
15124 -- Characteristics:
15126 -- * Analysis - The annotation undergoes initial checks to verify
15127 -- the legal placement and context. Secondary checks preanalyze the
15128 -- expressions in:
15130 -- Analyze_Contract_Cases_In_Decl_Part
15132 -- * Expansion - The annotation is expanded during the expansion of
15133 -- the related subprogram [body] contract as performed in:
15135 -- Expand_Subprogram_Contract
15137 -- * Template - The annotation utilizes the generic template of the
15138 -- related subprogram [body] when it is:
15140 -- aspect on subprogram declaration
15141 -- aspect on stand-alone subprogram body
15142 -- pragma on stand-alone subprogram body
15144 -- The annotation must prepare its own template when it is:
15146 -- pragma on subprogram declaration
15148 -- * Globals - Capture of global references must occur after full
15149 -- analysis.
15151 -- * Instance - The annotation is instantiated automatically when
15152 -- the related generic subprogram [body] is instantiated except for
15153 -- the "pragma on subprogram declaration" case. In that scenario
15154 -- the annotation must instantiate itself.
15156 when Pragma_Contract_Cases => Contract_Cases : declare
15157 Spec_Id : Entity_Id;
15158 Subp_Decl : Node_Id;
15159 Subp_Spec : Node_Id;
15161 begin
15162 GNAT_Pragma;
15163 Check_No_Identifiers;
15164 Check_Arg_Count (1);
15166 -- Ensure the proper placement of the pragma. Contract_Cases must
15167 -- be associated with a subprogram declaration or a body that acts
15168 -- as a spec.
15170 Subp_Decl :=
15171 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
15173 -- Entry
15175 if Nkind (Subp_Decl) = N_Entry_Declaration then
15176 null;
15178 -- Generic subprogram
15180 elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
15181 null;
15183 -- Body acts as spec
15185 elsif Nkind (Subp_Decl) = N_Subprogram_Body
15186 and then No (Corresponding_Spec (Subp_Decl))
15187 then
15188 null;
15190 -- Body stub acts as spec
15192 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
15193 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
15194 then
15195 null;
15197 -- Subprogram
15199 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
15200 Subp_Spec := Specification (Subp_Decl);
15202 -- Pragma Contract_Cases is forbidden on null procedures, as
15203 -- this may lead to potential ambiguities in behavior when
15204 -- interface null procedures are involved.
15206 if Nkind (Subp_Spec) = N_Procedure_Specification
15207 and then Null_Present (Subp_Spec)
15208 then
15209 Error_Msg_N (Fix_Error
15210 ("pragma % cannot apply to null procedure"), N);
15211 return;
15212 end if;
15214 else
15215 Pragma_Misplaced;
15216 end if;
15218 Spec_Id := Unique_Defining_Entity (Subp_Decl);
15220 -- A pragma that applies to a Ghost entity becomes Ghost for the
15221 -- purposes of legality checks and removal of ignored Ghost code.
15223 Mark_Ghost_Pragma (N, Spec_Id);
15224 Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
15226 -- Chain the pragma on the contract for further processing by
15227 -- Analyze_Contract_Cases_In_Decl_Part.
15229 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
15231 -- Fully analyze the pragma when it appears inside an entry
15232 -- or subprogram body because it cannot benefit from forward
15233 -- references.
15235 if Nkind (Subp_Decl) in N_Entry_Body
15236 | N_Subprogram_Body
15237 | N_Subprogram_Body_Stub
15238 then
15239 -- The legality checks of pragma Contract_Cases are affected by
15240 -- the SPARK mode in effect and the volatility of the context.
15241 -- Analyze all pragmas in a specific order.
15243 Analyze_If_Present (Pragma_SPARK_Mode);
15244 Analyze_If_Present (Pragma_Volatile_Function);
15245 Analyze_Contract_Cases_In_Decl_Part (N);
15246 end if;
15247 end Contract_Cases;
15249 ----------------
15250 -- Controlled --
15251 ----------------
15253 -- pragma Controlled (first_subtype_LOCAL_NAME);
15255 when Pragma_Controlled => Controlled : declare
15256 Arg : Node_Id;
15258 begin
15259 Check_No_Identifiers;
15260 Check_Arg_Count (1);
15261 Check_Arg_Is_Local_Name (Arg1);
15262 Arg := Get_Pragma_Arg (Arg1);
15264 if not Is_Entity_Name (Arg)
15265 or else not Is_Access_Type (Entity (Arg))
15266 then
15267 Error_Pragma_Arg ("pragma% requires access type", Arg1);
15268 else
15269 Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
15270 end if;
15271 end Controlled;
15273 ----------------
15274 -- Convention --
15275 ----------------
15277 -- pragma Convention ([Convention =>] convention_IDENTIFIER,
15278 -- [Entity =>] LOCAL_NAME);
15280 when Pragma_Convention => Convention : declare
15281 C : Convention_Id;
15282 E : Entity_Id;
15283 pragma Warnings (Off, C);
15284 pragma Warnings (Off, E);
15286 begin
15287 Check_Arg_Order ((Name_Convention, Name_Entity));
15288 Check_Ada_83_Warning;
15289 Check_Arg_Count (2);
15290 Process_Convention (C, E);
15292 -- A pragma that applies to a Ghost entity becomes Ghost for the
15293 -- purposes of legality checks and removal of ignored Ghost code.
15295 Mark_Ghost_Pragma (N, E);
15296 end Convention;
15298 ---------------------------
15299 -- Convention_Identifier --
15300 ---------------------------
15302 -- pragma Convention_Identifier ([Name =>] IDENTIFIER,
15303 -- [Convention =>] convention_IDENTIFIER);
15305 when Pragma_Convention_Identifier => Convention_Identifier : declare
15306 Idnam : Name_Id;
15307 Cname : Name_Id;
15309 begin
15310 GNAT_Pragma;
15311 Check_Arg_Order ((Name_Name, Name_Convention));
15312 Check_Arg_Count (2);
15313 Check_Optional_Identifier (Arg1, Name_Name);
15314 Check_Optional_Identifier (Arg2, Name_Convention);
15315 Check_Arg_Is_Identifier (Arg1);
15316 Check_Arg_Is_Identifier (Arg2);
15317 Idnam := Chars (Get_Pragma_Arg (Arg1));
15318 Cname := Chars (Get_Pragma_Arg (Arg2));
15320 if Is_Convention_Name (Cname) then
15321 Record_Convention_Identifier
15322 (Idnam, Get_Convention_Id (Cname));
15323 else
15324 Error_Pragma_Arg
15325 ("second arg for % pragma must be convention", Arg2);
15326 end if;
15327 end Convention_Identifier;
15329 ---------------
15330 -- CPP_Class --
15331 ---------------
15333 -- pragma CPP_Class ([Entity =>] LOCAL_NAME)
15335 when Pragma_CPP_Class =>
15336 GNAT_Pragma;
15338 if Warn_On_Obsolescent_Feature then
15339 Error_Msg_N
15340 ("'G'N'A'T pragma cpp'_class is now obsolete and has no "
15341 & "effect; replace it by pragma import?j?", N);
15342 end if;
15344 Check_Arg_Count (1);
15346 Rewrite (N,
15347 Make_Pragma (Loc,
15348 Chars => Name_Import,
15349 Pragma_Argument_Associations => New_List (
15350 Make_Pragma_Argument_Association (Loc,
15351 Expression => Make_Identifier (Loc, Name_CPP)),
15352 New_Copy (First (Pragma_Argument_Associations (N))))));
15353 Analyze (N);
15355 ---------------------
15356 -- CPP_Constructor --
15357 ---------------------
15359 -- pragma CPP_Constructor ([Entity =>] LOCAL_NAME
15360 -- [, [External_Name =>] static_string_EXPRESSION ]
15361 -- [, [Link_Name =>] static_string_EXPRESSION ]);
15363 when Pragma_CPP_Constructor => CPP_Constructor : declare
15364 Id : Entity_Id;
15365 Def_Id : Entity_Id;
15366 Tag_Typ : Entity_Id;
15368 begin
15369 GNAT_Pragma;
15370 Check_At_Least_N_Arguments (1);
15371 Check_At_Most_N_Arguments (3);
15372 Check_Optional_Identifier (Arg1, Name_Entity);
15373 Check_Arg_Is_Local_Name (Arg1);
15375 Id := Get_Pragma_Arg (Arg1);
15376 Find_Program_Unit_Name (Id);
15378 -- If we did not find the name, we are done
15380 if Etype (Id) = Any_Type then
15381 return;
15382 end if;
15384 Def_Id := Entity (Id);
15386 -- Check if already defined as constructor
15388 if Is_Constructor (Def_Id) then
15389 Error_Msg_N
15390 ("??duplicate argument for pragma 'C'P'P_Constructor", Arg1);
15391 return;
15392 end if;
15394 if Ekind (Def_Id) = E_Function
15395 and then (Is_CPP_Class (Etype (Def_Id))
15396 or else (Is_Class_Wide_Type (Etype (Def_Id))
15397 and then
15398 Is_CPP_Class (Root_Type (Etype (Def_Id)))))
15399 then
15400 if Scope (Def_Id) /= Scope (Etype (Def_Id)) then
15401 Error_Msg_N
15402 ("'C'P'P constructor must be defined in the scope of "
15403 & "its returned type", Arg1);
15404 end if;
15406 if Arg_Count >= 2 then
15407 Set_Imported (Def_Id);
15408 Set_Is_Public (Def_Id);
15409 Process_Interface_Name (Def_Id, Arg2, Arg3, N);
15410 end if;
15412 Set_Has_Completion (Def_Id);
15413 Set_Is_Constructor (Def_Id);
15414 Set_Convention (Def_Id, Convention_CPP);
15416 -- Imported C++ constructors are not dispatching primitives
15417 -- because in C++ they don't have a dispatch table slot.
15418 -- However, in Ada the constructor has the profile of a
15419 -- function that returns a tagged type and therefore it has
15420 -- been treated as a primitive operation during semantic
15421 -- analysis. We now remove it from the list of primitive
15422 -- operations of the type.
15424 if Is_Tagged_Type (Etype (Def_Id))
15425 and then not Is_Class_Wide_Type (Etype (Def_Id))
15426 and then Is_Dispatching_Operation (Def_Id)
15427 then
15428 Tag_Typ := Etype (Def_Id);
15430 Remove (Primitive_Operations (Tag_Typ), Def_Id);
15431 Set_Is_Dispatching_Operation (Def_Id, False);
15432 end if;
15434 -- For backward compatibility, if the constructor returns a
15435 -- class wide type, and we internally change the return type to
15436 -- the corresponding root type.
15438 if Is_Class_Wide_Type (Etype (Def_Id)) then
15439 Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
15440 end if;
15441 else
15442 Error_Pragma_Arg
15443 ("pragma% requires function returning a 'C'P'P_Class type",
15444 Arg1);
15445 end if;
15446 end CPP_Constructor;
15448 -----------------
15449 -- CPP_Virtual --
15450 -----------------
15452 when Pragma_CPP_Virtual =>
15453 GNAT_Pragma;
15455 if Warn_On_Obsolescent_Feature then
15456 Error_Msg_N
15457 ("'G'N'A'T pragma Cpp'_Virtual is now obsolete and has no "
15458 & "effect?j?", N);
15459 end if;
15461 -----------------
15462 -- CUDA_Device --
15463 -----------------
15465 when Pragma_CUDA_Device => CUDA_Device : declare
15466 Arg_Node : Node_Id;
15467 Device_Entity : Entity_Id;
15468 begin
15469 GNAT_Pragma;
15470 Check_Arg_Count (1);
15471 Check_Arg_Is_Library_Level_Local_Name (Arg1);
15473 Arg_Node := Get_Pragma_Arg (Arg1);
15474 Device_Entity := Entity (Arg_Node);
15476 if Ekind (Device_Entity) in E_Variable
15477 | E_Constant
15478 | E_Procedure
15479 | E_Function
15480 then
15481 Add_CUDA_Device_Entity
15482 (Package_Specification_Of_Scope (Scope (Device_Entity)),
15483 Device_Entity);
15485 else
15486 Error_Msg_NE ("& must be constant, variable or subprogram",
15488 Device_Entity);
15489 end if;
15491 end CUDA_Device;
15493 ------------------
15494 -- CUDA_Execute --
15495 ------------------
15497 -- pragma CUDA_Execute (PROCEDURE_CALL_STATEMENT,
15498 -- EXPRESSION,
15499 -- EXPRESSION,
15500 -- [, EXPRESSION
15501 -- [, EXPRESSION]]);
15503 when Pragma_CUDA_Execute => CUDA_Execute : declare
15505 function Is_Acceptable_Dim3 (N : Node_Id) return Boolean;
15506 -- Returns True if N is an acceptable argument for CUDA_Execute,
15507 -- False otherwise.
15509 ------------------------
15510 -- Is_Acceptable_Dim3 --
15511 ------------------------
15513 function Is_Acceptable_Dim3 (N : Node_Id) return Boolean is
15514 Expr : Node_Id;
15515 begin
15516 if Is_RTE (Etype (N), RE_Dim3)
15517 or else Is_Integer_Type (Etype (N))
15518 then
15519 return True;
15520 end if;
15522 if Nkind (N) = N_Aggregate
15523 and then not Null_Record_Present (N)
15524 and then No (Component_Associations (N))
15525 and then List_Length (Expressions (N)) = 3
15526 then
15527 Expr := First (Expressions (N));
15528 while Present (Expr) loop
15529 Analyze_And_Resolve (Expr, Any_Integer);
15530 Next (Expr);
15531 end loop;
15532 return True;
15533 end if;
15535 return False;
15536 end Is_Acceptable_Dim3;
15538 -- Local variables
15540 Block_Dimensions : constant Node_Id := Get_Pragma_Arg (Arg3);
15541 Grid_Dimensions : constant Node_Id := Get_Pragma_Arg (Arg2);
15542 Kernel_Call : constant Node_Id := Get_Pragma_Arg (Arg1);
15543 Shared_Memory : Node_Id;
15544 Stream : Node_Id;
15546 -- Start of processing for CUDA_Execute
15548 begin
15549 GNAT_Pragma;
15550 Check_At_Least_N_Arguments (3);
15551 Check_At_Most_N_Arguments (5);
15553 Analyze_And_Resolve (Kernel_Call);
15554 if Nkind (Kernel_Call) /= N_Function_Call
15555 or else Etype (Kernel_Call) /= Standard_Void_Type
15556 then
15557 -- In `pragma CUDA_Execute (Kernel_Call (...), ...)`,
15558 -- GNAT sees Kernel_Call as an N_Function_Call since
15559 -- Kernel_Call "looks" like an expression. However, only
15560 -- procedures can be kernels, so to make things easier for the
15561 -- user the error message complains about Kernel_Call not being
15562 -- a procedure call.
15564 Error_Msg_N ("first argument of & must be a procedure call", N);
15565 end if;
15567 Analyze (Grid_Dimensions);
15568 if not Is_Acceptable_Dim3 (Grid_Dimensions) then
15569 Error_Msg_N
15570 ("second argument of & must be an Integer, Dim3 or aggregate "
15571 & "containing 3 Integers", N);
15572 end if;
15574 Analyze (Block_Dimensions);
15575 if not Is_Acceptable_Dim3 (Block_Dimensions) then
15576 Error_Msg_N
15577 ("third argument of & must be an Integer, Dim3 or aggregate "
15578 & "containing 3 Integers", N);
15579 end if;
15581 if Present (Arg4) then
15582 Shared_Memory := Get_Pragma_Arg (Arg4);
15583 Analyze_And_Resolve (Shared_Memory, Any_Integer);
15585 if Present (Arg5) then
15586 Stream := Get_Pragma_Arg (Arg5);
15587 Analyze_And_Resolve (Stream, RTE (RE_Stream_T));
15588 end if;
15589 end if;
15590 end CUDA_Execute;
15592 -----------------
15593 -- CUDA_Global --
15594 -----------------
15596 -- pragma CUDA_Global ([Entity =>] IDENTIFIER);
15598 when Pragma_CUDA_Global => CUDA_Global : declare
15599 Arg_Node : Node_Id;
15600 Kernel_Proc : Entity_Id;
15601 Pack_Id : Entity_Id;
15602 begin
15603 GNAT_Pragma;
15604 Check_Arg_Count (1);
15605 Check_Optional_Identifier (Arg1, Name_Entity);
15606 Check_Arg_Is_Local_Name (Arg1);
15608 Arg_Node := Get_Pragma_Arg (Arg1);
15609 Analyze (Arg_Node);
15611 Kernel_Proc := Entity (Arg_Node);
15612 Pack_Id := Scope (Kernel_Proc);
15614 if Ekind (Kernel_Proc) /= E_Procedure then
15615 Error_Msg_NE ("& must be a procedure", N, Kernel_Proc);
15617 elsif Ekind (Pack_Id) /= E_Package
15618 or else not Is_Library_Level_Entity (Pack_Id)
15619 then
15620 Error_Msg_NE
15621 ("& must reside in a library-level package", N, Kernel_Proc);
15623 else
15624 Set_Is_CUDA_Kernel (Kernel_Proc);
15625 Add_CUDA_Kernel (Pack_Id, Kernel_Proc);
15626 end if;
15627 end CUDA_Global;
15629 ----------------
15630 -- CPP_Vtable --
15631 ----------------
15633 when Pragma_CPP_Vtable =>
15634 GNAT_Pragma;
15636 if Warn_On_Obsolescent_Feature then
15637 Error_Msg_N
15638 ("'G'N'A'T pragma Cpp'_Vtable is now obsolete and has no "
15639 & "effect?j?", N);
15640 end if;
15642 ---------
15643 -- CPU --
15644 ---------
15646 -- pragma CPU (EXPRESSION);
15648 when Pragma_CPU => CPU : declare
15649 P : constant Node_Id := Parent (N);
15650 Arg : Node_Id;
15651 Ent : Entity_Id;
15653 begin
15654 Ada_2012_Pragma;
15655 Check_No_Identifiers;
15656 Check_Arg_Count (1);
15657 Arg := Get_Pragma_Arg (Arg1);
15659 -- Subprogram case
15661 if Nkind (P) = N_Subprogram_Body then
15662 Check_In_Main_Program;
15664 Analyze_And_Resolve (Arg, Any_Integer);
15666 Ent := Defining_Unit_Name (Specification (P));
15668 if Nkind (Ent) = N_Defining_Program_Unit_Name then
15669 Ent := Defining_Identifier (Ent);
15670 end if;
15672 -- Must be static
15674 if not Is_OK_Static_Expression (Arg) then
15675 Flag_Non_Static_Expr
15676 ("main subprogram affinity is not static!", Arg);
15677 raise Pragma_Exit;
15679 -- If constraint error, then we already signalled an error
15681 elsif Raises_Constraint_Error (Arg) then
15682 null;
15684 -- Otherwise check in range
15686 else
15687 declare
15688 CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
15689 -- This is the entity System.Multiprocessors.CPU_Range;
15691 Val : constant Uint := Expr_Value (Arg);
15693 begin
15694 if Val < Expr_Value (Type_Low_Bound (CPU_Id))
15695 or else
15696 Val > Expr_Value (Type_High_Bound (CPU_Id))
15697 then
15698 Error_Pragma_Arg
15699 ("main subprogram CPU is out of range", Arg1);
15700 end if;
15701 end;
15702 end if;
15704 Set_Main_CPU
15705 (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
15707 -- Task case
15709 elsif Nkind (P) = N_Task_Definition then
15710 Ent := Defining_Identifier (Parent (P));
15712 -- The expression must be analyzed in the special manner
15713 -- described in "Handling of Default and Per-Object
15714 -- Expressions" in sem.ads.
15716 Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
15718 -- See comment in Sem_Ch13 about the following restrictions
15720 if Is_OK_Static_Expression (Arg) then
15721 if Expr_Value (Arg) = Uint_0 then
15722 Check_Restriction (No_Tasks_Unassigned_To_CPU, N);
15723 end if;
15724 else
15725 Check_Restriction (No_Dynamic_CPU_Assignment, N);
15726 end if;
15728 -- Anything else is incorrect
15730 else
15731 Pragma_Misplaced;
15732 end if;
15734 -- Check duplicate pragma before we chain the pragma in the Rep
15735 -- Item chain of Ent.
15737 Check_Duplicate_Pragma (Ent);
15738 Record_Rep_Item (Ent, N);
15739 end CPU;
15741 --------------------
15742 -- Deadline_Floor --
15743 --------------------
15745 -- pragma Deadline_Floor (time_span_EXPRESSION);
15747 when Pragma_Deadline_Floor => Deadline_Floor : declare
15748 P : constant Node_Id := Parent (N);
15749 Arg : Node_Id;
15750 Ent : Entity_Id;
15752 begin
15753 GNAT_Pragma;
15754 Check_No_Identifiers;
15755 Check_Arg_Count (1);
15757 Arg := Get_Pragma_Arg (Arg1);
15759 -- The expression must be analyzed in the special manner described
15760 -- in "Handling of Default and Per-Object Expressions" in sem.ads.
15762 Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
15764 -- Only protected types allowed
15766 if Nkind (P) /= N_Protected_Definition then
15767 Pragma_Misplaced;
15769 else
15770 Ent := Defining_Identifier (Parent (P));
15772 -- Check duplicate pragma before we chain the pragma in the Rep
15773 -- Item chain of Ent.
15775 Check_Duplicate_Pragma (Ent);
15776 Record_Rep_Item (Ent, N);
15777 end if;
15778 end Deadline_Floor;
15780 -----------
15781 -- Debug --
15782 -----------
15784 -- pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
15786 when Pragma_Debug => Debug : declare
15787 Cond : Node_Id;
15788 Call : Node_Id;
15790 begin
15791 GNAT_Pragma;
15793 -- The condition for executing the call is that the expander
15794 -- is active and that we are not ignoring this debug pragma.
15796 Cond :=
15797 New_Occurrence_Of
15798 (Boolean_Literals
15799 (Expander_Active and then not Is_Ignored (N)),
15800 Loc);
15802 if not Is_Ignored (N) then
15803 Set_SCO_Pragma_Enabled (Loc);
15804 end if;
15806 if Arg_Count = 2 then
15807 Cond :=
15808 Make_And_Then (Loc,
15809 Left_Opnd => Relocate_Node (Cond),
15810 Right_Opnd => Get_Pragma_Arg (Arg1));
15811 Call := Get_Pragma_Arg (Arg2);
15812 else
15813 Call := Get_Pragma_Arg (Arg1);
15814 end if;
15816 if Nkind (Call) in N_Expanded_Name
15817 | N_Function_Call
15818 | N_Identifier
15819 | N_Indexed_Component
15820 | N_Selected_Component
15821 then
15822 -- If this pragma Debug comes from source, its argument was
15823 -- parsed as a name form (which is syntactically identical).
15824 -- In a generic context a parameterless call will be left as
15825 -- an expanded name (if global) or selected_component if local.
15826 -- Change it to a procedure call statement now.
15828 Change_Name_To_Procedure_Call_Statement (Call);
15830 elsif Nkind (Call) = N_Procedure_Call_Statement then
15832 -- Already in the form of a procedure call statement: nothing
15833 -- to do (could happen in case of an internally generated
15834 -- pragma Debug).
15836 null;
15838 else
15839 -- All other cases: diagnose error
15841 Error_Msg_N
15842 ("argument of pragma ""Debug"" is not procedure call", Call);
15843 return;
15844 end if;
15846 -- Rewrite into a conditional with an appropriate condition. We
15847 -- wrap the procedure call in a block so that overhead from e.g.
15848 -- use of the secondary stack does not generate execution overhead
15849 -- for suppressed conditions.
15851 -- Normally the analysis that follows will freeze the subprogram
15852 -- being called. However, if the call is to a null procedure,
15853 -- we want to freeze it before creating the block, because the
15854 -- analysis that follows may be done with expansion disabled, in
15855 -- which case the body will not be generated, leading to spurious
15856 -- errors.
15858 if Nkind (Call) = N_Procedure_Call_Statement
15859 and then Is_Entity_Name (Name (Call))
15860 then
15861 Analyze (Name (Call));
15862 Freeze_Before (N, Entity (Name (Call)));
15863 end if;
15865 Rewrite (N,
15866 Make_Implicit_If_Statement (N,
15867 Condition => Cond,
15868 Then_Statements => New_List (
15869 Make_Block_Statement (Loc,
15870 Handled_Statement_Sequence =>
15871 Make_Handled_Sequence_Of_Statements (Loc,
15872 Statements => New_List (Relocate_Node (Call)))))));
15873 Analyze (N);
15875 -- Ignore pragma Debug in GNATprove mode. Do this rewriting
15876 -- after analysis of the normally rewritten node, to capture all
15877 -- references to entities, which avoids issuing wrong warnings
15878 -- about unused entities.
15880 if GNATprove_Mode then
15881 Rewrite (N, Make_Null_Statement (Loc));
15882 end if;
15883 end Debug;
15885 ------------------
15886 -- Debug_Policy --
15887 ------------------
15889 -- pragma Debug_Policy (On | Off | Check | Disable | Ignore)
15891 when Pragma_Debug_Policy =>
15892 GNAT_Pragma;
15893 Check_Arg_Count (1);
15894 Check_No_Identifiers;
15895 Check_Arg_Is_Identifier (Arg1);
15897 -- Exactly equivalent to pragma Check_Policy (Debug, arg), so
15898 -- rewrite it that way, and let the rest of the checking come
15899 -- from analyzing the rewritten pragma.
15901 Rewrite (N,
15902 Make_Pragma (Loc,
15903 Chars => Name_Check_Policy,
15904 Pragma_Argument_Associations => New_List (
15905 Make_Pragma_Argument_Association (Loc,
15906 Expression => Make_Identifier (Loc, Name_Debug)),
15908 Make_Pragma_Argument_Association (Loc,
15909 Expression => Get_Pragma_Arg (Arg1)))));
15910 Analyze (N);
15912 -------------------------------
15913 -- Default_Initial_Condition --
15914 -------------------------------
15916 -- pragma Default_Initial_Condition [ (null | boolean_EXPRESSION) ];
15918 when Pragma_Default_Initial_Condition => DIC : declare
15919 Discard : Boolean;
15920 Stmt : Node_Id;
15921 Typ : Entity_Id;
15923 begin
15924 GNAT_Pragma;
15925 Check_No_Identifiers;
15926 Check_At_Most_N_Arguments (2); -- Accounts for implicit type arg
15928 Typ := Empty;
15929 Stmt := Prev (N);
15930 while Present (Stmt) loop
15932 -- Skip prior pragmas, but check for duplicates
15934 if Nkind (Stmt) = N_Pragma then
15935 if Pragma_Name (Stmt) = Pname then
15936 Duplication_Error
15937 (Prag => N,
15938 Prev => Stmt);
15939 raise Pragma_Exit;
15940 end if;
15942 -- Skip internally generated code. Note that derived type
15943 -- declarations of untagged types with discriminants are
15944 -- rewritten as private type declarations.
15946 elsif not Comes_From_Source (Stmt)
15947 and then Nkind (Stmt) /= N_Private_Type_Declaration
15948 then
15949 null;
15951 -- The associated private type [extension] has been found, stop
15952 -- the search.
15954 elsif Nkind (Stmt) in N_Private_Extension_Declaration
15955 | N_Private_Type_Declaration
15956 then
15957 Typ := Defining_Entity (Stmt);
15958 exit;
15960 -- The pragma does not apply to a legal construct, issue an
15961 -- error and stop the analysis.
15963 else
15964 Pragma_Misplaced;
15965 end if;
15967 Stmt := Prev (Stmt);
15968 end loop;
15970 -- The pragma does not apply to a legal construct, issue an error
15971 -- and stop the analysis.
15973 if No (Typ) then
15974 Pragma_Misplaced;
15975 end if;
15977 -- A pragma that applies to a Ghost entity becomes Ghost for the
15978 -- purposes of legality checks and removal of ignored Ghost code.
15980 Mark_Ghost_Pragma (N, Typ);
15982 -- The pragma signals that the type defines its own DIC assertion
15983 -- expression.
15985 Set_Has_Own_DIC (Typ);
15987 -- A type entity argument is appended to facilitate inheriting the
15988 -- aspect/pragma from parent types (see Build_DIC_Procedure_Body),
15989 -- though that extra argument isn't documented for the pragma.
15991 if No (Arg2) then
15992 -- When the pragma has no arguments, create an argument with
15993 -- the value Empty, so the type name argument can be appended
15994 -- following it (since it's expected as the second argument).
15996 if No (Arg1) then
15997 Set_Pragma_Argument_Associations (N, New_List (
15998 Make_Pragma_Argument_Association (Sloc (Typ),
15999 Expression => Empty)));
16000 end if;
16002 Append_To
16003 (Pragma_Argument_Associations (N),
16004 Make_Pragma_Argument_Association (Sloc (Typ),
16005 Expression => New_Occurrence_Of (Typ, Sloc (Typ))));
16006 end if;
16008 -- Chain the pragma on the rep item chain for further processing
16010 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
16012 -- Create the declaration of the procedure which verifies the
16013 -- assertion expression of pragma DIC at runtime.
16015 Build_DIC_Procedure_Declaration (Typ);
16016 end DIC;
16018 ----------------------------------
16019 -- Default_Scalar_Storage_Order --
16020 ----------------------------------
16022 -- pragma Default_Scalar_Storage_Order
16023 -- (High_Order_First | Low_Order_First);
16025 when Pragma_Default_Scalar_Storage_Order => DSSO : declare
16026 Default : Character;
16028 begin
16029 GNAT_Pragma;
16030 Check_Arg_Count (1);
16032 -- Default_Scalar_Storage_Order can appear as a configuration
16033 -- pragma, or in a declarative part of a package spec.
16035 if not Is_Configuration_Pragma then
16036 Check_Is_In_Decl_Part_Or_Package_Spec;
16037 end if;
16039 Check_No_Identifiers;
16040 Check_Arg_Is_One_Of
16041 (Arg1, Name_High_Order_First, Name_Low_Order_First);
16042 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
16043 Default := Fold_Upper (Name_Buffer (1));
16045 if not Support_Nondefault_SSO_On_Target
16046 and then Ttypes.Bytes_Big_Endian /= (Default = 'H')
16047 then
16048 if Warn_On_Unrecognized_Pragma then
16049 Error_Msg_N
16050 ("non-default Scalar_Storage_Order not supported "
16051 & "on target?g?", N);
16052 Error_Msg_N
16053 ("\pragma Default_Scalar_Storage_Order ignored?g?", N);
16054 end if;
16056 -- Here set the specified default
16058 else
16059 Opt.Default_SSO := Default;
16060 end if;
16061 end DSSO;
16063 --------------------------
16064 -- Default_Storage_Pool --
16065 --------------------------
16067 -- pragma Default_Storage_Pool (storage_pool_NAME | null | Standard);
16069 when Pragma_Default_Storage_Pool => Default_Storage_Pool : declare
16070 Pool : Node_Id;
16072 begin
16073 Ada_2012_Pragma;
16074 Check_Arg_Count (1);
16076 -- Default_Storage_Pool can appear as a configuration pragma, or
16077 -- in a declarative part of a package spec.
16079 if not Is_Configuration_Pragma then
16080 Check_Is_In_Decl_Part_Or_Package_Spec;
16081 end if;
16083 if From_Aspect_Specification (N) then
16084 declare
16085 E : constant Entity_Id := Entity (Corresponding_Aspect (N));
16086 begin
16087 if not In_Open_Scopes (E) then
16088 Error_Msg_N
16089 ("aspect must apply to package or subprogram", N);
16090 end if;
16091 end;
16092 end if;
16094 if Present (Arg1) then
16095 Pool := Get_Pragma_Arg (Arg1);
16097 -- Case of Default_Storage_Pool (null);
16099 if Nkind (Pool) = N_Null then
16100 Analyze (Pool);
16102 -- This is an odd case, this is not really an expression,
16103 -- so we don't have a type for it. So just set the type to
16104 -- Empty.
16106 Set_Etype (Pool, Empty);
16108 -- Case of Default_Storage_Pool (Standard);
16110 elsif Nkind (Pool) = N_Identifier
16111 and then Chars (Pool) = Name_Standard
16112 then
16113 Analyze (Pool);
16115 if Entity (Pool) /= Standard_Standard then
16116 Error_Pragma_Arg
16117 ("package Standard is not directly visible", Arg1);
16118 end if;
16120 -- Case of Default_Storage_Pool (storage_pool_NAME);
16122 else
16123 -- If it's a configuration pragma, then the only allowed
16124 -- argument is "null".
16126 if Is_Configuration_Pragma then
16127 Error_Pragma_Arg ("NULL or Standard expected", Arg1);
16128 end if;
16130 -- The expected type for a non-"null" argument is
16131 -- Root_Storage_Pool'Class, and the pool must be a variable.
16133 Analyze_And_Resolve
16134 (Pool, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
16136 if Is_Variable (Pool) then
16138 -- A pragma that applies to a Ghost entity becomes Ghost
16139 -- for the purposes of legality checks and removal of
16140 -- ignored Ghost code.
16142 Mark_Ghost_Pragma (N, Entity (Pool));
16144 else
16145 Error_Pragma_Arg
16146 ("default storage pool must be a variable", Arg1);
16147 end if;
16148 end if;
16150 -- Record the pool name (or null). Freeze.Freeze_Entity for an
16151 -- access type will use this information to set the appropriate
16152 -- attributes of the access type. If the pragma appears in a
16153 -- generic unit it is ignored, given that it may refer to a
16154 -- local entity.
16156 if not Inside_A_Generic then
16157 Default_Pool := Pool;
16158 end if;
16159 end if;
16160 end Default_Storage_Pool;
16162 -------------
16163 -- Depends --
16164 -------------
16166 -- pragma Depends (DEPENDENCY_RELATION);
16168 -- DEPENDENCY_RELATION ::=
16169 -- null
16170 -- | (DEPENDENCY_CLAUSE {, DEPENDENCY_CLAUSE})
16172 -- DEPENDENCY_CLAUSE ::=
16173 -- OUTPUT_LIST =>[+] INPUT_LIST
16174 -- | NULL_DEPENDENCY_CLAUSE
16176 -- NULL_DEPENDENCY_CLAUSE ::= null => INPUT_LIST
16178 -- OUTPUT_LIST ::= OUTPUT | (OUTPUT {, OUTPUT})
16180 -- INPUT_LIST ::= null | INPUT | (INPUT {, INPUT})
16182 -- OUTPUT ::= NAME | FUNCTION_RESULT
16183 -- INPUT ::= NAME
16185 -- where FUNCTION_RESULT is a function Result attribute_reference
16187 -- Characteristics:
16189 -- * Analysis - The annotation undergoes initial checks to verify
16190 -- the legal placement and context. Secondary checks fully analyze
16191 -- the dependency clauses in:
16193 -- Analyze_Depends_In_Decl_Part
16195 -- * Expansion - None.
16197 -- * Template - The annotation utilizes the generic template of the
16198 -- related subprogram [body] when it is:
16200 -- aspect on subprogram declaration
16201 -- aspect on stand-alone subprogram body
16202 -- pragma on stand-alone subprogram body
16204 -- The annotation must prepare its own template when it is:
16206 -- pragma on subprogram declaration
16208 -- * Globals - Capture of global references must occur after full
16209 -- analysis.
16211 -- * Instance - The annotation is instantiated automatically when
16212 -- the related generic subprogram [body] is instantiated except for
16213 -- the "pragma on subprogram declaration" case. In that scenario
16214 -- the annotation must instantiate itself.
16216 when Pragma_Depends => Depends : declare
16217 Legal : Boolean;
16218 Spec_Id : Entity_Id;
16219 Subp_Decl : Node_Id;
16221 begin
16222 Analyze_Depends_Global (Spec_Id, Subp_Decl, Legal);
16224 if Legal then
16226 -- Chain the pragma on the contract for further processing by
16227 -- Analyze_Depends_In_Decl_Part.
16229 Add_Contract_Item (N, Spec_Id);
16231 -- Fully analyze the pragma when it appears inside an entry
16232 -- or subprogram body because it cannot benefit from forward
16233 -- references.
16235 if Nkind (Subp_Decl) in N_Entry_Body
16236 | N_Subprogram_Body
16237 | N_Subprogram_Body_Stub
16238 then
16239 -- The legality checks of pragmas Depends and Global are
16240 -- affected by the SPARK mode in effect and the volatility
16241 -- of the context. In addition these two pragmas are subject
16242 -- to an inherent order:
16244 -- 1) Global
16245 -- 2) Depends
16247 -- Analyze all these pragmas in the order outlined above
16249 Analyze_If_Present (Pragma_SPARK_Mode);
16250 Analyze_If_Present (Pragma_Volatile_Function);
16251 Analyze_If_Present (Pragma_Global);
16252 Analyze_Depends_In_Decl_Part (N);
16253 end if;
16254 end if;
16255 end Depends;
16257 ---------------------
16258 -- Detect_Blocking --
16259 ---------------------
16261 -- pragma Detect_Blocking;
16263 when Pragma_Detect_Blocking =>
16264 Ada_2005_Pragma;
16265 Check_Arg_Count (0);
16266 Check_Valid_Configuration_Pragma;
16267 Detect_Blocking := True;
16269 ------------------------------------
16270 -- Disable_Atomic_Synchronization --
16271 ------------------------------------
16273 -- pragma Disable_Atomic_Synchronization [(Entity)];
16275 when Pragma_Disable_Atomic_Synchronization =>
16276 GNAT_Pragma;
16277 Process_Disable_Enable_Atomic_Sync (Name_Suppress);
16279 -------------------
16280 -- Discard_Names --
16281 -------------------
16283 -- pragma Discard_Names [([On =>] LOCAL_NAME)];
16285 when Pragma_Discard_Names => Discard_Names : declare
16286 E : Entity_Id;
16287 E_Id : Node_Id;
16289 begin
16290 Check_Ada_83_Warning;
16292 -- Deal with configuration pragma case
16294 if Is_Configuration_Pragma then
16295 if Arg_Count /= 0 then
16296 Error_Pragma
16297 ("nonzero number of arguments for configuration pragma%");
16298 else
16299 Global_Discard_Names := True;
16300 end if;
16301 return;
16303 -- Otherwise, check correct appropriate context
16305 else
16306 Check_Is_In_Decl_Part_Or_Package_Spec;
16308 if Arg_Count = 0 then
16310 -- If there is no parameter, then from now on this pragma
16311 -- applies to any enumeration, exception or tagged type
16312 -- defined in the current declarative part, and recursively
16313 -- to any nested scope.
16315 Set_Discard_Names (Current_Scope);
16316 return;
16318 else
16319 Check_Arg_Count (1);
16320 Check_Optional_Identifier (Arg1, Name_On);
16321 Check_Arg_Is_Local_Name (Arg1);
16323 E_Id := Get_Pragma_Arg (Arg1);
16325 if Etype (E_Id) = Any_Type then
16326 return;
16327 end if;
16329 E := Entity (E_Id);
16331 -- A pragma that applies to a Ghost entity becomes Ghost for
16332 -- the purposes of legality checks and removal of ignored
16333 -- Ghost code.
16335 Mark_Ghost_Pragma (N, E);
16337 if (Is_First_Subtype (E)
16338 and then
16339 (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
16340 or else Ekind (E) = E_Exception
16341 then
16342 Set_Discard_Names (E);
16343 Record_Rep_Item (E, N);
16345 else
16346 Error_Pragma_Arg
16347 ("inappropriate entity for pragma%", Arg1);
16348 end if;
16349 end if;
16350 end if;
16351 end Discard_Names;
16353 ------------------------
16354 -- Dispatching_Domain --
16355 ------------------------
16357 -- pragma Dispatching_Domain (EXPRESSION);
16359 when Pragma_Dispatching_Domain => Dispatching_Domain : declare
16360 P : constant Node_Id := Parent (N);
16361 Arg : Node_Id;
16362 Ent : Entity_Id;
16364 begin
16365 Ada_2012_Pragma;
16366 Check_No_Identifiers;
16367 Check_Arg_Count (1);
16369 -- This pragma is born obsolete, but not the aspect
16371 if not From_Aspect_Specification (N) then
16372 Check_Restriction
16373 (No_Obsolescent_Features, Pragma_Identifier (N));
16374 end if;
16376 if Nkind (P) = N_Task_Definition then
16377 Arg := Get_Pragma_Arg (Arg1);
16378 Ent := Defining_Identifier (Parent (P));
16380 -- A pragma that applies to a Ghost entity becomes Ghost for
16381 -- the purposes of legality checks and removal of ignored Ghost
16382 -- code.
16384 Mark_Ghost_Pragma (N, Ent);
16386 -- The expression must be analyzed in the special manner
16387 -- described in "Handling of Default and Per-Object
16388 -- Expressions" in sem.ads.
16390 Preanalyze_Spec_Expression (Arg, RTE (RE_Dispatching_Domain));
16392 -- Check duplicate pragma before we chain the pragma in the Rep
16393 -- Item chain of Ent.
16395 Check_Duplicate_Pragma (Ent);
16396 Record_Rep_Item (Ent, N);
16398 -- Anything else is incorrect
16400 else
16401 Pragma_Misplaced;
16402 end if;
16403 end Dispatching_Domain;
16405 ---------------
16406 -- Elaborate --
16407 ---------------
16409 -- pragma Elaborate (library_unit_NAME {, library_unit_NAME});
16411 when Pragma_Elaborate => Elaborate : declare
16412 Arg : Node_Id;
16413 Citem : Node_Id;
16415 begin
16416 -- Pragma must be in context items list of a compilation unit
16418 if not Is_In_Context_Clause then
16419 Pragma_Misplaced;
16420 end if;
16422 -- Must be at least one argument
16424 if Arg_Count = 0 then
16425 Error_Pragma ("pragma% requires at least one argument");
16426 end if;
16428 -- In Ada 83 mode, there can be no items following it in the
16429 -- context list except other pragmas and implicit with clauses
16430 -- (e.g. those added by use of Rtsfind). In Ada 95 mode, this
16431 -- placement rule does not apply.
16433 if Ada_Version = Ada_83 and then Comes_From_Source (N) then
16434 Citem := Next (N);
16435 while Present (Citem) loop
16436 if Nkind (Citem) = N_Pragma
16437 or else (Nkind (Citem) = N_With_Clause
16438 and then Implicit_With (Citem))
16439 then
16440 null;
16441 else
16442 Error_Pragma
16443 ("(Ada 83) pragma% must be at end of context clause");
16444 end if;
16446 Next (Citem);
16447 end loop;
16448 end if;
16450 -- Finally, the arguments must all be units mentioned in a with
16451 -- clause in the same context clause. Note we already checked (in
16452 -- Par.Prag) that the arguments are all identifiers or selected
16453 -- components.
16455 Arg := Arg1;
16456 Outer : while Present (Arg) loop
16457 Citem := First (List_Containing (N));
16458 Inner : while Citem /= N loop
16459 if Nkind (Citem) = N_With_Clause
16460 and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
16461 then
16462 Set_Elaborate_Present (Citem, True);
16463 Set_Elab_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
16465 -- With the pragma present, elaboration calls on
16466 -- subprograms from the named unit need no further
16467 -- checks, as long as the pragma appears in the current
16468 -- compilation unit. If the pragma appears in some unit
16469 -- in the context, there might still be a need for an
16470 -- Elaborate_All_Desirable from the current compilation
16471 -- to the named unit, so we keep the check enabled. This
16472 -- does not apply in SPARK mode, where we allow pragma
16473 -- Elaborate, but we don't trust it to be right so we
16474 -- will still insist on the Elaborate_All.
16476 if Legacy_Elaboration_Checks
16477 and then In_Extended_Main_Source_Unit (N)
16478 and then SPARK_Mode /= On
16479 then
16480 Set_Suppress_Elaboration_Warnings
16481 (Entity (Name (Citem)));
16482 end if;
16484 exit Inner;
16485 end if;
16487 Next (Citem);
16488 end loop Inner;
16490 if Citem = N then
16491 Error_Pragma_Arg
16492 ("argument of pragma% is not withed unit", Arg);
16493 end if;
16495 Next (Arg);
16496 end loop Outer;
16497 end Elaborate;
16499 -------------------
16500 -- Elaborate_All --
16501 -------------------
16503 -- pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
16505 when Pragma_Elaborate_All => Elaborate_All : declare
16506 Arg : Node_Id;
16507 Citem : Node_Id;
16509 begin
16510 Check_Ada_83_Warning;
16512 -- Pragma must be in context items list of a compilation unit
16514 if not Is_In_Context_Clause then
16515 Pragma_Misplaced;
16516 end if;
16518 -- Must be at least one argument
16520 if Arg_Count = 0 then
16521 Error_Pragma ("pragma% requires at least one argument");
16522 end if;
16524 -- Note: unlike pragma Elaborate, pragma Elaborate_All does not
16525 -- have to appear at the end of the context clause, but may
16526 -- appear mixed in with other items, even in Ada 83 mode.
16528 -- Final check: the arguments must all be units mentioned in
16529 -- a with clause in the same context clause. Note that we
16530 -- already checked (in Par.Prag) that all the arguments are
16531 -- either identifiers or selected components.
16533 Arg := Arg1;
16534 Outr : while Present (Arg) loop
16535 Citem := First (List_Containing (N));
16536 Innr : while Citem /= N loop
16537 if Nkind (Citem) = N_With_Clause
16538 and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
16539 then
16540 Set_Elaborate_All_Present (Citem, True);
16541 Set_Elab_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
16543 -- Suppress warnings and elaboration checks on the named
16544 -- unit if the pragma is in the current compilation, as
16545 -- for pragma Elaborate.
16547 if Legacy_Elaboration_Checks
16548 and then In_Extended_Main_Source_Unit (N)
16549 then
16550 Set_Suppress_Elaboration_Warnings
16551 (Entity (Name (Citem)));
16552 end if;
16554 exit Innr;
16555 end if;
16557 Next (Citem);
16558 end loop Innr;
16560 if Citem = N then
16561 Error_Pragma_Arg
16562 ("argument of pragma% is not withed unit", Arg);
16563 end if;
16565 Next (Arg);
16566 end loop Outr;
16567 end Elaborate_All;
16569 --------------------
16570 -- Elaborate_Body --
16571 --------------------
16573 -- pragma Elaborate_Body [( library_unit_NAME )];
16575 when Pragma_Elaborate_Body => Elaborate_Body : declare
16576 Cunit_Node : Node_Id;
16577 Cunit_Ent : Entity_Id;
16579 begin
16580 Check_Ada_83_Warning;
16581 Check_Valid_Library_Unit_Pragma;
16583 -- If N was rewritten as a null statement there is nothing more
16584 -- to do.
16586 if Nkind (N) = N_Null_Statement then
16587 return;
16588 end if;
16590 Cunit_Node := Cunit (Current_Sem_Unit);
16591 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
16593 -- A pragma that applies to a Ghost entity becomes Ghost for the
16594 -- purposes of legality checks and removal of ignored Ghost code.
16596 Mark_Ghost_Pragma (N, Cunit_Ent);
16598 if Nkind (Unit (Cunit_Node)) in
16599 N_Package_Body | N_Subprogram_Body
16600 then
16601 Error_Pragma ("pragma% must refer to a spec, not a body");
16602 else
16603 Set_Body_Required (Cunit_Node);
16604 Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
16606 -- If we are in dynamic elaboration mode, then we suppress
16607 -- elaboration warnings for the unit, since it is definitely
16608 -- fine NOT to do dynamic checks at the first level (and such
16609 -- checks will be suppressed because no elaboration boolean
16610 -- is created for Elaborate_Body packages).
16612 -- But in the static model of elaboration, Elaborate_Body is
16613 -- definitely NOT good enough to ensure elaboration safety on
16614 -- its own, since the body may WITH other units that are not
16615 -- safe from an elaboration point of view, so a client must
16616 -- still do an Elaborate_All on such units.
16618 -- Debug flag -gnatdD restores the old behavior of 3.13, where
16619 -- Elaborate_Body always suppressed elab warnings.
16621 if Legacy_Elaboration_Checks
16622 and then (Dynamic_Elaboration_Checks or Debug_Flag_DD)
16623 then
16624 Set_Suppress_Elaboration_Warnings (Cunit_Ent);
16625 end if;
16626 end if;
16627 end Elaborate_Body;
16629 ------------------------
16630 -- Elaboration_Checks --
16631 ------------------------
16633 -- pragma Elaboration_Checks (Static | Dynamic);
16635 when Pragma_Elaboration_Checks => Elaboration_Checks : declare
16636 procedure Check_Duplicate_Elaboration_Checks_Pragma;
16637 -- Emit an error if the current context list already contains
16638 -- a previous Elaboration_Checks pragma. This routine raises
16639 -- Pragma_Exit if a duplicate is found.
16641 procedure Ignore_Elaboration_Checks_Pragma;
16642 -- Warn that the effects of the pragma are ignored. This routine
16643 -- raises Pragma_Exit.
16645 -----------------------------------------------
16646 -- Check_Duplicate_Elaboration_Checks_Pragma --
16647 -----------------------------------------------
16649 procedure Check_Duplicate_Elaboration_Checks_Pragma is
16650 Item : Node_Id;
16652 begin
16653 Item := Prev (N);
16654 while Present (Item) loop
16655 if Nkind (Item) = N_Pragma
16656 and then Pragma_Name (Item) = Name_Elaboration_Checks
16657 then
16658 Duplication_Error
16659 (Prag => N,
16660 Prev => Item);
16661 raise Pragma_Exit;
16662 end if;
16664 Prev (Item);
16665 end loop;
16666 end Check_Duplicate_Elaboration_Checks_Pragma;
16668 --------------------------------------
16669 -- Ignore_Elaboration_Checks_Pragma --
16670 --------------------------------------
16672 procedure Ignore_Elaboration_Checks_Pragma is
16673 begin
16674 Error_Msg_Name_1 := Pname;
16675 Error_Msg_N ("??effects of pragma % are ignored", N);
16676 Error_Msg_N
16677 ("\place pragma on initial declaration of library unit", N);
16679 raise Pragma_Exit;
16680 end Ignore_Elaboration_Checks_Pragma;
16682 -- Local variables
16684 Context : constant Node_Id := Parent (N);
16685 Unt : Node_Id;
16687 -- Start of processing for Elaboration_Checks
16689 begin
16690 GNAT_Pragma;
16691 Check_Arg_Count (1);
16692 Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
16694 -- The pragma appears in a configuration file
16696 if No (Context) then
16697 Check_Valid_Configuration_Pragma;
16698 Check_Duplicate_Elaboration_Checks_Pragma;
16700 -- The pragma acts as a configuration pragma in a compilation unit
16702 -- pragma Elaboration_Checks (...);
16703 -- package Pack is ...;
16705 elsif Nkind (Context) = N_Compilation_Unit
16706 and then List_Containing (N) = Context_Items (Context)
16707 then
16708 Check_Valid_Configuration_Pragma;
16709 Check_Duplicate_Elaboration_Checks_Pragma;
16711 Unt := Unit (Context);
16713 -- The pragma must appear on the initial declaration of a unit.
16714 -- If this is not the case, warn that the effects of the pragma
16715 -- are ignored.
16717 if Nkind (Unt) = N_Package_Body then
16718 Ignore_Elaboration_Checks_Pragma;
16720 -- Check the Acts_As_Spec flag of the compilation units itself
16721 -- to determine whether the subprogram body completes since it
16722 -- has not been analyzed yet. This is safe because compilation
16723 -- units are not overloadable.
16725 elsif Nkind (Unt) = N_Subprogram_Body
16726 and then not Acts_As_Spec (Context)
16727 then
16728 Ignore_Elaboration_Checks_Pragma;
16730 elsif Nkind (Unt) = N_Subunit then
16731 Ignore_Elaboration_Checks_Pragma;
16732 end if;
16734 -- Otherwise the pragma does not appear at the configuration level
16735 -- and is illegal.
16737 else
16738 Pragma_Misplaced;
16739 end if;
16741 -- At this point the pragma is not a duplicate, and appears in the
16742 -- proper context. Set the elaboration model in effect.
16744 Dynamic_Elaboration_Checks :=
16745 Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic;
16746 end Elaboration_Checks;
16748 ---------------
16749 -- Eliminate --
16750 ---------------
16752 -- pragma Eliminate (
16753 -- [Unit_Name =>] IDENTIFIER | SELECTED_COMPONENT,
16754 -- [Entity =>] IDENTIFIER |
16755 -- SELECTED_COMPONENT |
16756 -- STRING_LITERAL]
16757 -- [, Source_Location => SOURCE_TRACE]);
16759 -- SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
16760 -- SOURCE_TRACE ::= STRING_LITERAL
16762 when Pragma_Eliminate => Eliminate : declare
16763 Args : Args_List (1 .. 5);
16764 Names : constant Name_List (1 .. 5) := (
16765 Name_Unit_Name,
16766 Name_Entity,
16767 Name_Parameter_Types,
16768 Name_Result_Type,
16769 Name_Source_Location);
16771 -- Note : Parameter_Types and Result_Type are leftovers from
16772 -- prior implementations of the pragma. They are not generated
16773 -- by the gnatelim tool, and play no role in selecting which
16774 -- of a set of overloaded names is chosen for elimination.
16776 Unit_Name : Node_Id renames Args (1);
16777 Entity : Node_Id renames Args (2);
16778 Parameter_Types : Node_Id renames Args (3);
16779 Result_Type : Node_Id renames Args (4);
16780 Source_Location : Node_Id renames Args (5);
16782 begin
16783 GNAT_Pragma;
16784 Check_Valid_Configuration_Pragma;
16785 Gather_Associations (Names, Args);
16787 if No (Unit_Name) then
16788 Error_Pragma ("missing Unit_Name argument for pragma%");
16789 end if;
16791 if No (Entity)
16792 and then (Present (Parameter_Types)
16793 or else
16794 Present (Result_Type)
16795 or else
16796 Present (Source_Location))
16797 then
16798 Error_Pragma ("missing Entity argument for pragma%");
16799 end if;
16801 if (Present (Parameter_Types)
16802 or else
16803 Present (Result_Type))
16804 and then
16805 Present (Source_Location)
16806 then
16807 Error_Pragma
16808 ("parameter profile and source location cannot be used "
16809 & "together in pragma%");
16810 end if;
16812 Process_Eliminate_Pragma
16814 Unit_Name,
16815 Entity,
16816 Parameter_Types,
16817 Result_Type,
16818 Source_Location);
16819 end Eliminate;
16821 -----------------------------------
16822 -- Enable_Atomic_Synchronization --
16823 -----------------------------------
16825 -- pragma Enable_Atomic_Synchronization [(Entity)];
16827 when Pragma_Enable_Atomic_Synchronization =>
16828 GNAT_Pragma;
16829 Process_Disable_Enable_Atomic_Sync (Name_Unsuppress);
16831 -----------------------
16832 -- Exceptional_Cases --
16833 -----------------------
16835 -- pragma Exceptional_Cases ( EXCEPTIONAL_CONTRACT_LIST );
16837 -- EXCEPTIONAL_CONTRACT_LIST ::=
16838 -- ( EXCEPTIONAL_CONTRACT {, EXCEPTIONAL_CONTRACT })
16840 -- EXCEPTIONAL_CONTRACT ::=
16841 -- EXCEPTION_CHOICE {'|' EXCEPTION_CHOICE} => CONSEQUENCE
16843 -- where
16845 -- CONSEQUENCE ::= boolean_EXPRESSION
16847 -- Characteristics:
16849 -- * Analysis - The annotation undergoes initial checks to verify
16850 -- the legal placement and context. Secondary checks preanalyze the
16851 -- expressions in:
16853 -- Analyze_Exceptional_Cases_In_Decl_Part
16855 -- * Expansion - The annotation is expanded during the expansion of
16856 -- the related subprogram [body] contract as performed in:
16858 -- Expand_Subprogram_Contract
16860 -- * Template - The annotation utilizes the generic template of the
16861 -- related subprogram [body] when it is:
16863 -- aspect on subprogram declaration
16864 -- aspect on stand-alone subprogram body
16865 -- pragma on stand-alone subprogram body
16867 -- The annotation must prepare its own template when it is:
16869 -- pragma on subprogram declaration
16871 -- * Globals - Capture of global references must occur after full
16872 -- analysis.
16874 -- * Instance - The annotation is instantiated automatically when
16875 -- the related generic subprogram [body] is instantiated except for
16876 -- the "pragma on subprogram declaration" case. In that scenario
16877 -- the annotation must instantiate itself.
16879 when Pragma_Exceptional_Cases => Exceptional_Cases : declare
16880 Spec_Id : Entity_Id;
16881 Subp_Decl : Node_Id;
16882 Subp_Spec : Node_Id;
16884 begin
16885 GNAT_Pragma;
16886 Check_No_Identifiers;
16887 Check_Arg_Count (1);
16889 -- Ensure the proper placement of the pragma. Exceptional_Cases
16890 -- must be associated with a subprogram declaration or a body that
16891 -- acts as a spec.
16893 Subp_Decl :=
16894 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
16896 -- Generic subprogram
16898 if Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
16899 null;
16901 -- Body acts as spec
16903 elsif Nkind (Subp_Decl) = N_Subprogram_Body
16904 and then No (Corresponding_Spec (Subp_Decl))
16905 then
16906 null;
16908 -- Body stub acts as spec
16910 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
16911 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
16912 then
16913 null;
16915 -- Subprogram
16917 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
16918 Subp_Spec := Specification (Subp_Decl);
16920 -- Pragma Exceptional_Cases is forbidden on null procedures,
16921 -- as this may lead to potential ambiguities in behavior when
16922 -- interface null procedures are involved. Also, it just
16923 -- wouldn't make sense, because null procedures do not raise
16924 -- exceptions.
16926 if Nkind (Subp_Spec) = N_Procedure_Specification
16927 and then Null_Present (Subp_Spec)
16928 then
16929 Error_Msg_N (Fix_Error
16930 ("pragma % cannot apply to null procedure"), N);
16931 return;
16932 end if;
16934 else
16935 Pragma_Misplaced;
16936 end if;
16938 Spec_Id := Unique_Defining_Entity (Subp_Decl);
16940 -- A pragma that applies to a Ghost entity becomes Ghost for the
16941 -- purposes of legality checks and removal of ignored Ghost code.
16943 Mark_Ghost_Pragma (N, Spec_Id);
16944 Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
16946 -- Chain the pragma on the contract for further processing by
16947 -- Analyze_Exceptional_Cases_In_Decl_Part.
16949 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
16951 -- Fully analyze the pragma when it appears inside a subprogram
16952 -- body because it cannot benefit from forward references.
16954 if Nkind (Subp_Decl) in N_Subprogram_Body
16955 | N_Subprogram_Body_Stub
16956 then
16957 -- The legality checks of pragma Exceptional_Cases are
16958 -- affected by the SPARK mode in effect and the volatility
16959 -- of the context. Analyze all pragmas in a specific order.
16961 Analyze_If_Present (Pragma_SPARK_Mode);
16962 Analyze_If_Present (Pragma_Volatile_Function);
16963 Analyze_Exceptional_Cases_In_Decl_Part (N);
16964 end if;
16965 end Exceptional_Cases;
16967 ------------
16968 -- Export --
16969 ------------
16971 -- pragma Export (
16972 -- [ Convention =>] convention_IDENTIFIER,
16973 -- [ Entity =>] LOCAL_NAME
16974 -- [, [External_Name =>] static_string_EXPRESSION ]
16975 -- [, [Link_Name =>] static_string_EXPRESSION ]);
16977 when Pragma_Export => Export : declare
16978 C : Convention_Id;
16979 Def_Id : Entity_Id;
16981 pragma Warnings (Off, C);
16983 begin
16984 Check_Ada_83_Warning;
16985 Check_Arg_Order
16986 ((Name_Convention,
16987 Name_Entity,
16988 Name_External_Name,
16989 Name_Link_Name));
16991 Check_At_Least_N_Arguments (2);
16992 Check_At_Most_N_Arguments (4);
16994 -- In Relaxed_RM_Semantics, support old Ada 83 style:
16995 -- pragma Export (Entity, "external name");
16997 if Relaxed_RM_Semantics
16998 and then Arg_Count = 2
16999 and then Nkind (Expression (Arg2)) = N_String_Literal
17000 then
17001 C := Convention_C;
17002 Def_Id := Get_Pragma_Arg (Arg1);
17003 Analyze (Def_Id);
17005 if not Is_Entity_Name (Def_Id) then
17006 Error_Pragma_Arg ("entity name required", Arg1);
17007 end if;
17009 Def_Id := Entity (Def_Id);
17010 Set_Exported (Def_Id, Arg1);
17012 else
17013 Process_Convention (C, Def_Id);
17015 -- A pragma that applies to a Ghost entity becomes Ghost for
17016 -- the purposes of legality checks and removal of ignored Ghost
17017 -- code.
17019 Mark_Ghost_Pragma (N, Def_Id);
17021 if Ekind (Def_Id) /= E_Constant then
17022 Note_Possible_Modification
17023 (Get_Pragma_Arg (Arg2), Sure => False);
17024 end if;
17026 Process_Interface_Name (Def_Id, Arg3, Arg4, N);
17027 Set_Exported (Def_Id, Arg2);
17028 end if;
17030 -- If the entity is a deferred constant, propagate the information
17031 -- to the full view, because gigi elaborates the full view only.
17033 if Ekind (Def_Id) = E_Constant
17034 and then Present (Full_View (Def_Id))
17035 then
17036 declare
17037 Id2 : constant Entity_Id := Full_View (Def_Id);
17038 begin
17039 Set_Is_Exported (Id2, Is_Exported (Def_Id));
17040 Set_First_Rep_Item (Id2, First_Rep_Item (Def_Id));
17041 Set_Interface_Name
17042 (Id2, Einfo.Entities.Interface_Name (Def_Id));
17043 end;
17044 end if;
17045 end Export;
17047 ---------------------
17048 -- Export_Function --
17049 ---------------------
17051 -- pragma Export_Function (
17052 -- [Internal =>] LOCAL_NAME
17053 -- [, [External =>] EXTERNAL_SYMBOL]
17054 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
17055 -- [, [Result_Type =>] TYPE_DESIGNATOR]
17056 -- [, [Mechanism =>] MECHANISM]
17057 -- [, [Result_Mechanism =>] MECHANISM_NAME]);
17059 -- EXTERNAL_SYMBOL ::=
17060 -- IDENTIFIER
17061 -- | static_string_EXPRESSION
17063 -- PARAMETER_TYPES ::=
17064 -- null
17065 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
17067 -- TYPE_DESIGNATOR ::=
17068 -- subtype_NAME
17069 -- | subtype_Name ' Access
17071 -- MECHANISM ::=
17072 -- MECHANISM_NAME
17073 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
17075 -- MECHANISM_ASSOCIATION ::=
17076 -- [formal_parameter_NAME =>] MECHANISM_NAME
17078 -- MECHANISM_NAME ::=
17079 -- Value
17080 -- | Reference
17082 when Pragma_Export_Function => Export_Function : declare
17083 Args : Args_List (1 .. 6);
17084 Names : constant Name_List (1 .. 6) := (
17085 Name_Internal,
17086 Name_External,
17087 Name_Parameter_Types,
17088 Name_Result_Type,
17089 Name_Mechanism,
17090 Name_Result_Mechanism);
17092 Internal : Node_Id renames Args (1);
17093 External : Node_Id renames Args (2);
17094 Parameter_Types : Node_Id renames Args (3);
17095 Result_Type : Node_Id renames Args (4);
17096 Mechanism : Node_Id renames Args (5);
17097 Result_Mechanism : Node_Id renames Args (6);
17099 begin
17100 GNAT_Pragma;
17101 Gather_Associations (Names, Args);
17102 Process_Extended_Import_Export_Subprogram_Pragma (
17103 Arg_Internal => Internal,
17104 Arg_External => External,
17105 Arg_Parameter_Types => Parameter_Types,
17106 Arg_Result_Type => Result_Type,
17107 Arg_Mechanism => Mechanism,
17108 Arg_Result_Mechanism => Result_Mechanism);
17109 end Export_Function;
17111 -------------------
17112 -- Export_Object --
17113 -------------------
17115 -- pragma Export_Object (
17116 -- [Internal =>] LOCAL_NAME
17117 -- [, [External =>] EXTERNAL_SYMBOL]
17118 -- [, [Size =>] EXTERNAL_SYMBOL]);
17120 -- EXTERNAL_SYMBOL ::=
17121 -- IDENTIFIER
17122 -- | static_string_EXPRESSION
17124 -- PARAMETER_TYPES ::=
17125 -- null
17126 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
17128 -- TYPE_DESIGNATOR ::=
17129 -- subtype_NAME
17130 -- | subtype_Name ' Access
17132 -- MECHANISM ::=
17133 -- MECHANISM_NAME
17134 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
17136 -- MECHANISM_ASSOCIATION ::=
17137 -- [formal_parameter_NAME =>] MECHANISM_NAME
17139 -- MECHANISM_NAME ::=
17140 -- Value
17141 -- | Reference
17143 when Pragma_Export_Object => Export_Object : declare
17144 Args : Args_List (1 .. 3);
17145 Names : constant Name_List (1 .. 3) := (
17146 Name_Internal,
17147 Name_External,
17148 Name_Size);
17150 Internal : Node_Id renames Args (1);
17151 External : Node_Id renames Args (2);
17152 Size : Node_Id renames Args (3);
17154 begin
17155 GNAT_Pragma;
17156 Gather_Associations (Names, Args);
17157 Process_Extended_Import_Export_Object_Pragma (
17158 Arg_Internal => Internal,
17159 Arg_External => External,
17160 Arg_Size => Size);
17161 end Export_Object;
17163 ----------------------
17164 -- Export_Procedure --
17165 ----------------------
17167 -- pragma Export_Procedure (
17168 -- [Internal =>] LOCAL_NAME
17169 -- [, [External =>] EXTERNAL_SYMBOL]
17170 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
17171 -- [, [Mechanism =>] MECHANISM]);
17173 -- EXTERNAL_SYMBOL ::=
17174 -- IDENTIFIER
17175 -- | static_string_EXPRESSION
17177 -- PARAMETER_TYPES ::=
17178 -- null
17179 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
17181 -- TYPE_DESIGNATOR ::=
17182 -- subtype_NAME
17183 -- | subtype_Name ' Access
17185 -- MECHANISM ::=
17186 -- MECHANISM_NAME
17187 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
17189 -- MECHANISM_ASSOCIATION ::=
17190 -- [formal_parameter_NAME =>] MECHANISM_NAME
17192 -- MECHANISM_NAME ::=
17193 -- Value
17194 -- | Reference
17196 when Pragma_Export_Procedure => Export_Procedure : declare
17197 Args : Args_List (1 .. 4);
17198 Names : constant Name_List (1 .. 4) := (
17199 Name_Internal,
17200 Name_External,
17201 Name_Parameter_Types,
17202 Name_Mechanism);
17204 Internal : Node_Id renames Args (1);
17205 External : Node_Id renames Args (2);
17206 Parameter_Types : Node_Id renames Args (3);
17207 Mechanism : Node_Id renames Args (4);
17209 begin
17210 GNAT_Pragma;
17211 Gather_Associations (Names, Args);
17212 Process_Extended_Import_Export_Subprogram_Pragma (
17213 Arg_Internal => Internal,
17214 Arg_External => External,
17215 Arg_Parameter_Types => Parameter_Types,
17216 Arg_Mechanism => Mechanism);
17217 end Export_Procedure;
17219 -----------------------------
17220 -- Export_Valued_Procedure --
17221 -----------------------------
17223 -- pragma Export_Valued_Procedure (
17224 -- [Internal =>] LOCAL_NAME
17225 -- [, [External =>] EXTERNAL_SYMBOL,]
17226 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
17227 -- [, [Mechanism =>] MECHANISM]);
17229 -- EXTERNAL_SYMBOL ::=
17230 -- IDENTIFIER
17231 -- | static_string_EXPRESSION
17233 -- PARAMETER_TYPES ::=
17234 -- null
17235 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
17237 -- TYPE_DESIGNATOR ::=
17238 -- subtype_NAME
17239 -- | subtype_Name ' Access
17241 -- MECHANISM ::=
17242 -- MECHANISM_NAME
17243 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
17245 -- MECHANISM_ASSOCIATION ::=
17246 -- [formal_parameter_NAME =>] MECHANISM_NAME
17248 -- MECHANISM_NAME ::=
17249 -- Value
17250 -- | Reference
17252 when Pragma_Export_Valued_Procedure =>
17253 Export_Valued_Procedure : declare
17254 Args : Args_List (1 .. 4);
17255 Names : constant Name_List (1 .. 4) := (
17256 Name_Internal,
17257 Name_External,
17258 Name_Parameter_Types,
17259 Name_Mechanism);
17261 Internal : Node_Id renames Args (1);
17262 External : Node_Id renames Args (2);
17263 Parameter_Types : Node_Id renames Args (3);
17264 Mechanism : Node_Id renames Args (4);
17266 begin
17267 GNAT_Pragma;
17268 Gather_Associations (Names, Args);
17269 Process_Extended_Import_Export_Subprogram_Pragma (
17270 Arg_Internal => Internal,
17271 Arg_External => External,
17272 Arg_Parameter_Types => Parameter_Types,
17273 Arg_Mechanism => Mechanism);
17274 end Export_Valued_Procedure;
17276 -------------------
17277 -- Extend_System --
17278 -------------------
17280 -- pragma Extend_System ([Name =>] Identifier);
17282 when Pragma_Extend_System =>
17283 GNAT_Pragma;
17284 Check_Valid_Configuration_Pragma;
17285 Check_Arg_Count (1);
17286 Check_Optional_Identifier (Arg1, Name_Name);
17287 Check_Arg_Is_Identifier (Arg1);
17289 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
17291 if Name_Len > 4
17292 and then Name_Buffer (1 .. 4) = "aux_"
17293 then
17294 if Present (System_Extend_Pragma_Arg) then
17295 if Chars (Get_Pragma_Arg (Arg1)) =
17296 Chars (Expression (System_Extend_Pragma_Arg))
17297 then
17298 null;
17299 else
17300 Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
17301 Error_Pragma ("pragma% conflicts with that #");
17302 end if;
17304 else
17305 System_Extend_Pragma_Arg := Arg1;
17307 if not GNAT_Mode then
17308 System_Extend_Unit := Arg1;
17309 end if;
17310 end if;
17311 else
17312 Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
17313 end if;
17315 ------------------------
17316 -- Extensions_Allowed --
17317 ------------------------
17319 -- pragma Extensions_Allowed (ON | OFF | ALL);
17321 when Pragma_Extensions_Allowed =>
17322 GNAT_Pragma;
17323 Check_Arg_Count (1);
17324 Check_No_Identifiers;
17325 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off, Name_All);
17327 if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
17328 Ada_Version := Ada_With_Core_Extensions;
17329 elsif Chars (Get_Pragma_Arg (Arg1)) = Name_All then
17330 Ada_Version := Ada_With_All_Extensions;
17331 else
17332 Ada_Version := Ada_Version_Explicit;
17333 Ada_Version_Pragma := Empty;
17334 end if;
17336 ------------------------
17337 -- Extensions_Visible --
17338 ------------------------
17340 -- pragma Extensions_Visible [ (boolean_EXPRESSION) ];
17342 -- Characteristics:
17344 -- * Analysis - The annotation is fully analyzed immediately upon
17345 -- elaboration as its expression must be static.
17347 -- * Expansion - None.
17349 -- * Template - The annotation utilizes the generic template of the
17350 -- related subprogram [body] when it is:
17352 -- aspect on subprogram declaration
17353 -- aspect on stand-alone subprogram body
17354 -- pragma on stand-alone subprogram body
17356 -- The annotation must prepare its own template when it is:
17358 -- pragma on subprogram declaration
17360 -- * Globals - Capture of global references must occur after full
17361 -- analysis.
17363 -- * Instance - The annotation is instantiated automatically when
17364 -- the related generic subprogram [body] is instantiated except for
17365 -- the "pragma on subprogram declaration" case. In that scenario
17366 -- the annotation must instantiate itself.
17368 when Pragma_Extensions_Visible => Extensions_Visible : declare
17369 Formal : Entity_Id;
17370 Has_OK_Formal : Boolean := False;
17371 Spec_Id : Entity_Id;
17372 Subp_Decl : Node_Id;
17374 begin
17375 GNAT_Pragma;
17376 Check_No_Identifiers;
17377 Check_At_Most_N_Arguments (1);
17379 Subp_Decl :=
17380 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
17382 -- Abstract subprogram declaration
17384 if Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
17385 null;
17387 -- Generic subprogram declaration
17389 elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
17390 null;
17392 -- Body acts as spec
17394 elsif Nkind (Subp_Decl) = N_Subprogram_Body
17395 and then No (Corresponding_Spec (Subp_Decl))
17396 then
17397 null;
17399 -- Body stub acts as spec
17401 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
17402 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
17403 then
17404 null;
17406 -- Subprogram declaration
17408 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
17409 null;
17411 -- Otherwise the pragma is associated with an illegal construct
17413 else
17414 Error_Pragma ("pragma % must apply to a subprogram");
17415 end if;
17417 -- Mark the pragma as Ghost if the related subprogram is also
17418 -- Ghost. This also ensures that any expansion performed further
17419 -- below will produce Ghost nodes.
17421 Spec_Id := Unique_Defining_Entity (Subp_Decl);
17422 Mark_Ghost_Pragma (N, Spec_Id);
17424 -- Chain the pragma on the contract for completeness
17426 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
17428 -- The legality checks of pragma Extension_Visible are affected
17429 -- by the SPARK mode in effect. Analyze all pragmas in specific
17430 -- order.
17432 Analyze_If_Present (Pragma_SPARK_Mode);
17434 -- Examine the formals of the related subprogram
17436 Formal := First_Formal (Spec_Id);
17437 while Present (Formal) loop
17439 -- At least one of the formals is of a specific tagged type,
17440 -- the pragma is legal.
17442 if Is_Specific_Tagged_Type (Etype (Formal)) then
17443 Has_OK_Formal := True;
17444 exit;
17446 -- A generic subprogram with at least one formal of a private
17447 -- type ensures the legality of the pragma because the actual
17448 -- may be specifically tagged. Note that this is verified by
17449 -- the check above at instantiation time.
17451 elsif Is_Private_Type (Etype (Formal))
17452 and then Is_Generic_Type (Etype (Formal))
17453 then
17454 Has_OK_Formal := True;
17455 exit;
17456 end if;
17458 Next_Formal (Formal);
17459 end loop;
17461 if not Has_OK_Formal then
17462 Error_Msg_Name_1 := Pname;
17463 Error_Msg_N (Fix_Error ("incorrect placement of pragma %"), N);
17464 Error_Msg_NE
17465 ("\subprogram & lacks parameter of specific tagged or "
17466 & "generic private type", N, Spec_Id);
17468 return;
17469 end if;
17471 -- Analyze the Boolean expression (if any)
17473 if Present (Arg1) then
17474 Check_Static_Boolean_Expression
17475 (Expression (Get_Argument (N, Spec_Id)));
17476 end if;
17477 end Extensions_Visible;
17479 --------------
17480 -- External --
17481 --------------
17483 -- pragma External (
17484 -- [ Convention =>] convention_IDENTIFIER,
17485 -- [ Entity =>] LOCAL_NAME
17486 -- [, [External_Name =>] static_string_EXPRESSION ]
17487 -- [, [Link_Name =>] static_string_EXPRESSION ]);
17489 when Pragma_External => External : declare
17490 C : Convention_Id;
17491 E : Entity_Id;
17492 pragma Warnings (Off, C);
17494 begin
17495 GNAT_Pragma;
17496 Check_Arg_Order
17497 ((Name_Convention,
17498 Name_Entity,
17499 Name_External_Name,
17500 Name_Link_Name));
17501 Check_At_Least_N_Arguments (2);
17502 Check_At_Most_N_Arguments (4);
17503 Process_Convention (C, E);
17505 -- A pragma that applies to a Ghost entity becomes Ghost for the
17506 -- purposes of legality checks and removal of ignored Ghost code.
17508 Mark_Ghost_Pragma (N, E);
17510 Note_Possible_Modification
17511 (Get_Pragma_Arg (Arg2), Sure => False);
17512 Process_Interface_Name (E, Arg3, Arg4, N);
17513 Set_Exported (E, Arg2);
17514 end External;
17516 --------------------------
17517 -- External_Name_Casing --
17518 --------------------------
17520 -- pragma External_Name_Casing (
17521 -- UPPERCASE | LOWERCASE
17522 -- [, AS_IS | UPPERCASE | LOWERCASE]);
17524 when Pragma_External_Name_Casing =>
17525 GNAT_Pragma;
17526 Check_No_Identifiers;
17528 if Arg_Count = 2 then
17529 Check_Arg_Is_One_Of
17530 (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
17532 case Chars (Get_Pragma_Arg (Arg2)) is
17533 when Name_As_Is =>
17534 Opt.External_Name_Exp_Casing := As_Is;
17536 when Name_Uppercase =>
17537 Opt.External_Name_Exp_Casing := Uppercase;
17539 when Name_Lowercase =>
17540 Opt.External_Name_Exp_Casing := Lowercase;
17542 when others =>
17543 null;
17544 end case;
17546 else
17547 Check_Arg_Count (1);
17548 end if;
17550 Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
17552 case Chars (Get_Pragma_Arg (Arg1)) is
17553 when Name_Uppercase =>
17554 Opt.External_Name_Imp_Casing := Uppercase;
17556 when Name_Lowercase =>
17557 Opt.External_Name_Imp_Casing := Lowercase;
17559 when others =>
17560 null;
17561 end case;
17563 ---------------
17564 -- Fast_Math --
17565 ---------------
17567 -- pragma Fast_Math;
17569 when Pragma_Fast_Math =>
17570 GNAT_Pragma;
17571 Check_No_Identifiers;
17572 Check_Valid_Configuration_Pragma;
17573 Fast_Math := True;
17575 --------------------------
17576 -- Favor_Top_Level --
17577 --------------------------
17579 -- pragma Favor_Top_Level (type_NAME);
17581 when Pragma_Favor_Top_Level => Favor_Top_Level : declare
17582 Typ : Entity_Id;
17584 begin
17585 GNAT_Pragma;
17586 Check_No_Identifiers;
17587 Check_Arg_Count (1);
17588 Check_Arg_Is_Local_Name (Arg1);
17589 Typ := Entity (Get_Pragma_Arg (Arg1));
17591 -- A pragma that applies to a Ghost entity becomes Ghost for the
17592 -- purposes of legality checks and removal of ignored Ghost code.
17594 Mark_Ghost_Pragma (N, Typ);
17596 -- If it's an access-to-subprogram type (in particular, not a
17597 -- subtype), set the flag on that type.
17599 if Is_Access_Subprogram_Type (Typ) then
17600 Set_Can_Use_Internal_Rep (Typ, False);
17602 -- Otherwise it's an error (name denotes the wrong sort of entity)
17604 else
17605 Error_Pragma_Arg
17606 ("access-to-subprogram type expected",
17607 Get_Pragma_Arg (Arg1));
17608 end if;
17609 end Favor_Top_Level;
17611 ---------------------------
17612 -- Finalize_Storage_Only --
17613 ---------------------------
17615 -- pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
17617 when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
17618 Assoc : constant Node_Id := Arg1;
17619 Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
17620 Typ : Entity_Id;
17622 begin
17623 GNAT_Pragma;
17624 Check_No_Identifiers;
17625 Check_Arg_Count (1);
17626 Check_Arg_Is_Local_Name (Arg1);
17628 Find_Type (Type_Id);
17629 Typ := Entity (Type_Id);
17631 if Typ = Any_Type
17632 or else Rep_Item_Too_Early (Typ, N)
17633 then
17634 return;
17635 else
17636 Typ := Underlying_Type (Typ);
17637 end if;
17639 if not Is_Controlled (Typ) then
17640 Error_Pragma ("pragma% must specify controlled type");
17641 end if;
17643 Check_First_Subtype (Arg1);
17645 if Finalize_Storage_Only (Typ) then
17646 Error_Pragma ("duplicate pragma%, only one allowed");
17648 elsif not Rep_Item_Too_Late (Typ, N) then
17649 Set_Finalize_Storage_Only (Base_Type (Typ), True);
17650 end if;
17651 end Finalize_Storage;
17653 -----------
17654 -- Ghost --
17655 -----------
17657 -- pragma Ghost [ (boolean_EXPRESSION) ];
17659 when Pragma_Ghost => Ghost : declare
17660 Context : Node_Id;
17661 Expr : Node_Id;
17662 Id : Entity_Id;
17663 Orig_Stmt : Node_Id;
17664 Prev_Id : Entity_Id;
17665 Stmt : Node_Id;
17667 begin
17668 GNAT_Pragma;
17669 Check_No_Identifiers;
17670 Check_At_Most_N_Arguments (1);
17672 Id := Empty;
17673 Stmt := Prev (N);
17674 while Present (Stmt) loop
17676 -- Skip prior pragmas, but check for duplicates
17678 if Nkind (Stmt) = N_Pragma then
17679 if Pragma_Name (Stmt) = Pname then
17680 Duplication_Error
17681 (Prag => N,
17682 Prev => Stmt);
17683 raise Pragma_Exit;
17684 end if;
17686 -- Task unit declared without a definition cannot be subject to
17687 -- pragma Ghost (SPARK RM 6.9(19)).
17689 elsif Nkind (Stmt) in
17690 N_Single_Task_Declaration | N_Task_Type_Declaration
17691 then
17692 Error_Pragma ("pragma % cannot apply to a task type");
17694 -- Skip internally generated code
17696 elsif not Comes_From_Source (Stmt) then
17697 Orig_Stmt := Original_Node (Stmt);
17699 -- When pragma Ghost applies to an untagged derivation, the
17700 -- derivation is transformed into a [sub]type declaration.
17702 if Nkind (Stmt) in
17703 N_Full_Type_Declaration | N_Subtype_Declaration
17704 and then Comes_From_Source (Orig_Stmt)
17705 and then Nkind (Orig_Stmt) = N_Full_Type_Declaration
17706 and then Nkind (Type_Definition (Orig_Stmt)) =
17707 N_Derived_Type_Definition
17708 then
17709 Id := Defining_Entity (Stmt);
17710 exit;
17712 -- When pragma Ghost applies to an object declaration which
17713 -- is initialized by means of a function call that returns
17714 -- on the secondary stack, the object declaration becomes a
17715 -- renaming.
17717 elsif Nkind (Stmt) = N_Object_Renaming_Declaration
17718 and then Comes_From_Source (Orig_Stmt)
17719 and then Nkind (Orig_Stmt) = N_Object_Declaration
17720 then
17721 Id := Defining_Entity (Stmt);
17722 exit;
17724 -- When pragma Ghost applies to an expression function, the
17725 -- expression function is transformed into a subprogram.
17727 elsif Nkind (Stmt) = N_Subprogram_Declaration
17728 and then Comes_From_Source (Orig_Stmt)
17729 and then Nkind (Orig_Stmt) = N_Expression_Function
17730 then
17731 Id := Defining_Entity (Stmt);
17732 exit;
17734 -- When pragma Ghost applies to a generic formal type, the
17735 -- type declaration in the instantiation is a generated
17736 -- subtype declaration.
17738 elsif Nkind (Stmt) = N_Subtype_Declaration
17739 and then Present (Generic_Parent_Type (Stmt))
17740 then
17741 Id := Defining_Entity (Stmt);
17742 exit;
17743 end if;
17745 -- The pragma applies to a legal construct, stop the traversal
17747 elsif Nkind (Stmt) in N_Abstract_Subprogram_Declaration
17748 | N_Formal_Object_Declaration
17749 | N_Formal_Subprogram_Declaration
17750 | N_Formal_Type_Declaration
17751 | N_Full_Type_Declaration
17752 | N_Generic_Subprogram_Declaration
17753 | N_Object_Declaration
17754 | N_Private_Extension_Declaration
17755 | N_Private_Type_Declaration
17756 | N_Subprogram_Declaration
17757 | N_Subtype_Declaration
17758 then
17759 Id := Defining_Entity (Stmt);
17760 exit;
17762 -- The pragma does not apply to a legal construct, issue an
17763 -- error and stop the analysis.
17765 else
17766 Error_Pragma
17767 ("pragma % must apply to an object, package, subprogram "
17768 & "or type");
17769 end if;
17771 Stmt := Prev (Stmt);
17772 end loop;
17774 Context := Parent (N);
17776 -- Handle compilation units
17778 if Nkind (Context) = N_Compilation_Unit_Aux then
17779 Context := Unit (Parent (Context));
17780 end if;
17782 -- Protected and task types cannot be subject to pragma Ghost
17783 -- (SPARK RM 6.9(19)).
17785 if Nkind (Context) in N_Protected_Body | N_Protected_Definition
17786 then
17787 Error_Pragma ("pragma % cannot apply to a protected type");
17789 elsif Nkind (Context) in N_Task_Body | N_Task_Definition then
17790 Error_Pragma ("pragma % cannot apply to a task type");
17791 end if;
17793 if No (Id) then
17795 -- When pragma Ghost is associated with a [generic] package, it
17796 -- appears in the visible declarations.
17798 if Nkind (Context) = N_Package_Specification
17799 and then Present (Visible_Declarations (Context))
17800 and then List_Containing (N) = Visible_Declarations (Context)
17801 then
17802 Id := Defining_Entity (Context);
17804 -- Pragma Ghost applies to a stand-alone subprogram body
17806 elsif Nkind (Context) = N_Subprogram_Body
17807 and then No (Corresponding_Spec (Context))
17808 then
17809 Id := Defining_Entity (Context);
17811 -- Pragma Ghost applies to a subprogram declaration that acts
17812 -- as a compilation unit.
17814 elsif Nkind (Context) = N_Subprogram_Declaration then
17815 Id := Defining_Entity (Context);
17817 -- Pragma Ghost applies to a generic subprogram
17819 elsif Nkind (Context) = N_Generic_Subprogram_Declaration then
17820 Id := Defining_Entity (Specification (Context));
17821 end if;
17822 end if;
17824 if No (Id) then
17825 Error_Pragma
17826 ("pragma % must apply to an object, package, subprogram or "
17827 & "type");
17828 end if;
17830 -- Handle completions of types and constants that are subject to
17831 -- pragma Ghost.
17833 if Is_Record_Type (Id) or else Ekind (Id) = E_Constant then
17834 Prev_Id := Incomplete_Or_Partial_View (Id);
17836 if Present (Prev_Id) and then not Is_Ghost_Entity (Prev_Id) then
17837 Error_Msg_Name_1 := Pname;
17839 -- The full declaration of a deferred constant cannot be
17840 -- subject to pragma Ghost unless the deferred declaration
17841 -- is also Ghost (SPARK RM 6.9(9)).
17843 if Ekind (Prev_Id) = E_Constant then
17844 Error_Msg_Name_1 := Pname;
17845 Error_Msg_NE (Fix_Error
17846 ("pragma % must apply to declaration of deferred "
17847 & "constant &"), N, Id);
17848 return;
17850 -- Pragma Ghost may appear on the full view of an incomplete
17851 -- type because the incomplete declaration lacks aspects and
17852 -- cannot be subject to pragma Ghost.
17854 elsif Ekind (Prev_Id) = E_Incomplete_Type then
17855 null;
17857 -- The full declaration of a type cannot be subject to
17858 -- pragma Ghost unless the partial view is also Ghost
17859 -- (SPARK RM 6.9(9)).
17861 else
17862 Error_Msg_NE (Fix_Error
17863 ("pragma % must apply to partial view of type &"),
17864 N, Id);
17865 return;
17866 end if;
17867 end if;
17869 -- A synchronized object cannot be subject to pragma Ghost
17870 -- (SPARK RM 6.9(19)).
17872 elsif Ekind (Id) = E_Variable then
17873 if Is_Protected_Type (Etype (Id)) then
17874 Error_Pragma ("pragma % cannot apply to a protected object");
17876 elsif Is_Task_Type (Etype (Id)) then
17877 Error_Pragma ("pragma % cannot apply to a task object");
17878 end if;
17879 end if;
17881 -- Analyze the Boolean expression (if any)
17883 if Present (Arg1) then
17884 Expr := Get_Pragma_Arg (Arg1);
17886 Analyze_And_Resolve (Expr, Standard_Boolean);
17888 if Is_OK_Static_Expression (Expr) then
17890 -- "Ghostness" cannot be turned off once enabled within a
17891 -- region (SPARK RM 6.9(6)).
17893 if Is_False (Expr_Value (Expr))
17894 and then Ghost_Mode > None
17895 then
17896 Error_Pragma
17897 ("pragma % with value False cannot appear in enabled "
17898 & "ghost region");
17899 end if;
17901 -- Otherwise the expression is not static
17903 else
17904 Error_Pragma_Arg
17905 ("expression of pragma % must be static", Expr);
17906 end if;
17907 end if;
17909 Set_Is_Ghost_Entity (Id);
17910 end Ghost;
17912 ------------
17913 -- Global --
17914 ------------
17916 -- pragma Global (GLOBAL_SPECIFICATION);
17918 -- GLOBAL_SPECIFICATION ::=
17919 -- null
17920 -- | (GLOBAL_LIST)
17921 -- | (MODED_GLOBAL_LIST {, MODED_GLOBAL_LIST})
17923 -- MODED_GLOBAL_LIST ::= MODE_SELECTOR => GLOBAL_LIST
17925 -- MODE_SELECTOR ::= In_Out | Input | Output | Proof_In
17926 -- GLOBAL_LIST ::= GLOBAL_ITEM | (GLOBAL_ITEM {, GLOBAL_ITEM})
17927 -- GLOBAL_ITEM ::= NAME
17929 -- Characteristics:
17931 -- * Analysis - The annotation undergoes initial checks to verify
17932 -- the legal placement and context. Secondary checks fully analyze
17933 -- the dependency clauses in:
17935 -- Analyze_Global_In_Decl_Part
17937 -- * Expansion - None.
17939 -- * Template - The annotation utilizes the generic template of the
17940 -- related subprogram [body] when it is:
17942 -- aspect on subprogram declaration
17943 -- aspect on stand-alone subprogram body
17944 -- pragma on stand-alone subprogram body
17946 -- The annotation must prepare its own template when it is:
17948 -- pragma on subprogram declaration
17950 -- * Globals - Capture of global references must occur after full
17951 -- analysis.
17953 -- * Instance - The annotation is instantiated automatically when
17954 -- the related generic subprogram [body] is instantiated except for
17955 -- the "pragma on subprogram declaration" case. In that scenario
17956 -- the annotation must instantiate itself.
17958 when Pragma_Global => Global : declare
17959 Legal : Boolean;
17960 Spec_Id : Entity_Id;
17961 Subp_Decl : Node_Id;
17963 begin
17964 Analyze_Depends_Global (Spec_Id, Subp_Decl, Legal);
17966 if Legal then
17968 -- Chain the pragma on the contract for further processing by
17969 -- Analyze_Global_In_Decl_Part.
17971 Add_Contract_Item (N, Spec_Id);
17973 -- Fully analyze the pragma when it appears inside an entry
17974 -- or subprogram body because it cannot benefit from forward
17975 -- references.
17977 if Nkind (Subp_Decl) in N_Entry_Body
17978 | N_Subprogram_Body
17979 | N_Subprogram_Body_Stub
17980 then
17981 -- The legality checks of pragmas Depends and Global are
17982 -- affected by the SPARK mode in effect and the volatility
17983 -- of the context. In addition these two pragmas are subject
17984 -- to an inherent order:
17986 -- 1) Global
17987 -- 2) Depends
17989 -- Analyze all these pragmas in the order outlined above
17991 Analyze_If_Present (Pragma_SPARK_Mode);
17992 Analyze_If_Present (Pragma_Volatile_Function);
17993 Analyze_Global_In_Decl_Part (N);
17994 Analyze_If_Present (Pragma_Depends);
17995 end if;
17996 end if;
17997 end Global;
17999 -----------
18000 -- Ident --
18001 -----------
18003 -- pragma Ident (static_string_EXPRESSION)
18005 -- Note: pragma Comment shares this processing. Pragma Ident is
18006 -- identical in effect to pragma Commment.
18008 when Pragma_Comment
18009 | Pragma_Ident
18011 Ident : declare
18012 Str : Node_Id;
18014 begin
18015 GNAT_Pragma;
18016 Check_Arg_Count (1);
18017 Check_No_Identifiers;
18018 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
18019 Store_Note (N);
18021 Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
18023 declare
18024 CS : Node_Id;
18025 GP : Node_Id;
18027 begin
18028 GP := Parent (Parent (N));
18030 if Nkind (GP) in
18031 N_Package_Declaration | N_Generic_Package_Declaration
18032 then
18033 GP := Parent (GP);
18034 end if;
18036 -- If we have a compilation unit, then record the ident value,
18037 -- checking for improper duplication.
18039 if Nkind (GP) = N_Compilation_Unit then
18040 CS := Ident_String (Current_Sem_Unit);
18042 if Present (CS) then
18044 -- If we have multiple instances, concatenate them.
18046 Start_String (Strval (CS));
18047 Store_String_Char (' ');
18048 Store_String_Chars (Strval (Str));
18049 Set_Strval (CS, End_String);
18051 else
18052 Set_Ident_String (Current_Sem_Unit, Str);
18053 end if;
18055 -- For subunits, we just ignore the Ident, since in GNAT these
18056 -- are not separate object files, and hence not separate units
18057 -- in the unit table.
18059 elsif Nkind (GP) = N_Subunit then
18060 null;
18061 end if;
18062 end;
18063 end Ident;
18065 -------------------
18066 -- Ignore_Pragma --
18067 -------------------
18069 -- pragma Ignore_Pragma (pragma_IDENTIFIER);
18071 -- Entirely handled in the parser, nothing to do here
18073 when Pragma_Ignore_Pragma =>
18074 null;
18076 ----------------------------
18077 -- Implementation_Defined --
18078 ----------------------------
18080 -- pragma Implementation_Defined (LOCAL_NAME);
18082 -- Marks previously declared entity as implementation defined. For
18083 -- an overloaded entity, applies to the most recent homonym.
18085 -- pragma Implementation_Defined;
18087 -- The form with no arguments appears anywhere within a scope, most
18088 -- typically a package spec, and indicates that all entities that are
18089 -- defined within the package spec are Implementation_Defined.
18091 when Pragma_Implementation_Defined => Implementation_Defined : declare
18092 Ent : Entity_Id;
18094 begin
18095 GNAT_Pragma;
18096 Check_No_Identifiers;
18098 -- Form with no arguments
18100 if Arg_Count = 0 then
18101 Set_Is_Implementation_Defined (Current_Scope);
18103 -- Form with one argument
18105 else
18106 Check_Arg_Count (1);
18107 Check_Arg_Is_Local_Name (Arg1);
18108 Ent := Entity (Get_Pragma_Arg (Arg1));
18109 Set_Is_Implementation_Defined (Ent);
18110 end if;
18111 end Implementation_Defined;
18113 -----------------
18114 -- Implemented --
18115 -----------------
18117 -- pragma Implemented (procedure_LOCAL_NAME, IMPLEMENTATION_KIND);
18119 -- IMPLEMENTATION_KIND ::=
18120 -- By_Entry | By_Protected_Procedure | By_Any | Optional
18122 -- "By_Any" and "Optional" are treated as synonyms in order to
18123 -- support Ada 2012 aspect Synchronization.
18125 when Pragma_Implemented => Implemented : declare
18126 Proc_Id : Entity_Id;
18127 Typ : Entity_Id;
18129 begin
18130 Ada_2012_Pragma;
18131 Check_Arg_Count (2);
18132 Check_No_Identifiers;
18133 Check_Arg_Is_Identifier (Arg1);
18134 Check_Arg_Is_Local_Name (Arg1);
18135 Check_Arg_Is_One_Of (Arg2,
18136 Name_By_Any,
18137 Name_By_Entry,
18138 Name_By_Protected_Procedure,
18139 Name_Optional);
18141 -- Extract the name of the local procedure
18143 Proc_Id := Entity (Get_Pragma_Arg (Arg1));
18145 -- Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
18146 -- primitive procedure of a synchronized tagged type.
18148 if Ekind (Proc_Id) = E_Procedure
18149 and then Is_Primitive (Proc_Id)
18150 and then Present (First_Formal (Proc_Id))
18151 then
18152 Typ := Etype (First_Formal (Proc_Id));
18154 if Is_Tagged_Type (Typ)
18155 and then
18157 -- Check for a protected, a synchronized or a task interface
18159 ((Is_Interface (Typ)
18160 and then Is_Synchronized_Interface (Typ))
18162 -- Check for a protected type or a task type that implements
18163 -- an interface.
18165 or else
18166 (Is_Concurrent_Record_Type (Typ)
18167 and then Present (Interfaces (Typ)))
18169 -- In analysis-only mode, examine original protected type
18171 or else
18172 (Nkind (Parent (Typ)) = N_Protected_Type_Declaration
18173 and then Present (Interface_List (Parent (Typ))))
18175 -- Check for a private record extension with keyword
18176 -- "synchronized".
18178 or else
18179 (Ekind (Typ) in E_Record_Type_With_Private
18180 | E_Record_Subtype_With_Private
18181 and then Synchronized_Present (Parent (Typ))))
18182 then
18183 null;
18184 else
18185 Error_Pragma_Arg
18186 ("controlling formal must be of synchronized tagged type",
18187 Arg1);
18188 end if;
18190 -- Ada 2012 (AI05-0030): Cannot apply the implementation_kind
18191 -- By_Protected_Procedure to the primitive procedure of a task
18192 -- interface.
18194 if Chars (Get_Pragma_Arg (Arg2)) = Name_By_Protected_Procedure
18195 and then Is_Interface (Typ)
18196 and then Is_Task_Interface (Typ)
18197 then
18198 Error_Pragma_Arg
18199 ("implementation kind By_Protected_Procedure cannot be "
18200 & "applied to a task interface primitive", Arg2);
18201 end if;
18203 -- Procedures declared inside a protected type must be accepted
18205 elsif Ekind (Proc_Id) = E_Procedure
18206 and then Is_Protected_Type (Scope (Proc_Id))
18207 then
18208 null;
18210 -- The first argument is not a primitive procedure
18212 else
18213 Error_Pragma_Arg
18214 ("pragma % must be applied to a primitive procedure", Arg1);
18215 end if;
18217 -- Ada 2012 (AI12-0279): Cannot apply the implementation_kind
18218 -- By_Protected_Procedure to a procedure that has aspect Yield
18220 if Chars (Get_Pragma_Arg (Arg2)) = Name_By_Protected_Procedure
18221 and then Has_Yield_Aspect (Proc_Id)
18222 then
18223 Error_Pragma_Arg
18224 ("implementation kind By_Protected_Procedure cannot be "
18225 & "applied to entities with aspect 'Yield", Arg2);
18226 end if;
18228 Record_Rep_Item (Proc_Id, N);
18229 end Implemented;
18231 ----------------------
18232 -- Implicit_Packing --
18233 ----------------------
18235 -- pragma Implicit_Packing;
18237 when Pragma_Implicit_Packing =>
18238 GNAT_Pragma;
18239 Check_Arg_Count (0);
18240 Implicit_Packing := True;
18242 ------------
18243 -- Import --
18244 ------------
18246 -- pragma Import (
18247 -- [Convention =>] convention_IDENTIFIER,
18248 -- [Entity =>] LOCAL_NAME
18249 -- [, [External_Name =>] static_string_EXPRESSION ]
18250 -- [, [Link_Name =>] static_string_EXPRESSION ]);
18252 when Pragma_Import =>
18253 Check_Ada_83_Warning;
18254 Check_Arg_Order
18255 ((Name_Convention,
18256 Name_Entity,
18257 Name_External_Name,
18258 Name_Link_Name));
18260 Check_At_Least_N_Arguments (2);
18261 Check_At_Most_N_Arguments (4);
18262 Process_Import_Or_Interface;
18264 ---------------------
18265 -- Import_Function --
18266 ---------------------
18268 -- pragma Import_Function (
18269 -- [Internal =>] LOCAL_NAME,
18270 -- [, [External =>] EXTERNAL_SYMBOL]
18271 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
18272 -- [, [Result_Type =>] SUBTYPE_MARK]
18273 -- [, [Mechanism =>] MECHANISM]
18274 -- [, [Result_Mechanism =>] MECHANISM_NAME]);
18276 -- EXTERNAL_SYMBOL ::=
18277 -- IDENTIFIER
18278 -- | static_string_EXPRESSION
18280 -- PARAMETER_TYPES ::=
18281 -- null
18282 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
18284 -- TYPE_DESIGNATOR ::=
18285 -- subtype_NAME
18286 -- | subtype_Name ' Access
18288 -- MECHANISM ::=
18289 -- MECHANISM_NAME
18290 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
18292 -- MECHANISM_ASSOCIATION ::=
18293 -- [formal_parameter_NAME =>] MECHANISM_NAME
18295 -- MECHANISM_NAME ::=
18296 -- Value
18297 -- | Reference
18299 when Pragma_Import_Function => Import_Function : declare
18300 Args : Args_List (1 .. 6);
18301 Names : constant Name_List (1 .. 6) := (
18302 Name_Internal,
18303 Name_External,
18304 Name_Parameter_Types,
18305 Name_Result_Type,
18306 Name_Mechanism,
18307 Name_Result_Mechanism);
18309 Internal : Node_Id renames Args (1);
18310 External : Node_Id renames Args (2);
18311 Parameter_Types : Node_Id renames Args (3);
18312 Result_Type : Node_Id renames Args (4);
18313 Mechanism : Node_Id renames Args (5);
18314 Result_Mechanism : Node_Id renames Args (6);
18316 begin
18317 GNAT_Pragma;
18318 Gather_Associations (Names, Args);
18319 Process_Extended_Import_Export_Subprogram_Pragma (
18320 Arg_Internal => Internal,
18321 Arg_External => External,
18322 Arg_Parameter_Types => Parameter_Types,
18323 Arg_Result_Type => Result_Type,
18324 Arg_Mechanism => Mechanism,
18325 Arg_Result_Mechanism => Result_Mechanism);
18326 end Import_Function;
18328 -------------------
18329 -- Import_Object --
18330 -------------------
18332 -- pragma Import_Object (
18333 -- [Internal =>] LOCAL_NAME
18334 -- [, [External =>] EXTERNAL_SYMBOL]
18335 -- [, [Size =>] EXTERNAL_SYMBOL]);
18337 -- EXTERNAL_SYMBOL ::=
18338 -- IDENTIFIER
18339 -- | static_string_EXPRESSION
18341 when Pragma_Import_Object => Import_Object : declare
18342 Args : Args_List (1 .. 3);
18343 Names : constant Name_List (1 .. 3) := (
18344 Name_Internal,
18345 Name_External,
18346 Name_Size);
18348 Internal : Node_Id renames Args (1);
18349 External : Node_Id renames Args (2);
18350 Size : Node_Id renames Args (3);
18352 begin
18353 GNAT_Pragma;
18354 Gather_Associations (Names, Args);
18355 Process_Extended_Import_Export_Object_Pragma (
18356 Arg_Internal => Internal,
18357 Arg_External => External,
18358 Arg_Size => Size);
18359 end Import_Object;
18361 ----------------------
18362 -- Import_Procedure --
18363 ----------------------
18365 -- pragma Import_Procedure (
18366 -- [Internal =>] LOCAL_NAME
18367 -- [, [External =>] EXTERNAL_SYMBOL]
18368 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
18369 -- [, [Mechanism =>] MECHANISM]);
18371 -- EXTERNAL_SYMBOL ::=
18372 -- IDENTIFIER
18373 -- | static_string_EXPRESSION
18375 -- PARAMETER_TYPES ::=
18376 -- null
18377 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
18379 -- TYPE_DESIGNATOR ::=
18380 -- subtype_NAME
18381 -- | subtype_Name ' Access
18383 -- MECHANISM ::=
18384 -- MECHANISM_NAME
18385 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
18387 -- MECHANISM_ASSOCIATION ::=
18388 -- [formal_parameter_NAME =>] MECHANISM_NAME
18390 -- MECHANISM_NAME ::=
18391 -- Value
18392 -- | Reference
18394 when Pragma_Import_Procedure => Import_Procedure : declare
18395 Args : Args_List (1 .. 4);
18396 Names : constant Name_List (1 .. 4) := (
18397 Name_Internal,
18398 Name_External,
18399 Name_Parameter_Types,
18400 Name_Mechanism);
18402 Internal : Node_Id renames Args (1);
18403 External : Node_Id renames Args (2);
18404 Parameter_Types : Node_Id renames Args (3);
18405 Mechanism : Node_Id renames Args (4);
18407 begin
18408 GNAT_Pragma;
18409 Gather_Associations (Names, Args);
18410 Process_Extended_Import_Export_Subprogram_Pragma (
18411 Arg_Internal => Internal,
18412 Arg_External => External,
18413 Arg_Parameter_Types => Parameter_Types,
18414 Arg_Mechanism => Mechanism);
18415 end Import_Procedure;
18417 -----------------------------
18418 -- Import_Valued_Procedure --
18419 -----------------------------
18421 -- pragma Import_Valued_Procedure (
18422 -- [Internal =>] LOCAL_NAME
18423 -- [, [External =>] EXTERNAL_SYMBOL]
18424 -- [, [Parameter_Types =>] (PARAMETER_TYPES)]
18425 -- [, [Mechanism =>] MECHANISM]);
18427 -- EXTERNAL_SYMBOL ::=
18428 -- IDENTIFIER
18429 -- | static_string_EXPRESSION
18431 -- PARAMETER_TYPES ::=
18432 -- null
18433 -- | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
18435 -- TYPE_DESIGNATOR ::=
18436 -- subtype_NAME
18437 -- | subtype_Name ' Access
18439 -- MECHANISM ::=
18440 -- MECHANISM_NAME
18441 -- | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
18443 -- MECHANISM_ASSOCIATION ::=
18444 -- [formal_parameter_NAME =>] MECHANISM_NAME
18446 -- MECHANISM_NAME ::=
18447 -- Value
18448 -- | Reference
18450 when Pragma_Import_Valued_Procedure =>
18451 Import_Valued_Procedure : declare
18452 Args : Args_List (1 .. 4);
18453 Names : constant Name_List (1 .. 4) := (
18454 Name_Internal,
18455 Name_External,
18456 Name_Parameter_Types,
18457 Name_Mechanism);
18459 Internal : Node_Id renames Args (1);
18460 External : Node_Id renames Args (2);
18461 Parameter_Types : Node_Id renames Args (3);
18462 Mechanism : Node_Id renames Args (4);
18464 begin
18465 GNAT_Pragma;
18466 Gather_Associations (Names, Args);
18467 Process_Extended_Import_Export_Subprogram_Pragma (
18468 Arg_Internal => Internal,
18469 Arg_External => External,
18470 Arg_Parameter_Types => Parameter_Types,
18471 Arg_Mechanism => Mechanism);
18472 end Import_Valued_Procedure;
18474 -----------------
18475 -- Independent --
18476 -----------------
18478 -- pragma Independent (LOCAL_NAME);
18480 when Pragma_Independent =>
18481 Process_Atomic_Independent_Shared_Volatile;
18483 ----------------------------
18484 -- Independent_Components --
18485 ----------------------------
18487 -- pragma Independent_Components (array_or_record_LOCAL_NAME);
18489 when Pragma_Independent_Components => Independent_Components : declare
18490 C : Node_Id;
18491 D : Node_Id;
18492 E_Id : Node_Id;
18493 E : Entity_Id;
18495 begin
18496 Check_Ada_83_Warning;
18497 Ada_2012_Pragma;
18498 Check_No_Identifiers;
18499 Check_Arg_Count (1);
18500 Check_Arg_Is_Local_Name (Arg1);
18501 E_Id := Get_Pragma_Arg (Arg1);
18503 if Etype (E_Id) = Any_Type then
18504 return;
18505 end if;
18507 E := Entity (E_Id);
18509 -- A record type with a self-referential component of anonymous
18510 -- access type is given an incomplete view in order to handle the
18511 -- self reference:
18513 -- type Rec is record
18514 -- Self : access Rec;
18515 -- end record;
18517 -- becomes
18519 -- type Rec;
18520 -- type Ptr is access Rec;
18521 -- type Rec is record
18522 -- Self : Ptr;
18523 -- end record;
18525 -- Since the incomplete view is now the initial view of the type,
18526 -- the argument of the pragma will reference the incomplete view,
18527 -- but this view is illegal according to the semantics of the
18528 -- pragma.
18530 -- Obtain the full view of an internally-generated incomplete type
18531 -- only. This way an attempt to associate the pragma with a source
18532 -- incomplete type is still caught.
18534 if Ekind (E) = E_Incomplete_Type
18535 and then not Comes_From_Source (E)
18536 and then Present (Full_View (E))
18537 then
18538 E := Full_View (E);
18539 end if;
18541 -- A pragma that applies to a Ghost entity becomes Ghost for the
18542 -- purposes of legality checks and removal of ignored Ghost code.
18544 Mark_Ghost_Pragma (N, E);
18546 -- Check duplicate before we chain ourselves
18548 Check_Duplicate_Pragma (E);
18550 -- Check appropriate entity
18552 if Rep_Item_Too_Early (E, N)
18553 or else
18554 Rep_Item_Too_Late (E, N)
18555 then
18556 return;
18557 end if;
18559 D := Declaration_Node (E);
18561 -- The flag is set on the base type, or on the object
18563 if Nkind (D) = N_Full_Type_Declaration
18564 and then (Is_Array_Type (E) or else Is_Record_Type (E))
18565 then
18566 Set_Has_Independent_Components (Base_Type (E));
18567 Record_Independence_Check (N, Base_Type (E));
18569 -- For record type, set all components independent
18571 if Is_Record_Type (E) then
18572 C := First_Component (E);
18573 while Present (C) loop
18574 Set_Is_Independent (C);
18575 Next_Component (C);
18576 end loop;
18577 end if;
18579 elsif (Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
18580 and then Nkind (D) = N_Object_Declaration
18581 and then Nkind (Object_Definition (D)) =
18582 N_Constrained_Array_Definition
18583 then
18584 Set_Has_Independent_Components (E);
18585 Record_Independence_Check (N, E);
18587 else
18588 Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
18589 end if;
18590 end Independent_Components;
18592 -----------------------
18593 -- Initial_Condition --
18594 -----------------------
18596 -- pragma Initial_Condition (boolean_EXPRESSION);
18598 -- Characteristics:
18600 -- * Analysis - The annotation undergoes initial checks to verify
18601 -- the legal placement and context. Secondary checks preanalyze the
18602 -- expression in:
18604 -- Analyze_Initial_Condition_In_Decl_Part
18606 -- * Expansion - The annotation is expanded during the expansion of
18607 -- the package body whose declaration is subject to the annotation
18608 -- as done in:
18610 -- Expand_Pragma_Initial_Condition
18612 -- * Template - The annotation utilizes the generic template of the
18613 -- related package declaration.
18615 -- * Globals - Capture of global references must occur after full
18616 -- analysis.
18618 -- * Instance - The annotation is instantiated automatically when
18619 -- the related generic package is instantiated.
18621 when Pragma_Initial_Condition => Initial_Condition : declare
18622 Pack_Decl : Node_Id;
18623 Pack_Id : Entity_Id;
18625 begin
18626 GNAT_Pragma;
18627 Check_No_Identifiers;
18628 Check_Arg_Count (1);
18630 Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
18632 if Nkind (Pack_Decl) not in
18633 N_Generic_Package_Declaration | N_Package_Declaration
18634 then
18635 Pragma_Misplaced;
18636 end if;
18638 Pack_Id := Defining_Entity (Pack_Decl);
18640 -- A pragma that applies to a Ghost entity becomes Ghost for the
18641 -- purposes of legality checks and removal of ignored Ghost code.
18643 Mark_Ghost_Pragma (N, Pack_Id);
18645 -- Chain the pragma on the contract for further processing by
18646 -- Analyze_Initial_Condition_In_Decl_Part.
18648 Add_Contract_Item (N, Pack_Id);
18650 -- The legality checks of pragmas Abstract_State, Initializes, and
18651 -- Initial_Condition are affected by the SPARK mode in effect. In
18652 -- addition, these three pragmas are subject to an inherent order:
18654 -- 1) Abstract_State
18655 -- 2) Initializes
18656 -- 3) Initial_Condition
18658 -- Analyze all these pragmas in the order outlined above
18660 Analyze_If_Present (Pragma_SPARK_Mode);
18661 Analyze_If_Present (Pragma_Abstract_State);
18662 Analyze_If_Present (Pragma_Initializes);
18663 end Initial_Condition;
18665 ------------------------
18666 -- Initialize_Scalars --
18667 ------------------------
18669 -- pragma Initialize_Scalars
18670 -- [ ( TYPE_VALUE_PAIR {, TYPE_VALUE_PAIR} ) ];
18672 -- TYPE_VALUE_PAIR ::=
18673 -- SCALAR_TYPE => static_EXPRESSION
18675 -- SCALAR_TYPE :=
18676 -- Short_Float
18677 -- | Float
18678 -- | Long_Float
18679 -- | Long_Long_Float
18680 -- | Signed_8
18681 -- | Signed_16
18682 -- | Signed_32
18683 -- | Signed_64
18684 -- | Signed_128
18685 -- | Unsigned_8
18686 -- | Unsigned_16
18687 -- | Unsigned_32
18688 -- | Unsigned_64
18689 -- | Unsigned_128
18691 when Pragma_Initialize_Scalars => Do_Initialize_Scalars : declare
18692 Seen : array (Scalar_Id) of Node_Id := (others => Empty);
18693 -- This collection holds the individual pairs which specify the
18694 -- invalid values of their respective scalar types.
18696 procedure Analyze_Float_Value
18697 (Scal_Typ : Float_Scalar_Id;
18698 Val_Expr : Node_Id);
18699 -- Analyze a type value pair associated with float type Scal_Typ
18700 -- and expression Val_Expr.
18702 procedure Analyze_Integer_Value
18703 (Scal_Typ : Integer_Scalar_Id;
18704 Val_Expr : Node_Id);
18705 -- Analyze a type value pair associated with integer type Scal_Typ
18706 -- and expression Val_Expr.
18708 procedure Analyze_Type_Value_Pair (Pair : Node_Id);
18709 -- Analyze type value pair Pair
18711 -------------------------
18712 -- Analyze_Float_Value --
18713 -------------------------
18715 procedure Analyze_Float_Value
18716 (Scal_Typ : Float_Scalar_Id;
18717 Val_Expr : Node_Id)
18719 begin
18720 Analyze_And_Resolve (Val_Expr, Any_Real);
18722 if Is_OK_Static_Expression (Val_Expr) then
18723 Set_Invalid_Scalar_Value (Scal_Typ, Expr_Value_R (Val_Expr));
18725 else
18726 Error_Msg_Name_1 := Scal_Typ;
18727 Error_Msg_N ("value for type % must be static", Val_Expr);
18728 end if;
18729 end Analyze_Float_Value;
18731 ---------------------------
18732 -- Analyze_Integer_Value --
18733 ---------------------------
18735 procedure Analyze_Integer_Value
18736 (Scal_Typ : Integer_Scalar_Id;
18737 Val_Expr : Node_Id)
18739 begin
18740 Analyze_And_Resolve (Val_Expr, Any_Integer);
18742 if (Scal_Typ = Name_Signed_128
18743 or else Scal_Typ = Name_Unsigned_128)
18744 and then Ttypes.System_Max_Integer_Size < 128
18745 then
18746 Error_Msg_Name_1 := Scal_Typ;
18747 Error_Msg_N ("value cannot be set for type %", Val_Expr);
18749 elsif Is_OK_Static_Expression (Val_Expr) then
18750 Set_Invalid_Scalar_Value (Scal_Typ, Expr_Value (Val_Expr));
18752 else
18753 Error_Msg_Name_1 := Scal_Typ;
18754 Error_Msg_N ("value for type % must be static", Val_Expr);
18755 end if;
18756 end Analyze_Integer_Value;
18758 -----------------------------
18759 -- Analyze_Type_Value_Pair --
18760 -----------------------------
18762 procedure Analyze_Type_Value_Pair (Pair : Node_Id) is
18763 Scal_Typ : constant Name_Id := Chars (Pair);
18764 Val_Expr : constant Node_Id := Expression (Pair);
18765 Prev_Pair : Node_Id;
18767 begin
18768 if Scal_Typ in Scalar_Id then
18769 Prev_Pair := Seen (Scal_Typ);
18771 -- Prevent multiple attempts to set a value for a scalar
18772 -- type.
18774 if Present (Prev_Pair) then
18775 Error_Msg_Name_1 := Scal_Typ;
18776 Error_Msg_N
18777 ("cannot specify multiple invalid values for type %",
18778 Pair);
18780 Error_Msg_Sloc := Sloc (Prev_Pair);
18781 Error_Msg_N ("previous value set #", Pair);
18783 -- Ignore the effects of the pair, but do not halt the
18784 -- analysis of the pragma altogether.
18786 return;
18788 -- Otherwise capture the first pair for this scalar type
18790 else
18791 Seen (Scal_Typ) := Pair;
18792 end if;
18794 if Scal_Typ in Float_Scalar_Id then
18795 Analyze_Float_Value (Scal_Typ, Val_Expr);
18797 else pragma Assert (Scal_Typ in Integer_Scalar_Id);
18798 Analyze_Integer_Value (Scal_Typ, Val_Expr);
18799 end if;
18801 -- Otherwise the scalar family is illegal
18803 else
18804 Error_Msg_Name_1 := Pname;
18805 Error_Msg_N
18806 ("argument of pragma % must denote valid scalar family",
18807 Pair);
18808 end if;
18809 end Analyze_Type_Value_Pair;
18811 -- Local variables
18813 Pairs : constant List_Id := Pragma_Argument_Associations (N);
18814 Pair : Node_Id;
18816 -- Start of processing for Do_Initialize_Scalars
18818 begin
18819 GNAT_Pragma;
18820 Check_Valid_Configuration_Pragma;
18821 Check_Restriction (No_Initialize_Scalars, N);
18823 -- Ignore the effects of the pragma when No_Initialize_Scalars is
18824 -- in effect.
18826 if Restriction_Active (No_Initialize_Scalars) then
18827 null;
18829 -- Initialize_Scalars creates false positives in CodePeer, and
18830 -- incorrect negative results in GNATprove mode, so ignore this
18831 -- pragma in these modes.
18833 elsif CodePeer_Mode or GNATprove_Mode then
18834 null;
18836 -- Otherwise analyze the pragma
18838 else
18839 if Present (Pairs) then
18841 -- Install Standard in order to provide access to primitive
18842 -- types in case the expressions contain attributes such as
18843 -- Integer'Last.
18845 Push_Scope (Standard_Standard);
18847 Pair := First (Pairs);
18848 while Present (Pair) loop
18849 Analyze_Type_Value_Pair (Pair);
18850 Next (Pair);
18851 end loop;
18853 -- Remove Standard
18855 Pop_Scope;
18856 end if;
18858 Init_Or_Norm_Scalars := True;
18859 Initialize_Scalars := True;
18860 end if;
18861 end Do_Initialize_Scalars;
18863 -----------------
18864 -- Initializes --
18865 -----------------
18867 -- pragma Initializes (INITIALIZATION_LIST);
18869 -- INITIALIZATION_LIST ::=
18870 -- null
18871 -- | (INITIALIZATION_ITEM {, INITIALIZATION_ITEM})
18873 -- INITIALIZATION_ITEM ::= name [=> INPUT_LIST]
18875 -- INPUT_LIST ::=
18876 -- null
18877 -- | INPUT
18878 -- | (INPUT {, INPUT})
18880 -- INPUT ::= name
18882 -- Characteristics:
18884 -- * Analysis - The annotation undergoes initial checks to verify
18885 -- the legal placement and context. Secondary checks preanalyze the
18886 -- expression in:
18888 -- Analyze_Initializes_In_Decl_Part
18890 -- * Expansion - None.
18892 -- * Template - The annotation utilizes the generic template of the
18893 -- related package declaration.
18895 -- * Globals - Capture of global references must occur after full
18896 -- analysis.
18898 -- * Instance - The annotation is instantiated automatically when
18899 -- the related generic package is instantiated.
18901 when Pragma_Initializes => Initializes : declare
18902 Pack_Decl : Node_Id;
18903 Pack_Id : Entity_Id;
18905 begin
18906 GNAT_Pragma;
18907 Check_No_Identifiers;
18908 Check_Arg_Count (1);
18910 Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
18912 if Nkind (Pack_Decl) not in
18913 N_Generic_Package_Declaration | N_Package_Declaration
18914 then
18915 Pragma_Misplaced;
18916 end if;
18918 Pack_Id := Defining_Entity (Pack_Decl);
18920 -- A pragma that applies to a Ghost entity becomes Ghost for the
18921 -- purposes of legality checks and removal of ignored Ghost code.
18923 Mark_Ghost_Pragma (N, Pack_Id);
18924 Ensure_Aggregate_Form (Get_Argument (N, Pack_Id));
18926 -- Chain the pragma on the contract for further processing by
18927 -- Analyze_Initializes_In_Decl_Part.
18929 Add_Contract_Item (N, Pack_Id);
18931 -- The legality checks of pragmas Abstract_State, Initializes, and
18932 -- Initial_Condition are affected by the SPARK mode in effect. In
18933 -- addition, these three pragmas are subject to an inherent order:
18935 -- 1) Abstract_State
18936 -- 2) Initializes
18937 -- 3) Initial_Condition
18939 -- Analyze all these pragmas in the order outlined above
18941 Analyze_If_Present (Pragma_SPARK_Mode);
18942 Analyze_If_Present (Pragma_Abstract_State);
18943 Analyze_If_Present (Pragma_Initial_Condition);
18944 end Initializes;
18946 ------------
18947 -- Inline --
18948 ------------
18950 -- pragma Inline ( NAME {, NAME} );
18952 when Pragma_Inline =>
18954 -- Pragma always active unless in GNATprove mode. It is disabled
18955 -- in GNATprove mode because frontend inlining is applied
18956 -- independently of pragmas Inline and Inline_Always for
18957 -- formal verification, see Can_Be_Inlined_In_GNATprove_Mode
18958 -- in inline.ads.
18960 if not GNATprove_Mode then
18962 -- Inline status is Enabled if option -gnatn is specified.
18963 -- However this status determines only the value of the
18964 -- Is_Inlined flag on the subprogram and does not prevent
18965 -- the pragma itself from being recorded for later use,
18966 -- in particular for a later modification of Is_Inlined
18967 -- independently of the -gnatn option.
18969 -- In other words, if -gnatn is specified for a unit, then
18970 -- all Inline pragmas processed for the compilation of this
18971 -- unit, including those in the spec of other units, are
18972 -- activated, so subprograms will be inlined across units.
18974 -- If -gnatn is not specified, no Inline pragma is activated
18975 -- here, which means that subprograms will not be inlined
18976 -- across units. The Is_Inlined flag will nevertheless be
18977 -- set later when bodies are analyzed, so subprograms will
18978 -- be inlined within the unit.
18980 if Inline_Active then
18981 Process_Inline (Enabled);
18982 else
18983 Process_Inline (Disabled);
18984 end if;
18985 end if;
18987 -------------------
18988 -- Inline_Always --
18989 -------------------
18991 -- pragma Inline_Always ( NAME {, NAME} );
18993 when Pragma_Inline_Always =>
18994 GNAT_Pragma;
18996 -- Pragma always active unless in CodePeer mode or GNATprove
18997 -- mode. It is disabled in CodePeer mode because inlining is
18998 -- not helpful, and enabling it caused walk order issues. It
18999 -- is disabled in GNATprove mode because frontend inlining is
19000 -- applied independently of pragmas Inline and Inline_Always for
19001 -- formal verification, see Can_Be_Inlined_In_GNATprove_Mode in
19002 -- inline.ads.
19004 if not CodePeer_Mode and not GNATprove_Mode then
19005 Process_Inline (Enabled);
19006 end if;
19008 --------------------
19009 -- Inline_Generic --
19010 --------------------
19012 -- pragma Inline_Generic (NAME {, NAME});
19014 when Pragma_Inline_Generic =>
19015 GNAT_Pragma;
19016 Process_Generic_List;
19018 ----------------------
19019 -- Inspection_Point --
19020 ----------------------
19022 -- pragma Inspection_Point [(object_NAME {, object_NAME})];
19024 when Pragma_Inspection_Point => Inspection_Point : declare
19025 Arg : Node_Id;
19026 Exp : Node_Id;
19028 begin
19031 if Arg_Count > 0 then
19032 Arg := Arg1;
19033 loop
19034 Exp := Get_Pragma_Arg (Arg);
19035 Analyze (Exp);
19037 if not Is_Entity_Name (Exp)
19038 or else not Is_Object (Entity (Exp))
19039 then
19040 Error_Pragma_Arg ("object name required", Arg);
19041 end if;
19043 Next (Arg);
19044 exit when No (Arg);
19045 end loop;
19046 end if;
19047 end Inspection_Point;
19049 ---------------
19050 -- Interface --
19051 ---------------
19053 -- pragma Interface (
19054 -- [ Convention =>] convention_IDENTIFIER,
19055 -- [ Entity =>] LOCAL_NAME
19056 -- [, [External_Name =>] static_string_EXPRESSION ]
19057 -- [, [Link_Name =>] static_string_EXPRESSION ]);
19059 when Pragma_Interface =>
19060 GNAT_Pragma;
19061 Check_Arg_Order
19062 ((Name_Convention,
19063 Name_Entity,
19064 Name_External_Name,
19065 Name_Link_Name));
19066 Check_At_Least_N_Arguments (2);
19067 Check_At_Most_N_Arguments (4);
19068 Process_Import_Or_Interface;
19070 -- In Ada 2005, the permission to use Interface (a reserved word)
19071 -- as a pragma name is considered an obsolescent feature, and this
19072 -- pragma was already obsolescent in Ada 95.
19074 if Ada_Version >= Ada_95 then
19075 Check_Restriction
19076 (No_Obsolescent_Features, Pragma_Identifier (N));
19078 if Warn_On_Obsolescent_Feature then
19079 Error_Msg_N
19080 ("pragma Interface is an obsolescent feature?j?", N);
19081 Error_Msg_N
19082 ("|use pragma Import instead?j?", N);
19083 end if;
19084 end if;
19086 --------------------
19087 -- Interface_Name --
19088 --------------------
19090 -- pragma Interface_Name (
19091 -- [ Entity =>] LOCAL_NAME
19092 -- [,[External_Name =>] static_string_EXPRESSION ]
19093 -- [,[Link_Name =>] static_string_EXPRESSION ]);
19095 when Pragma_Interface_Name => Interface_Name : declare
19096 Id : Node_Id;
19097 Def_Id : Entity_Id;
19098 Hom_Id : Entity_Id;
19099 Found : Boolean;
19101 begin
19102 GNAT_Pragma;
19103 Check_Arg_Order
19104 ((Name_Entity, Name_External_Name, Name_Link_Name));
19105 Check_At_Least_N_Arguments (2);
19106 Check_At_Most_N_Arguments (3);
19107 Id := Get_Pragma_Arg (Arg1);
19108 Analyze (Id);
19110 -- This is obsolete from Ada 95 on, but it is an implementation
19111 -- defined pragma, so we do not consider that it violates the
19112 -- restriction (No_Obsolescent_Features).
19114 if Ada_Version >= Ada_95 then
19115 if Warn_On_Obsolescent_Feature then
19116 Error_Msg_N
19117 ("pragma Interface_Name is an obsolescent feature?j?", N);
19118 Error_Msg_N
19119 ("|use pragma Import instead?j?", N);
19120 end if;
19121 end if;
19123 if not Is_Entity_Name (Id) then
19124 Error_Pragma_Arg
19125 ("first argument for pragma% must be entity name", Arg1);
19126 elsif Etype (Id) = Any_Type then
19127 return;
19128 else
19129 Def_Id := Entity (Id);
19130 end if;
19132 -- Special DEC-compatible processing for the object case, forces
19133 -- object to be imported.
19135 if Ekind (Def_Id) = E_Variable then
19136 Kill_Size_Check_Code (Def_Id);
19137 Note_Possible_Modification (Id, Sure => False);
19139 -- Initialization is not allowed for imported variable
19141 if Present (Expression (Parent (Def_Id)))
19142 and then Comes_From_Source (Expression (Parent (Def_Id)))
19143 then
19144 Error_Msg_Sloc := Sloc (Def_Id);
19145 Error_Pragma_Arg
19146 ("no initialization allowed for declaration of& #",
19147 Arg2);
19149 else
19150 -- For compatibility, support VADS usage of providing both
19151 -- pragmas Interface and Interface_Name to obtain the effect
19152 -- of a single Import pragma.
19154 if Is_Imported (Def_Id)
19155 and then Present (First_Rep_Item (Def_Id))
19156 and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
19157 and then Pragma_Name (First_Rep_Item (Def_Id)) =
19158 Name_Interface
19159 then
19160 null;
19161 else
19162 Set_Imported (Def_Id);
19163 end if;
19165 Set_Is_Public (Def_Id);
19166 Process_Interface_Name (Def_Id, Arg2, Arg3, N);
19167 end if;
19169 -- Otherwise must be subprogram
19171 elsif not Is_Subprogram (Def_Id) then
19172 Error_Pragma_Arg
19173 ("argument of pragma% is not subprogram", Arg1);
19175 else
19176 Check_At_Most_N_Arguments (3);
19177 Hom_Id := Def_Id;
19178 Found := False;
19180 -- Loop through homonyms
19182 loop
19183 Def_Id := Get_Base_Subprogram (Hom_Id);
19185 if Is_Imported (Def_Id) then
19186 Process_Interface_Name (Def_Id, Arg2, Arg3, N);
19187 Found := True;
19188 end if;
19190 exit when From_Aspect_Specification (N);
19191 Hom_Id := Homonym (Hom_Id);
19193 exit when No (Hom_Id)
19194 or else Scope (Hom_Id) /= Current_Scope;
19195 end loop;
19197 if not Found then
19198 Error_Pragma_Arg
19199 ("argument of pragma% is not imported subprogram",
19200 Arg1);
19201 end if;
19202 end if;
19203 end Interface_Name;
19205 -----------------------
19206 -- Interrupt_Handler --
19207 -----------------------
19209 -- pragma Interrupt_Handler (handler_NAME);
19211 when Pragma_Interrupt_Handler =>
19212 Check_Ada_83_Warning;
19213 Check_Arg_Count (1);
19214 Check_No_Identifiers;
19216 if No_Run_Time_Mode then
19217 Error_Msg_CRT ("Interrupt_Handler pragma", N);
19218 else
19219 Check_Interrupt_Or_Attach_Handler;
19220 Process_Interrupt_Or_Attach_Handler;
19221 end if;
19223 ------------------------
19224 -- Interrupt_Priority --
19225 ------------------------
19227 -- pragma Interrupt_Priority [(EXPRESSION)];
19229 when Pragma_Interrupt_Priority => Interrupt_Priority : declare
19230 P : constant Node_Id := Parent (N);
19231 Arg : Node_Id;
19232 Ent : Entity_Id;
19234 begin
19235 Check_Ada_83_Warning;
19237 if Arg_Count /= 0 then
19238 Arg := Get_Pragma_Arg (Arg1);
19239 Check_Arg_Count (1);
19240 Check_No_Identifiers;
19242 -- The expression must be analyzed in the special manner
19243 -- described in "Handling of Default and Per-Object
19244 -- Expressions" in sem.ads.
19246 Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
19247 end if;
19249 if Nkind (P) not in N_Task_Definition | N_Protected_Definition then
19250 Pragma_Misplaced;
19252 else
19253 Ent := Defining_Identifier (Parent (P));
19255 -- Check duplicate pragma before we chain the pragma in the Rep
19256 -- Item chain of Ent.
19258 Check_Duplicate_Pragma (Ent);
19259 Record_Rep_Item (Ent, N);
19261 -- Check the No_Task_At_Interrupt_Priority restriction
19263 if Nkind (P) = N_Task_Definition then
19264 Check_Restriction (No_Task_At_Interrupt_Priority, N);
19265 end if;
19266 end if;
19267 end Interrupt_Priority;
19269 ---------------------
19270 -- Interrupt_State --
19271 ---------------------
19273 -- pragma Interrupt_State (
19274 -- [Name =>] INTERRUPT_ID,
19275 -- [State =>] INTERRUPT_STATE);
19277 -- INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
19278 -- INTERRUPT_STATE => System | Runtime | User
19280 -- Note: if the interrupt id is given as an identifier, then it must
19281 -- be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
19282 -- given as a static integer expression which must be in the range of
19283 -- Ada.Interrupts.Interrupt_ID.
19285 when Pragma_Interrupt_State => Interrupt_State : declare
19286 Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
19287 -- This is the entity Ada.Interrupts.Interrupt_ID;
19289 State_Type : Character;
19290 -- Set to 's'/'r'/'u' for System/Runtime/User
19292 IST_Num : Pos;
19293 -- Index to entry in Interrupt_States table
19295 Int_Val : Uint;
19296 -- Value of interrupt
19298 Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
19299 -- The first argument to the pragma
19301 Int_Ent : Entity_Id;
19302 -- Interrupt entity in Ada.Interrupts.Names
19304 begin
19305 GNAT_Pragma;
19306 Check_Arg_Order ((Name_Name, Name_State));
19307 Check_Arg_Count (2);
19309 Check_Optional_Identifier (Arg1, Name_Name);
19310 Check_Optional_Identifier (Arg2, Name_State);
19311 Check_Arg_Is_Identifier (Arg2);
19313 -- First argument is identifier
19315 if Nkind (Arg1X) = N_Identifier then
19317 -- Search list of names in Ada.Interrupts.Names
19319 Int_Ent := First_Entity (RTE (RE_Names));
19320 loop
19321 if No (Int_Ent) then
19322 Error_Pragma_Arg ("invalid interrupt name", Arg1);
19324 elsif Chars (Int_Ent) = Chars (Arg1X) then
19325 Int_Val := Expr_Value (Constant_Value (Int_Ent));
19326 exit;
19327 end if;
19329 Next_Entity (Int_Ent);
19330 end loop;
19332 -- First argument is not an identifier, so it must be a static
19333 -- expression of type Ada.Interrupts.Interrupt_ID.
19335 else
19336 Check_Arg_Is_OK_Static_Expression (Arg1, Any_Integer);
19337 Int_Val := Expr_Value (Arg1X);
19339 if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
19340 or else
19341 Int_Val > Expr_Value (Type_High_Bound (Int_Id))
19342 then
19343 Error_Pragma_Arg
19344 ("value not in range of type "
19345 & """Ada.Interrupts.Interrupt_'I'D""", Arg1);
19346 end if;
19347 end if;
19349 -- Check OK state
19351 case Chars (Get_Pragma_Arg (Arg2)) is
19352 when Name_Runtime => State_Type := 'r';
19353 when Name_System => State_Type := 's';
19354 when Name_User => State_Type := 'u';
19356 when others =>
19357 Error_Pragma_Arg ("invalid interrupt state", Arg2);
19358 end case;
19360 -- Check if entry is already stored
19362 IST_Num := Interrupt_States.First;
19363 loop
19364 -- If entry not found, add it
19366 if IST_Num > Interrupt_States.Last then
19367 Interrupt_States.Append
19368 ((Interrupt_Number => UI_To_Int (Int_Val),
19369 Interrupt_State => State_Type,
19370 Pragma_Loc => Loc));
19371 exit;
19373 -- Case of entry for the same entry
19375 elsif Int_Val = Interrupt_States.Table (IST_Num).
19376 Interrupt_Number
19377 then
19378 -- If state matches, done, no need to make redundant entry
19380 exit when
19381 State_Type = Interrupt_States.Table (IST_Num).
19382 Interrupt_State;
19384 -- Otherwise if state does not match, error
19386 Error_Msg_Sloc :=
19387 Interrupt_States.Table (IST_Num).Pragma_Loc;
19388 Error_Pragma_Arg
19389 ("state conflicts with that given #", Arg2);
19390 end if;
19392 IST_Num := IST_Num + 1;
19393 end loop;
19394 end Interrupt_State;
19396 ---------------
19397 -- Invariant --
19398 ---------------
19400 -- pragma Invariant
19401 -- ([Entity =>] type_LOCAL_NAME,
19402 -- [Check =>] EXPRESSION
19403 -- [,[Message =>] String_Expression]);
19405 when Pragma_Invariant => Invariant : declare
19406 Discard : Boolean;
19407 Typ : Entity_Id;
19408 Typ_Arg : Node_Id;
19410 begin
19411 GNAT_Pragma;
19412 Check_At_Least_N_Arguments (2);
19413 Check_At_Most_N_Arguments (3);
19414 Check_Optional_Identifier (Arg1, Name_Entity);
19415 Check_Optional_Identifier (Arg2, Name_Check);
19417 if Arg_Count = 3 then
19418 Check_Optional_Identifier (Arg3, Name_Message);
19419 Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
19420 end if;
19422 Check_Arg_Is_Local_Name (Arg1);
19424 Typ_Arg := Get_Pragma_Arg (Arg1);
19425 Find_Type (Typ_Arg);
19426 Typ := Entity (Typ_Arg);
19428 -- Nothing to do of the related type is erroneous in some way
19430 if Typ = Any_Type then
19431 return;
19433 -- AI12-0041: Invariants are allowed in interface types
19435 elsif Is_Interface (Typ) then
19436 null;
19438 -- An invariant must apply to a private type, or appear in the
19439 -- private part of a package spec and apply to a completion.
19440 -- a class-wide invariant can only appear on a private declaration
19441 -- or private extension, not a completion.
19443 -- A [class-wide] invariant may be associated a [limited] private
19444 -- type or a private extension.
19446 elsif Ekind (Typ) in E_Limited_Private_Type
19447 | E_Private_Type
19448 | E_Record_Type_With_Private
19449 then
19450 null;
19452 -- A non-class-wide invariant may be associated with the full view
19453 -- of a [limited] private type or a private extension.
19455 elsif Has_Private_Declaration (Typ)
19456 and then not Class_Present (N)
19457 then
19458 null;
19460 -- A class-wide invariant may appear on the partial view only
19462 elsif Class_Present (N) then
19463 Error_Pragma_Arg
19464 ("pragma % only allowed for private type", Arg1);
19466 -- A regular invariant may appear on both views
19468 else
19469 Error_Pragma_Arg
19470 ("pragma % only allowed for private type or corresponding "
19471 & "full view", Arg1);
19472 end if;
19474 -- An invariant associated with an abstract type (this includes
19475 -- interfaces) must be class-wide.
19477 if Is_Abstract_Type (Typ) and then not Class_Present (N) then
19478 Error_Pragma_Arg
19479 ("pragma % not allowed for abstract type", Arg1);
19480 end if;
19482 -- A pragma that applies to a Ghost entity becomes Ghost for the
19483 -- purposes of legality checks and removal of ignored Ghost code.
19485 Mark_Ghost_Pragma (N, Typ);
19487 -- The pragma defines a type-specific invariant, the type is said
19488 -- to have invariants of its "own".
19490 Set_Has_Own_Invariants (Base_Type (Typ));
19492 -- If the invariant is class-wide, then it can be inherited by
19493 -- derived or interface implementing types. The type is said to
19494 -- have "inheritable" invariants.
19496 if Class_Present (N) then
19497 Set_Has_Inheritable_Invariants (Typ);
19498 end if;
19500 -- Chain the pragma on to the rep item chain, for processing when
19501 -- the type is frozen.
19503 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
19505 -- Create the declaration of the invariant procedure that will
19506 -- verify the invariant at run time. Interfaces are treated as the
19507 -- partial view of a private type in order to achieve uniformity
19508 -- with the general case. As a result, an interface receives only
19509 -- a "partial" invariant procedure, which is never called.
19511 Build_Invariant_Procedure_Declaration
19512 (Typ => Typ,
19513 Partial_Invariant => Is_Interface (Typ));
19514 end Invariant;
19516 ----------------
19517 -- Keep_Names --
19518 ----------------
19520 -- pragma Keep_Names ([On => ] LOCAL_NAME);
19522 when Pragma_Keep_Names => Keep_Names : declare
19523 Arg : Node_Id;
19525 begin
19526 GNAT_Pragma;
19527 Check_Arg_Count (1);
19528 Check_Optional_Identifier (Arg1, Name_On);
19529 Check_Arg_Is_Local_Name (Arg1);
19531 Arg := Get_Pragma_Arg (Arg1);
19532 Analyze (Arg);
19534 if Etype (Arg) = Any_Type then
19535 return;
19536 end if;
19538 if not Is_Entity_Name (Arg)
19539 or else Ekind (Entity (Arg)) /= E_Enumeration_Type
19540 then
19541 Error_Pragma_Arg
19542 ("pragma% requires a local enumeration type", Arg1);
19543 end if;
19545 Set_Discard_Names (Entity (Arg), False);
19546 end Keep_Names;
19548 -------------
19549 -- License --
19550 -------------
19552 -- pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
19554 when Pragma_License =>
19555 GNAT_Pragma;
19557 -- Do not analyze pragma any further in CodePeer mode, to avoid
19558 -- extraneous errors in this implementation-dependent pragma,
19559 -- which has a different profile on other compilers.
19561 if CodePeer_Mode then
19562 return;
19563 end if;
19565 Check_Arg_Count (1);
19566 Check_No_Identifiers;
19567 Check_Valid_Configuration_Pragma;
19568 Check_Arg_Is_Identifier (Arg1);
19570 declare
19571 Sind : constant Source_File_Index :=
19572 Source_Index (Current_Sem_Unit);
19574 begin
19575 case Chars (Get_Pragma_Arg (Arg1)) is
19576 when Name_GPL =>
19577 Set_License (Sind, GPL);
19579 when Name_Modified_GPL =>
19580 Set_License (Sind, Modified_GPL);
19582 when Name_Restricted =>
19583 Set_License (Sind, Restricted);
19585 when Name_Unrestricted =>
19586 Set_License (Sind, Unrestricted);
19588 when others =>
19589 Error_Pragma_Arg ("invalid license name", Arg1);
19590 end case;
19591 end;
19593 ---------------
19594 -- Link_With --
19595 ---------------
19597 -- pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
19599 when Pragma_Link_With => Link_With : declare
19600 Arg : Node_Id;
19602 begin
19603 GNAT_Pragma;
19605 if Operating_Mode = Generate_Code
19606 and then In_Extended_Main_Source_Unit (N)
19607 then
19608 Check_At_Least_N_Arguments (1);
19609 Check_No_Identifiers;
19610 Check_Is_In_Decl_Part_Or_Package_Spec;
19611 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
19612 Start_String;
19614 Arg := Arg1;
19615 while Present (Arg) loop
19616 Check_Arg_Is_OK_Static_Expression (Arg, Standard_String);
19618 -- Store argument, converting sequences of spaces to a
19619 -- single null character (this is one of the differences
19620 -- in processing between Link_With and Linker_Options).
19622 Arg_Store : declare
19623 C : constant Char_Code := Get_Char_Code (' ');
19624 S : constant String_Id :=
19625 Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
19626 L : constant Nat := String_Length (S);
19627 F : Nat := 1;
19629 procedure Skip_Spaces;
19630 -- Advance F past any spaces
19632 -----------------
19633 -- Skip_Spaces --
19634 -----------------
19636 procedure Skip_Spaces is
19637 begin
19638 while F <= L and then Get_String_Char (S, F) = C loop
19639 F := F + 1;
19640 end loop;
19641 end Skip_Spaces;
19643 -- Start of processing for Arg_Store
19645 begin
19646 Skip_Spaces; -- skip leading spaces
19648 -- Loop through characters, changing any embedded
19649 -- sequence of spaces to a single null character (this
19650 -- is how Link_With/Linker_Options differ)
19652 while F <= L loop
19653 if Get_String_Char (S, F) = C then
19654 Skip_Spaces;
19655 exit when F > L;
19656 Store_String_Char (ASCII.NUL);
19658 else
19659 Store_String_Char (Get_String_Char (S, F));
19660 F := F + 1;
19661 end if;
19662 end loop;
19663 end Arg_Store;
19665 Arg := Next (Arg);
19667 if Present (Arg) then
19668 Store_String_Char (ASCII.NUL);
19669 end if;
19670 end loop;
19672 Store_Linker_Option_String (End_String);
19673 end if;
19674 end Link_With;
19676 ------------------
19677 -- Linker_Alias --
19678 ------------------
19680 -- pragma Linker_Alias (
19681 -- [Entity =>] LOCAL_NAME
19682 -- [Target =>] static_string_EXPRESSION);
19684 when Pragma_Linker_Alias =>
19685 GNAT_Pragma;
19686 Check_Arg_Order ((Name_Entity, Name_Target));
19687 Check_Arg_Count (2);
19688 Check_Optional_Identifier (Arg1, Name_Entity);
19689 Check_Optional_Identifier (Arg2, Name_Target);
19690 Check_Arg_Is_Library_Level_Local_Name (Arg1);
19691 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
19693 -- The only processing required is to link this item on to the
19694 -- list of rep items for the given entity. This is accomplished
19695 -- by the call to Rep_Item_Too_Late (when no error is detected
19696 -- and False is returned).
19698 if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
19699 return;
19700 else
19701 Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
19702 end if;
19704 ------------------------
19705 -- Linker_Constructor --
19706 ------------------------
19708 -- pragma Linker_Constructor (procedure_LOCAL_NAME);
19710 -- Code is shared with Linker_Destructor
19712 -----------------------
19713 -- Linker_Destructor --
19714 -----------------------
19716 -- pragma Linker_Destructor (procedure_LOCAL_NAME);
19718 when Pragma_Linker_Constructor
19719 | Pragma_Linker_Destructor
19721 Linker_Constructor : declare
19722 Arg1_X : Node_Id;
19723 Proc : Entity_Id;
19725 begin
19726 GNAT_Pragma;
19727 Check_Arg_Count (1);
19728 Check_No_Identifiers;
19729 Check_Arg_Is_Local_Name (Arg1);
19730 Arg1_X := Get_Pragma_Arg (Arg1);
19731 Analyze (Arg1_X);
19732 Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
19734 if not Is_Library_Level_Entity (Proc) then
19735 Error_Pragma_Arg
19736 ("argument for pragma% must be library level entity", Arg1);
19737 end if;
19739 -- The only processing required is to link this item on to the
19740 -- list of rep items for the given entity. This is accomplished
19741 -- by the call to Rep_Item_Too_Late (when no error is detected
19742 -- and False is returned).
19744 if Rep_Item_Too_Late (Proc, N) then
19745 return;
19746 else
19747 Set_Has_Gigi_Rep_Item (Proc);
19748 end if;
19749 end Linker_Constructor;
19751 --------------------
19752 -- Linker_Options --
19753 --------------------
19755 -- pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
19757 when Pragma_Linker_Options => Linker_Options : declare
19758 Arg : Node_Id;
19760 begin
19761 Check_Ada_83_Warning;
19762 Check_No_Identifiers;
19763 Check_Arg_Count (1);
19764 Check_Is_In_Decl_Part_Or_Package_Spec;
19765 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
19766 Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
19768 Arg := Arg2;
19769 while Present (Arg) loop
19770 Check_Arg_Is_OK_Static_Expression (Arg, Standard_String);
19771 Store_String_Char (ASCII.NUL);
19772 Store_String_Chars
19773 (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
19774 Arg := Next (Arg);
19775 end loop;
19777 if Operating_Mode = Generate_Code
19778 and then In_Extended_Main_Source_Unit (N)
19779 then
19780 Store_Linker_Option_String (End_String);
19781 end if;
19782 end Linker_Options;
19784 --------------------
19785 -- Linker_Section --
19786 --------------------
19788 -- pragma Linker_Section (
19789 -- [Entity =>] LOCAL_NAME
19790 -- [Section =>] static_string_EXPRESSION);
19792 when Pragma_Linker_Section => Linker_Section : declare
19793 Arg : Node_Id;
19794 Ent : Entity_Id;
19795 LPE : Node_Id;
19797 Ghost_Error_Posted : Boolean := False;
19798 -- Flag set when an error concerning the illegal mix of Ghost and
19799 -- non-Ghost subprograms is emitted.
19801 Ghost_Id : Entity_Id := Empty;
19802 -- The entity of the first Ghost subprogram encountered while
19803 -- processing the arguments of the pragma.
19805 begin
19806 GNAT_Pragma;
19807 Check_Arg_Order ((Name_Entity, Name_Section));
19808 Check_Arg_Count (2);
19809 Check_Optional_Identifier (Arg1, Name_Entity);
19810 Check_Optional_Identifier (Arg2, Name_Section);
19811 Check_Arg_Is_Library_Level_Local_Name (Arg1);
19812 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
19814 -- Check kind of entity
19816 Arg := Get_Pragma_Arg (Arg1);
19817 Ent := Entity (Arg);
19819 case Ekind (Ent) is
19821 -- Objects (constants and variables) and types. For these cases
19822 -- all we need to do is to set the Linker_Section_pragma field,
19823 -- checking that we do not have a duplicate.
19825 when Type_Kind
19826 | E_Constant
19827 | E_Variable
19829 LPE := Linker_Section_Pragma (Ent);
19831 if Present (LPE) then
19832 Error_Msg_Sloc := Sloc (LPE);
19833 Error_Msg_NE
19834 ("Linker_Section already specified for &#", Arg1, Ent);
19835 end if;
19837 Set_Linker_Section_Pragma (Ent, N);
19839 -- A pragma that applies to a Ghost entity becomes Ghost for
19840 -- the purposes of legality checks and removal of ignored
19841 -- Ghost code.
19843 Mark_Ghost_Pragma (N, Ent);
19845 -- Subprograms
19847 when Subprogram_Kind =>
19849 -- Aspect case, entity already set
19851 if From_Aspect_Specification (N) then
19852 Set_Linker_Section_Pragma
19853 (Entity (Corresponding_Aspect (N)), N);
19855 -- Propagate it to its ultimate aliased entity to
19856 -- facilitate the backend processing this attribute
19857 -- in instantiations of generic subprograms.
19859 if Present (Alias (Entity (Corresponding_Aspect (N))))
19860 then
19861 Set_Linker_Section_Pragma
19862 (Ultimate_Alias
19863 (Entity (Corresponding_Aspect (N))), N);
19864 end if;
19866 -- Pragma case, we must climb the homonym chain, but skip
19867 -- any for which the linker section is already set.
19869 else
19870 loop
19871 if No (Linker_Section_Pragma (Ent)) then
19872 Set_Linker_Section_Pragma (Ent, N);
19874 -- Propagate it to its ultimate aliased entity to
19875 -- facilitate the backend processing this attribute
19876 -- in instantiations of generic subprograms.
19878 if Present (Alias (Ent)) then
19879 Set_Linker_Section_Pragma
19880 (Ultimate_Alias (Ent), N);
19881 end if;
19883 -- A pragma that applies to a Ghost entity becomes
19884 -- Ghost for the purposes of legality checks and
19885 -- removal of ignored Ghost code.
19887 Mark_Ghost_Pragma (N, Ent);
19889 -- Capture the entity of the first Ghost subprogram
19890 -- being processed for error detection purposes.
19892 if Is_Ghost_Entity (Ent) then
19893 if No (Ghost_Id) then
19894 Ghost_Id := Ent;
19895 end if;
19897 -- Otherwise the subprogram is non-Ghost. It is
19898 -- illegal to mix references to Ghost and non-Ghost
19899 -- entities (SPARK RM 6.9).
19901 elsif Present (Ghost_Id)
19902 and then not Ghost_Error_Posted
19903 then
19904 Ghost_Error_Posted := True;
19906 Error_Msg_Name_1 := Pname;
19907 Error_Msg_N
19908 ("pragma % cannot mention ghost and "
19909 & "non-ghost subprograms", N);
19911 Error_Msg_Sloc := Sloc (Ghost_Id);
19912 Error_Msg_NE
19913 ("\& # declared as ghost", N, Ghost_Id);
19915 Error_Msg_Sloc := Sloc (Ent);
19916 Error_Msg_NE
19917 ("\& # declared as non-ghost", N, Ent);
19918 end if;
19919 end if;
19921 Ent := Homonym (Ent);
19922 exit when No (Ent)
19923 or else Scope (Ent) /= Current_Scope;
19924 end loop;
19925 end if;
19927 -- All other cases are illegal
19929 when others =>
19930 Error_Pragma_Arg
19931 ("pragma% applies only to objects, subprograms, and types",
19932 Arg1);
19933 end case;
19934 end Linker_Section;
19936 ----------
19937 -- List --
19938 ----------
19940 -- pragma List (On | Off)
19942 -- There is nothing to do here, since we did all the processing for
19943 -- this pragma in Par.Prag (so that it works properly even in syntax
19944 -- only mode).
19946 when Pragma_List =>
19947 null;
19949 ---------------
19950 -- Lock_Free --
19951 ---------------
19953 -- pragma Lock_Free [(Boolean_EXPRESSION)];
19955 when Pragma_Lock_Free => Lock_Free : declare
19956 P : constant Node_Id := Parent (N);
19957 Arg : Node_Id;
19958 Ent : Entity_Id;
19959 Val : Boolean;
19961 begin
19962 Check_No_Identifiers;
19963 Check_At_Most_N_Arguments (1);
19965 -- Protected definition case
19967 if Nkind (P) = N_Protected_Definition then
19968 Ent := Defining_Identifier (Parent (P));
19970 -- One argument
19972 if Arg_Count = 1 then
19973 Arg := Get_Pragma_Arg (Arg1);
19974 Val := Is_True (Static_Boolean (Arg));
19976 -- No arguments (expression is considered to be True)
19978 else
19979 Val := True;
19980 end if;
19982 -- Check duplicate pragma before we chain the pragma in the Rep
19983 -- Item chain of Ent.
19985 Check_Duplicate_Pragma (Ent);
19986 Record_Rep_Item (Ent, N);
19987 Set_Uses_Lock_Free (Ent, Val);
19989 -- Anything else is incorrect placement
19991 else
19992 Pragma_Misplaced;
19993 end if;
19994 end Lock_Free;
19996 --------------------
19997 -- Locking_Policy --
19998 --------------------
20000 -- pragma Locking_Policy (policy_IDENTIFIER);
20002 when Pragma_Locking_Policy => declare
20003 subtype LP_Range is Name_Id
20004 range First_Locking_Policy_Name .. Last_Locking_Policy_Name;
20005 LP_Val : LP_Range;
20006 LP : Character;
20008 begin
20009 Check_Ada_83_Warning;
20010 Check_Arg_Count (1);
20011 Check_No_Identifiers;
20012 Check_Arg_Is_Locking_Policy (Arg1);
20013 Check_Valid_Configuration_Pragma;
20014 LP_Val := Chars (Get_Pragma_Arg (Arg1));
20016 case LP_Val is
20017 when Name_Ceiling_Locking => LP := 'C';
20018 when Name_Concurrent_Readers_Locking => LP := 'R';
20019 when Name_Inheritance_Locking => LP := 'I';
20020 end case;
20022 if Locking_Policy /= ' '
20023 and then Locking_Policy /= LP
20024 then
20025 Error_Msg_Sloc := Locking_Policy_Sloc;
20026 Error_Pragma ("locking policy incompatible with policy#");
20028 -- Set new policy, but always preserve System_Location since we
20029 -- like the error message with the run time name.
20031 else
20032 Locking_Policy := LP;
20034 if Locking_Policy_Sloc /= System_Location then
20035 Locking_Policy_Sloc := Loc;
20036 end if;
20037 end if;
20038 end;
20040 -------------------
20041 -- Loop_Optimize --
20042 -------------------
20044 -- pragma Loop_Optimize ( OPTIMIZATION_HINT {, OPTIMIZATION_HINT } );
20046 -- OPTIMIZATION_HINT ::=
20047 -- Ivdep | No_Unroll | Unroll | No_Vector | Vector
20049 when Pragma_Loop_Optimize => Loop_Optimize : declare
20050 Hint : Node_Id;
20052 begin
20053 GNAT_Pragma;
20054 Check_At_Least_N_Arguments (1);
20055 Check_No_Identifiers;
20057 Hint := First (Pragma_Argument_Associations (N));
20058 while Present (Hint) loop
20059 Check_Arg_Is_One_Of (Hint, Name_Ivdep,
20060 Name_No_Unroll,
20061 Name_Unroll,
20062 Name_No_Vector,
20063 Name_Vector);
20064 Next (Hint);
20065 end loop;
20067 Check_Loop_Pragma_Placement;
20068 end Loop_Optimize;
20070 ------------------
20071 -- Loop_Variant --
20072 ------------------
20074 -- pragma Loop_Variant
20075 -- ( LOOP_VARIANT_ITEM {, LOOP_VARIANT_ITEM } );
20077 -- LOOP_VARIANT_ITEM ::= CHANGE_DIRECTION => discrete_EXPRESSION
20079 -- CHANGE_DIRECTION ::= Increases | Decreases
20081 when Pragma_Loop_Variant => Loop_Variant : declare
20082 Variant : Node_Id;
20084 begin
20085 GNAT_Pragma;
20086 Check_At_Least_N_Arguments (1);
20087 Check_Loop_Pragma_Placement;
20089 -- Process all increasing / decreasing expressions
20091 Variant := First (Pragma_Argument_Associations (N));
20092 while Present (Variant) loop
20093 if Chars (Variant) = No_Name then
20094 Error_Pragma_Arg_Ident ("expect name `Increases`", Variant);
20096 elsif Chars (Variant) not in
20097 Name_Decreases | Name_Increases | Name_Structural
20098 then
20099 declare
20100 Name : String := Get_Name_String (Chars (Variant));
20102 begin
20103 -- It is a common mistake to write "Increasing" for
20104 -- "Increases" or "Decreasing" for "Decreases". Recognize
20105 -- specially names starting with "incr" or "decr" to
20106 -- suggest the corresponding name.
20108 System.Case_Util.To_Lower (Name);
20110 if Name'Length >= 4
20111 and then Name (1 .. 4) = "incr"
20112 then
20113 Error_Pragma_Arg_Ident
20114 ("expect name `Increases`", Variant);
20116 elsif Name'Length >= 4
20117 and then Name (1 .. 4) = "decr"
20118 then
20119 Error_Pragma_Arg_Ident
20120 ("expect name `Decreases`", Variant);
20122 elsif Name'Length >= 4
20123 and then Name (1 .. 4) = "stru"
20124 then
20125 Error_Pragma_Arg_Ident
20126 ("expect name `Structural`", Variant);
20128 else
20129 Error_Pragma_Arg_Ident
20130 ("expect name `Increases`, `Decreases`,"
20131 & " or `Structural`", Variant);
20132 end if;
20133 end;
20135 elsif Chars (Variant) = Name_Structural
20136 and then List_Length (Pragma_Argument_Associations (N)) > 1
20137 then
20138 Error_Pragma_Arg_Ident
20139 ("Structural variant shall be the only variant", Variant);
20140 end if;
20142 -- Preanalyze_Assert_Expression, but without enforcing any of
20143 -- the two acceptable types.
20145 Preanalyze_Assert_Expression (Expression (Variant));
20147 -- Expression of a discrete type is allowed. Nothing to
20148 -- check for structural variants.
20150 if Chars (Variant) = Name_Structural
20151 or else Is_Discrete_Type (Etype (Expression (Variant)))
20152 then
20153 null;
20155 -- Expression of a Big_Integer type (or its ghost variant) is
20156 -- only allowed in Decreases clause.
20158 elsif
20159 Is_RTE (Base_Type (Etype (Expression (Variant))),
20160 RE_Big_Integer)
20161 or else
20162 Is_RTE (Base_Type (Etype (Expression (Variant))),
20163 RO_GH_Big_Integer)
20164 then
20165 if Chars (Variant) = Name_Increases then
20166 Error_Msg_N
20167 ("Loop_Variant with Big_Integer can only decrease",
20168 Expression (Variant));
20169 end if;
20171 -- Expression of other types is not allowed
20173 else
20174 Error_Msg_N
20175 ("expected a discrete or Big_Integer type",
20176 Expression (Variant));
20177 end if;
20179 Next (Variant);
20180 end loop;
20181 end Loop_Variant;
20183 -----------------------
20184 -- Machine_Attribute --
20185 -----------------------
20187 -- pragma Machine_Attribute (
20188 -- [Entity =>] LOCAL_NAME,
20189 -- [Attribute_Name =>] static_string_EXPRESSION
20190 -- [, [Info =>] static_EXPRESSION {, static_EXPRESSION}] );
20192 when Pragma_Machine_Attribute => Machine_Attribute : declare
20193 Arg : Node_Id;
20194 Def_Id : Entity_Id;
20196 begin
20197 GNAT_Pragma;
20198 Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
20200 if Arg_Count >= 3 then
20201 Check_Optional_Identifier (Arg3, Name_Info);
20202 Arg := Arg3;
20203 while Present (Arg) loop
20204 Check_Arg_Is_OK_Static_Expression (Arg);
20205 Arg := Next (Arg);
20206 end loop;
20207 else
20208 Check_Arg_Count (2);
20209 end if;
20211 Check_Optional_Identifier (Arg1, Name_Entity);
20212 Check_Optional_Identifier (Arg2, Name_Attribute_Name);
20213 Check_Arg_Is_Local_Name (Arg1);
20214 Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
20215 Def_Id := Entity (Get_Pragma_Arg (Arg1));
20217 -- Apply the pragma to the designated type, rather than to the
20218 -- access type, unless it's a strub annotation. We wish to enable
20219 -- objects of access type, as well as access types themselves, to
20220 -- be annotated, so that reading the access objects (as oposed to
20221 -- the designated data) automatically enables stack
20222 -- scrubbing. That said, as in the attribute handler that
20223 -- processes the pragma turned into a compiler attribute, a strub
20224 -- annotation that must be associated with a subprogram type (for
20225 -- holding an explicit strub mode), when applied to an
20226 -- access-to-subprogram, gets promoted to the subprogram type. We
20227 -- might be tempted to leave it alone here, since the C attribute
20228 -- handler will adjust it, but then GNAT would convert the
20229 -- annotated subprogram types to naked ones before using them,
20230 -- cancelling out their intended effects.
20232 if Is_Access_Type (Def_Id)
20233 and then (not Strub_Pragma_P (N)
20234 or else
20235 (Present (Arg3)
20236 and then
20237 Ekind (Designated_Type
20238 (Def_Id)) = E_Subprogram_Type))
20239 then
20240 Def_Id := Designated_Type (Def_Id);
20241 end if;
20243 if Rep_Item_Too_Early (Def_Id, N) then
20244 return;
20245 end if;
20247 Def_Id := Underlying_Type (Def_Id);
20249 -- The only processing required is to link this item on to the
20250 -- list of rep items for the given entity. This is accomplished
20251 -- by the call to Rep_Item_Too_Late (when no error is detected
20252 -- and False is returned).
20254 if Rep_Item_Too_Late (Def_Id, N) then
20255 return;
20256 else
20257 Set_Has_Gigi_Rep_Item (Def_Id);
20258 end if;
20259 end Machine_Attribute;
20261 ----------
20262 -- Main --
20263 ----------
20265 -- pragma Main
20266 -- (MAIN_OPTION [, MAIN_OPTION]);
20268 -- MAIN_OPTION ::=
20269 -- [STACK_SIZE =>] static_integer_EXPRESSION
20270 -- | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
20271 -- | [TIME_SLICING_ENABLED =>] static_boolean_EXPRESSION
20273 when Pragma_Main => Main : declare
20274 Args : Args_List (1 .. 3);
20275 Names : constant Name_List (1 .. 3) := (
20276 Name_Stack_Size,
20277 Name_Task_Stack_Size_Default,
20278 Name_Time_Slicing_Enabled);
20280 Nod : Node_Id;
20282 begin
20283 GNAT_Pragma;
20284 Gather_Associations (Names, Args);
20286 for J in 1 .. 2 loop
20287 if Present (Args (J)) then
20288 Check_Arg_Is_OK_Static_Expression (Args (J), Any_Integer);
20289 end if;
20290 end loop;
20292 if Present (Args (3)) then
20293 Check_Arg_Is_OK_Static_Expression (Args (3), Standard_Boolean);
20294 end if;
20296 Nod := Next (N);
20297 while Present (Nod) loop
20298 if Nkind (Nod) = N_Pragma
20299 and then Pragma_Name (Nod) = Name_Main
20300 then
20301 Error_Msg_Name_1 := Pname;
20302 Error_Msg_N ("duplicate pragma% not permitted", Nod);
20303 end if;
20305 Next (Nod);
20306 end loop;
20307 end Main;
20309 ------------------
20310 -- Main_Storage --
20311 ------------------
20313 -- pragma Main_Storage
20314 -- (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
20316 -- MAIN_STORAGE_OPTION ::=
20317 -- [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
20318 -- | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
20320 when Pragma_Main_Storage => Main_Storage : declare
20321 Args : Args_List (1 .. 2);
20322 Names : constant Name_List (1 .. 2) := (
20323 Name_Working_Storage,
20324 Name_Top_Guard);
20326 Nod : Node_Id;
20328 begin
20329 GNAT_Pragma;
20330 Gather_Associations (Names, Args);
20332 for J in 1 .. 2 loop
20333 if Present (Args (J)) then
20334 Check_Arg_Is_OK_Static_Expression (Args (J), Any_Integer);
20335 end if;
20336 end loop;
20338 Check_In_Main_Program;
20340 Nod := Next (N);
20341 while Present (Nod) loop
20342 if Nkind (Nod) = N_Pragma
20343 and then Pragma_Name (Nod) = Name_Main_Storage
20344 then
20345 Error_Msg_Name_1 := Pname;
20346 Error_Msg_N ("duplicate pragma% not permitted", Nod);
20347 end if;
20349 Next (Nod);
20350 end loop;
20351 end Main_Storage;
20353 ----------------------------
20354 -- Max_Entry_Queue_Length --
20355 ----------------------------
20357 -- pragma Max_Entry_Queue_Length (static_integer_EXPRESSION);
20359 -- This processing is shared by Pragma_Max_Entry_Queue_Depth and
20360 -- Pragma_Max_Queue_Length.
20362 when Pragma_Max_Entry_Queue_Length
20363 | Pragma_Max_Entry_Queue_Depth
20364 | Pragma_Max_Queue_Length
20366 Max_Entry_Queue_Length : declare
20367 Arg : Node_Id;
20368 Entry_Decl : Node_Id;
20369 Entry_Id : Entity_Id;
20370 Val : Uint;
20372 begin
20373 if Prag_Id = Pragma_Max_Entry_Queue_Depth
20374 or else Prag_Id = Pragma_Max_Queue_Length
20375 then
20376 GNAT_Pragma;
20377 end if;
20379 Check_Arg_Count (1);
20381 Entry_Decl :=
20382 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
20384 -- Entry declaration
20386 if Nkind (Entry_Decl) = N_Entry_Declaration then
20388 -- Entry illegally within a task
20390 if Nkind (Parent (N)) = N_Task_Definition then
20391 Error_Pragma ("pragma % cannot apply to task entries");
20392 end if;
20394 Entry_Id := Defining_Entity (Entry_Decl);
20396 -- Otherwise the pragma is associated with an illegal construct
20398 else
20399 Error_Pragma
20400 ("pragma % must apply to a protected entry declaration");
20401 end if;
20403 -- Mark the pragma as Ghost if the related subprogram is also
20404 -- Ghost. This also ensures that any expansion performed further
20405 -- below will produce Ghost nodes.
20407 Mark_Ghost_Pragma (N, Entry_Id);
20409 -- Analyze the Integer expression
20411 Arg := Get_Pragma_Arg (Arg1);
20412 Check_Arg_Is_OK_Static_Expression (Arg, Any_Integer);
20414 Val := Expr_Value (Arg);
20416 if Val < -1 then
20417 Error_Pragma_Arg
20418 ("argument for pragma% cannot be less than -1", Arg1);
20420 elsif not UI_Is_In_Int_Range (Val) then
20421 Error_Pragma_Arg
20422 ("argument for pragma% out of range of Integer", Arg1);
20424 end if;
20426 Record_Rep_Item (Entry_Id, N);
20427 end Max_Entry_Queue_Length;
20429 -----------------
20430 -- Memory_Size --
20431 -----------------
20433 -- pragma Memory_Size (NUMERIC_LITERAL)
20435 when Pragma_Memory_Size =>
20436 GNAT_Pragma;
20438 -- Memory size is simply ignored
20440 Check_No_Identifiers;
20441 Check_Arg_Count (1);
20442 Check_Arg_Is_Integer_Literal (Arg1);
20444 -------------
20445 -- No_Body --
20446 -------------
20448 -- pragma No_Body;
20450 -- The only correct use of this pragma is on its own in a file, in
20451 -- which case it is specially processed (see Gnat1drv.Check_Bad_Body
20452 -- and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
20453 -- check for a file containing nothing but a No_Body pragma). If we
20454 -- attempt to process it during normal semantics processing, it means
20455 -- it was misplaced.
20457 when Pragma_No_Body =>
20458 GNAT_Pragma;
20459 Pragma_Misplaced;
20461 -----------------------------
20462 -- No_Elaboration_Code_All --
20463 -----------------------------
20465 -- pragma No_Elaboration_Code_All;
20467 when Pragma_No_Elaboration_Code_All =>
20468 GNAT_Pragma;
20469 Check_Valid_Library_Unit_Pragma;
20471 -- If N was rewritten as a null statement there is nothing more
20472 -- to do.
20474 if Nkind (N) = N_Null_Statement then
20475 return;
20476 end if;
20478 -- Must appear for a spec or generic spec
20480 if Nkind (Unit (Cunit (Current_Sem_Unit))) not in
20481 N_Generic_Package_Declaration |
20482 N_Generic_Subprogram_Declaration |
20483 N_Package_Declaration |
20484 N_Subprogram_Declaration
20485 then
20486 Error_Pragma
20487 (Fix_Error
20488 ("pragma% can only occur for package "
20489 & "or subprogram spec"));
20490 end if;
20492 -- Set flag in unit table
20494 Set_No_Elab_Code_All (Current_Sem_Unit);
20496 -- Set restriction No_Elaboration_Code if this is the main unit
20498 if Current_Sem_Unit = Main_Unit then
20499 Set_Restriction (No_Elaboration_Code, N);
20500 end if;
20502 -- If we are in the main unit or in an extended main source unit,
20503 -- then we also add it to the configuration restrictions so that
20504 -- it will apply to all units in the extended main source.
20506 if Current_Sem_Unit = Main_Unit
20507 or else In_Extended_Main_Source_Unit (N)
20508 then
20509 Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
20510 end if;
20512 -- If in main extended unit, activate transitive with test
20514 if In_Extended_Main_Source_Unit (N) then
20515 Opt.No_Elab_Code_All_Pragma := N;
20516 end if;
20518 -----------------------------
20519 -- No_Component_Reordering --
20520 -----------------------------
20522 -- pragma No_Component_Reordering [([Entity =>] type_LOCAL_NAME)];
20524 when Pragma_No_Component_Reordering => No_Comp_Reordering : declare
20525 E : Entity_Id;
20526 E_Id : Node_Id;
20528 begin
20529 GNAT_Pragma;
20530 Check_At_Most_N_Arguments (1);
20532 if Arg_Count = 0 then
20533 Check_Valid_Configuration_Pragma;
20534 Opt.No_Component_Reordering := True;
20536 else
20537 Check_Optional_Identifier (Arg2, Name_Entity);
20538 Check_Arg_Is_Local_Name (Arg1);
20539 E_Id := Get_Pragma_Arg (Arg1);
20541 if Etype (E_Id) = Any_Type then
20542 return;
20543 end if;
20545 E := Entity (E_Id);
20547 if not Is_Record_Type (E) then
20548 Error_Pragma_Arg ("pragma% requires record type", Arg1);
20549 end if;
20551 Set_No_Reordering (Base_Type (E));
20552 end if;
20553 end No_Comp_Reordering;
20555 --------------------------
20556 -- No_Heap_Finalization --
20557 --------------------------
20559 -- pragma No_Heap_Finalization [ (first_subtype_LOCAL_NAME) ];
20561 when Pragma_No_Heap_Finalization => No_Heap_Finalization : declare
20562 Context : constant Node_Id := Parent (N);
20563 Typ_Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
20564 Prev : Node_Id;
20565 Typ : Entity_Id;
20567 begin
20568 GNAT_Pragma;
20569 Check_No_Identifiers;
20571 -- The pragma appears in a configuration file
20573 if No (Context) then
20574 Check_Arg_Count (0);
20575 Check_Valid_Configuration_Pragma;
20577 -- Detect a duplicate pragma
20579 if Present (No_Heap_Finalization_Pragma) then
20580 Duplication_Error
20581 (Prag => N,
20582 Prev => No_Heap_Finalization_Pragma);
20583 raise Pragma_Exit;
20584 end if;
20586 No_Heap_Finalization_Pragma := N;
20588 -- Otherwise the pragma should be associated with a library-level
20589 -- named access-to-object type.
20591 else
20592 Check_Arg_Count (1);
20593 Check_Arg_Is_Local_Name (Arg1);
20595 Find_Type (Typ_Arg);
20596 Typ := Entity (Typ_Arg);
20598 -- The type being subjected to the pragma is erroneous
20600 if Typ = Any_Type then
20601 Error_Pragma ("cannot find type referenced by pragma %");
20603 -- The pragma is applied to an incomplete or generic formal
20604 -- type way too early.
20606 elsif Rep_Item_Too_Early (Typ, N) then
20607 return;
20609 else
20610 Typ := Underlying_Type (Typ);
20611 end if;
20613 -- The pragma must apply to an access-to-object type
20615 if Ekind (Typ) in E_Access_Type | E_General_Access_Type then
20616 null;
20618 -- Give a detailed error message on all other access type kinds
20620 elsif Ekind (Typ) = E_Access_Protected_Subprogram_Type then
20621 Error_Pragma
20622 ("pragma % cannot apply to access protected subprogram "
20623 & "type");
20625 elsif Ekind (Typ) = E_Access_Subprogram_Type then
20626 Error_Pragma
20627 ("pragma % cannot apply to access subprogram type");
20629 elsif Is_Anonymous_Access_Type (Typ) then
20630 Error_Pragma
20631 ("pragma % cannot apply to anonymous access type");
20633 -- Give a general error message in case the pragma applies to a
20634 -- non-access type.
20636 else
20637 Error_Pragma
20638 ("pragma % must apply to library level access type");
20639 end if;
20641 -- At this point the argument denotes an access-to-object type.
20642 -- Ensure that the type is declared at the library level.
20644 if Is_Library_Level_Entity (Typ) then
20645 null;
20647 -- Quietly ignore an access-to-object type originally declared
20648 -- at the library level within a generic, but instantiated at
20649 -- a non-library level. As a result the access-to-object type
20650 -- "loses" its No_Heap_Finalization property.
20652 elsif In_Instance then
20653 raise Pragma_Exit;
20655 else
20656 Error_Pragma
20657 ("pragma % must apply to library level access type");
20658 end if;
20660 -- Detect a duplicate pragma
20662 if Present (No_Heap_Finalization_Pragma) then
20663 Duplication_Error
20664 (Prag => N,
20665 Prev => No_Heap_Finalization_Pragma);
20666 raise Pragma_Exit;
20668 else
20669 Prev := Get_Pragma (Typ, Pragma_No_Heap_Finalization);
20671 if Present (Prev) then
20672 Duplication_Error
20673 (Prag => N,
20674 Prev => Prev);
20675 raise Pragma_Exit;
20676 end if;
20677 end if;
20679 Record_Rep_Item (Typ, N);
20680 end if;
20681 end No_Heap_Finalization;
20683 ---------------
20684 -- No_Inline --
20685 ---------------
20687 -- pragma No_Inline ( NAME {, NAME} );
20689 when Pragma_No_Inline =>
20690 GNAT_Pragma;
20691 Process_Inline (Suppressed);
20693 ---------------
20694 -- No_Return --
20695 ---------------
20697 -- pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
20699 when Pragma_No_Return => Prag_No_Return : declare
20701 function Check_No_Return
20702 (E : Entity_Id;
20703 N : Node_Id) return Boolean;
20704 -- Check rule 6.5.1(4/3) of the Ada RM. If the rule is violated,
20705 -- emit an error message and return False, otherwise return True.
20706 -- 6.5.1 Nonreturning procedures:
20707 -- 4/3 "Aspect No_Return shall not be specified for a null
20708 -- procedure nor an instance of a generic unit."
20710 ---------------------
20711 -- Check_No_Return --
20712 ---------------------
20714 function Check_No_Return
20715 (E : Entity_Id;
20716 N : Node_Id) return Boolean
20718 begin
20719 if Ekind (E) in E_Function | E_Generic_Function then
20720 Error_Msg_Ada_2022_Feature ("No_Return function", Sloc (N));
20721 return Ada_Version >= Ada_2022;
20723 elsif Ekind (E) = E_Procedure then
20725 -- If E is a generic instance, marking it with No_Return
20726 -- is forbidden, but having it inherit the No_Return of
20727 -- the generic is allowed. We check if E is inheriting its
20728 -- No_Return flag from the generic by checking if No_Return
20729 -- is already set.
20731 if Is_Generic_Instance (E) and then not No_Return (E) then
20732 Error_Msg_NE
20733 ("generic instance & is marked as No_Return", N, E);
20734 Error_Msg_NE
20735 ("\generic procedure & must be marked No_Return",
20737 Generic_Parent (Parent (E)));
20738 return False;
20740 elsif Null_Present (Subprogram_Specification (E)) then
20741 Error_Msg_NE
20742 ("null procedure & cannot be marked No_Return", N, E);
20743 return False;
20744 end if;
20745 end if;
20747 return True;
20748 end Check_No_Return;
20750 Arg : Node_Id;
20751 E : Entity_Id;
20752 Found : Boolean;
20753 Id : Node_Id;
20755 Ghost_Error_Posted : Boolean := False;
20756 -- Flag set when an error concerning the illegal mix of Ghost and
20757 -- non-Ghost subprograms is emitted.
20759 Ghost_Id : Entity_Id := Empty;
20760 -- The entity of the first Ghost procedure encountered while
20761 -- processing the arguments of the pragma.
20763 begin
20764 Ada_2005_Pragma;
20765 Check_At_Least_N_Arguments (1);
20767 -- Loop through arguments of pragma
20769 Arg := Arg1;
20770 while Present (Arg) loop
20771 Check_Arg_Is_Local_Name (Arg);
20772 Id := Get_Pragma_Arg (Arg);
20773 Analyze (Id);
20775 if not Is_Entity_Name (Id) then
20776 Error_Pragma_Arg ("entity name required", Arg);
20777 end if;
20779 if Etype (Id) = Any_Type then
20780 raise Pragma_Exit;
20781 end if;
20783 -- Loop to find matching procedures or functions (Ada 2022)
20785 E := Entity (Id);
20787 Found := False;
20788 while Present (E)
20789 and then Scope (E) = Current_Scope
20790 loop
20791 -- Ada 2022 (AI12-0269): A function can be No_Return
20793 if Ekind (E) in E_Generic_Procedure | E_Procedure
20794 | E_Generic_Function | E_Function
20795 then
20796 -- Check that the pragma is not applied to a body.
20797 -- First check the specless body case, to give a
20798 -- different error message. These checks do not apply
20799 -- if Relaxed_RM_Semantics, to accommodate other Ada
20800 -- compilers. Disable these checks under -gnatd.J.
20802 if not Debug_Flag_Dot_JJ then
20803 if Nkind (Parent (Declaration_Node (E))) =
20804 N_Subprogram_Body
20805 and then not Relaxed_RM_Semantics
20806 then
20807 Error_Pragma
20808 ("pragma% requires separate spec and must come "
20809 & "before body");
20810 end if;
20812 -- Now the "specful" body case
20814 if Rep_Item_Too_Late (E, N) then
20815 raise Pragma_Exit;
20816 end if;
20817 end if;
20819 if Check_No_Return (E, N) then
20820 Set_No_Return (E);
20821 end if;
20823 -- A pragma that applies to a Ghost entity becomes Ghost
20824 -- for the purposes of legality checks and removal of
20825 -- ignored Ghost code.
20827 Mark_Ghost_Pragma (N, E);
20829 -- Capture the entity of the first Ghost procedure being
20830 -- processed for error detection purposes.
20832 if Is_Ghost_Entity (E) then
20833 if No (Ghost_Id) then
20834 Ghost_Id := E;
20835 end if;
20837 -- Otherwise the subprogram is non-Ghost. It is illegal
20838 -- to mix references to Ghost and non-Ghost entities
20839 -- (SPARK RM 6.9).
20841 elsif Present (Ghost_Id)
20842 and then not Ghost_Error_Posted
20843 then
20844 Ghost_Error_Posted := True;
20846 Error_Msg_Name_1 := Pname;
20847 Error_Msg_N
20848 ("pragma % cannot mention ghost and non-ghost "
20849 & "procedures", N);
20851 Error_Msg_Sloc := Sloc (Ghost_Id);
20852 Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
20854 Error_Msg_Sloc := Sloc (E);
20855 Error_Msg_NE ("\& # declared as non-ghost", N, E);
20856 end if;
20858 -- Set flag on any alias as well
20860 if Is_Overloadable (E)
20861 and then Present (Alias (E))
20862 and then Check_No_Return (Alias (E), N)
20863 then
20864 Set_No_Return (Alias (E));
20865 end if;
20867 Found := True;
20868 end if;
20870 exit when From_Aspect_Specification (N);
20871 E := Homonym (E);
20872 end loop;
20874 -- If entity in not in current scope it may be the enclosing
20875 -- subprogram body to which the aspect applies.
20877 if not Found then
20878 if Entity (Id) = Current_Scope
20879 and then From_Aspect_Specification (N)
20880 and then Check_No_Return (Entity (Id), N)
20881 then
20882 Set_No_Return (Entity (Id));
20884 elsif Ada_Version >= Ada_2022 then
20885 Error_Pragma_Arg
20886 ("no subprogram& found for pragma%", Arg);
20888 else
20889 Error_Pragma_Arg ("no procedure& found for pragma%", Arg);
20890 end if;
20891 end if;
20893 Next (Arg);
20894 end loop;
20895 end Prag_No_Return;
20897 -----------------
20898 -- No_Run_Time --
20899 -----------------
20901 -- pragma No_Run_Time;
20903 -- Note: this pragma is retained for backwards compatibility. See
20904 -- body of Rtsfind for full details on its handling.
20906 when Pragma_No_Run_Time =>
20907 GNAT_Pragma;
20908 Check_Valid_Configuration_Pragma;
20909 Check_Arg_Count (0);
20911 -- Remove backward compatibility if Build_Type is FSF or GPL and
20912 -- generate a warning.
20914 declare
20915 Ignore : constant Boolean := Build_Type in FSF .. GPL;
20916 begin
20917 if Ignore then
20918 Error_Pragma ("pragma% is ignored, has no effect??");
20919 else
20920 No_Run_Time_Mode := True;
20921 Configurable_Run_Time_Mode := True;
20923 -- Set Duration to 32 bits if word size is 32
20925 if Ttypes.System_Word_Size = 32 then
20926 Duration_32_Bits_On_Target := True;
20927 end if;
20929 -- Set appropriate restrictions
20931 Set_Restriction (No_Finalization, N);
20932 Set_Restriction (No_Exception_Handlers, N);
20933 Set_Restriction (Max_Tasks, N, 0);
20934 Set_Restriction (No_Tasking, N);
20935 end if;
20936 end;
20938 -----------------------
20939 -- No_Tagged_Streams --
20940 -----------------------
20942 -- pragma No_Tagged_Streams [([Entity => ]tagged_type_local_NAME)];
20944 when Pragma_No_Tagged_Streams => No_Tagged_Strms : declare
20945 E : Entity_Id;
20946 E_Id : Node_Id;
20948 begin
20949 GNAT_Pragma;
20950 Check_At_Most_N_Arguments (1);
20952 -- One argument case
20954 if Arg_Count = 1 then
20955 Check_Optional_Identifier (Arg1, Name_Entity);
20956 Check_Arg_Is_Local_Name (Arg1);
20957 E_Id := Get_Pragma_Arg (Arg1);
20959 if Etype (E_Id) = Any_Type then
20960 return;
20961 end if;
20963 E := Entity (E_Id);
20965 Check_Duplicate_Pragma (E);
20967 if not Is_Tagged_Type (E) or else Is_Derived_Type (E) then
20968 Error_Pragma_Arg
20969 ("argument for pragma% must be root tagged type", Arg1);
20970 end if;
20972 if Rep_Item_Too_Early (E, N)
20973 or else
20974 Rep_Item_Too_Late (E, N)
20975 then
20976 return;
20977 else
20978 Set_No_Tagged_Streams_Pragma (E, N);
20979 end if;
20981 -- Zero argument case
20983 else
20984 Check_Is_In_Decl_Part_Or_Package_Spec;
20985 No_Tagged_Streams := N;
20986 end if;
20987 end No_Tagged_Strms;
20989 ------------------------
20990 -- No_Strict_Aliasing --
20991 ------------------------
20993 -- pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
20995 when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
20996 E : Entity_Id;
20997 E_Id : Node_Id;
20999 begin
21000 GNAT_Pragma;
21001 Check_At_Most_N_Arguments (1);
21003 if Arg_Count = 0 then
21004 Check_Valid_Configuration_Pragma;
21005 Opt.No_Strict_Aliasing := True;
21007 else
21008 Check_Optional_Identifier (Arg2, Name_Entity);
21009 Check_Arg_Is_Local_Name (Arg1);
21010 E_Id := Get_Pragma_Arg (Arg1);
21012 if Etype (E_Id) = Any_Type then
21013 return;
21014 end if;
21016 E := Entity (E_Id);
21018 if not Is_Access_Type (E) then
21019 Error_Pragma_Arg ("pragma% requires access type", Arg1);
21020 end if;
21022 Set_No_Strict_Aliasing (Base_Type (E));
21023 end if;
21024 end No_Strict_Aliasing;
21026 -----------------------
21027 -- Normalize_Scalars --
21028 -----------------------
21030 -- pragma Normalize_Scalars;
21032 when Pragma_Normalize_Scalars =>
21033 Check_Ada_83_Warning;
21034 Check_Arg_Count (0);
21035 Check_Valid_Configuration_Pragma;
21037 -- Normalize_Scalars creates false positives in CodePeer, and
21038 -- incorrect negative results in GNATprove mode, so ignore this
21039 -- pragma in these modes.
21041 if not (CodePeer_Mode or GNATprove_Mode) then
21042 Normalize_Scalars := True;
21043 Init_Or_Norm_Scalars := True;
21044 end if;
21046 -----------------
21047 -- Obsolescent --
21048 -----------------
21050 -- pragma Obsolescent;
21052 -- pragma Obsolescent (
21053 -- [Message =>] static_string_EXPRESSION
21054 -- [,[Version =>] Ada_05]);
21056 -- pragma Obsolescent (
21057 -- [Entity =>] NAME
21058 -- [,[Message =>] static_string_EXPRESSION
21059 -- [,[Version =>] Ada_05]]);
21061 when Pragma_Obsolescent => Obsolescent : declare
21062 Decl : Node_Id;
21063 Ename : Node_Id;
21065 procedure Set_Obsolescent (E : Entity_Id);
21066 -- Given an entity Ent, mark it as obsolescent if appropriate
21068 ---------------------
21069 -- Set_Obsolescent --
21070 ---------------------
21072 procedure Set_Obsolescent (E : Entity_Id) is
21073 Active : Boolean;
21074 Ent : Entity_Id;
21075 S : String_Id;
21077 begin
21078 Active := True;
21079 Ent := E;
21081 -- A pragma that applies to a Ghost entity becomes Ghost for
21082 -- the purposes of legality checks and removal of ignored Ghost
21083 -- code.
21085 Mark_Ghost_Pragma (N, E);
21087 -- Entity name was given
21089 if Present (Ename) then
21091 -- If entity name matches, we are fine.
21093 if Chars (Ename) = Chars (Ent) then
21094 Set_Entity (Ename, Ent);
21095 Generate_Reference (Ent, Ename);
21097 -- If entity name does not match, only possibility is an
21098 -- enumeration literal from an enumeration type declaration.
21100 elsif Ekind (Ent) /= E_Enumeration_Type then
21101 Error_Pragma
21102 ("pragma % entity name does not match declaration");
21104 else
21105 Ent := First_Literal (E);
21106 loop
21107 if No (Ent) then
21108 Error_Pragma
21109 ("pragma % entity name does not match any "
21110 & "enumeration literal");
21112 elsif Chars (Ent) = Chars (Ename) then
21113 Set_Entity (Ename, Ent);
21114 Generate_Reference (Ent, Ename);
21115 exit;
21117 else
21118 Next_Literal (Ent);
21119 end if;
21120 end loop;
21121 end if;
21122 end if;
21124 -- Ent points to entity to be marked
21126 if Arg_Count >= 1 then
21128 -- Deal with static string argument
21130 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
21131 S := Strval (Get_Pragma_Arg (Arg1));
21133 for J in 1 .. String_Length (S) loop
21134 if not In_Character_Range (Get_String_Char (S, J)) then
21135 Error_Pragma_Arg
21136 ("pragma% argument does not allow wide characters",
21137 Arg1);
21138 end if;
21139 end loop;
21141 Obsolescent_Warnings.Append
21142 ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
21144 -- Check for Ada_05 parameter
21146 if Arg_Count /= 1 then
21147 Check_Arg_Count (2);
21149 declare
21150 Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
21152 begin
21153 Check_Arg_Is_Identifier (Argx);
21155 if Chars (Argx) /= Name_Ada_05 then
21156 Error_Msg_Name_2 := Name_Ada_05;
21157 Error_Pragma_Arg
21158 ("only allowed argument for pragma% is %", Argx);
21159 end if;
21161 if Ada_Version_Explicit < Ada_2005
21162 or else not Warn_On_Ada_2005_Compatibility
21163 then
21164 Active := False;
21165 end if;
21166 end;
21167 end if;
21168 end if;
21170 -- Set flag if pragma active
21172 if Active then
21173 Set_Is_Obsolescent (Ent);
21174 end if;
21176 return;
21177 end Set_Obsolescent;
21179 -- Start of processing for pragma Obsolescent
21181 begin
21182 GNAT_Pragma;
21184 Check_At_Most_N_Arguments (3);
21186 -- See if first argument specifies an entity name
21188 if Arg_Count >= 1
21189 and then
21190 (Chars (Arg1) = Name_Entity
21191 or else
21192 Nkind (Get_Pragma_Arg (Arg1)) in
21193 N_Character_Literal | N_Identifier | N_Operator_Symbol)
21194 then
21195 Ename := Get_Pragma_Arg (Arg1);
21197 -- Eliminate first argument, so we can share processing
21199 Arg1 := Arg2;
21200 Arg2 := Arg3;
21201 Arg_Count := Arg_Count - 1;
21203 -- No Entity name argument given
21205 else
21206 Ename := Empty;
21207 end if;
21209 if Arg_Count >= 1 then
21210 Check_Optional_Identifier (Arg1, Name_Message);
21212 if Arg_Count = 2 then
21213 Check_Optional_Identifier (Arg2, Name_Version);
21214 end if;
21215 end if;
21217 -- Get immediately preceding declaration
21219 Decl := Prev (N);
21220 while Present (Decl) and then Nkind (Decl) = N_Pragma loop
21221 Prev (Decl);
21222 end loop;
21224 -- Cases where we do not follow anything other than another pragma
21226 if No (Decl) then
21228 -- Case 0: library level compilation unit declaration with
21229 -- the pragma preceding the declaration.
21231 if Nkind (Parent (N)) = N_Compilation_Unit then
21232 Pragma_Misplaced;
21234 -- Case 1: library level compilation unit declaration with
21235 -- the pragma immediately following the declaration.
21237 elsif Nkind (Parent (N)) = N_Compilation_Unit_Aux then
21238 Set_Obsolescent
21239 (Defining_Entity (Unit (Parent (Parent (N)))));
21240 return;
21242 -- Case 2: library unit placement for package
21244 else
21245 declare
21246 Ent : constant Entity_Id := Find_Lib_Unit_Name;
21247 begin
21248 if Is_Package_Or_Generic_Package (Ent) then
21249 Set_Obsolescent (Ent);
21250 return;
21251 end if;
21252 end;
21253 end if;
21255 -- Cases where we must follow a declaration, including an
21256 -- abstract subprogram declaration, which is not in the
21257 -- other node subtypes.
21259 else
21260 if Nkind (Decl) not in N_Declaration
21261 and then Nkind (Decl) not in N_Later_Decl_Item
21262 and then Nkind (Decl) not in N_Generic_Declaration
21263 and then Nkind (Decl) not in N_Renaming_Declaration
21264 and then Nkind (Decl) /= N_Abstract_Subprogram_Declaration
21265 then
21266 Error_Pragma
21267 ("pragma% misplaced, "
21268 & "must immediately follow a declaration");
21270 else
21271 Set_Obsolescent (Defining_Entity (Decl));
21272 return;
21273 end if;
21274 end if;
21275 end Obsolescent;
21277 --------------
21278 -- Optimize --
21279 --------------
21281 -- pragma Optimize (Time | Space | Off);
21283 -- The actual check for optimize is done in Gigi. Note that this
21284 -- pragma does not actually change the optimization setting, it
21285 -- simply checks that it is consistent with the pragma.
21287 when Pragma_Optimize =>
21288 Check_No_Identifiers;
21289 Check_Arg_Count (1);
21290 Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
21292 ------------------------
21293 -- Optimize_Alignment --
21294 ------------------------
21296 -- pragma Optimize_Alignment (Time | Space | Off);
21298 when Pragma_Optimize_Alignment => Optimize_Alignment : begin
21299 GNAT_Pragma;
21300 Check_No_Identifiers;
21301 Check_Arg_Count (1);
21302 Check_Valid_Configuration_Pragma;
21304 declare
21305 Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
21306 begin
21307 case Nam is
21308 when Name_Off => Opt.Optimize_Alignment := 'O';
21309 when Name_Space => Opt.Optimize_Alignment := 'S';
21310 when Name_Time => Opt.Optimize_Alignment := 'T';
21312 when others =>
21313 Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
21314 end case;
21315 end;
21317 -- Set indication that mode is set locally. If we are in fact in a
21318 -- configuration pragma file, this setting is harmless since the
21319 -- switch will get reset anyway at the start of each unit.
21321 Optimize_Alignment_Local := True;
21322 end Optimize_Alignment;
21324 -------------
21325 -- Ordered --
21326 -------------
21328 -- pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
21330 when Pragma_Ordered => Ordered : declare
21331 Assoc : constant Node_Id := Arg1;
21332 Type_Id : Node_Id;
21333 Typ : Entity_Id;
21335 begin
21336 GNAT_Pragma;
21337 Check_No_Identifiers;
21338 Check_Arg_Count (1);
21339 Check_Arg_Is_Local_Name (Arg1);
21341 Type_Id := Get_Pragma_Arg (Assoc);
21342 Find_Type (Type_Id);
21343 Typ := Entity (Type_Id);
21345 if Typ = Any_Type then
21346 return;
21347 else
21348 Typ := Underlying_Type (Typ);
21349 end if;
21351 if not Is_Enumeration_Type (Typ) then
21352 Error_Pragma ("pragma% must specify enumeration type");
21353 end if;
21355 Check_First_Subtype (Arg1);
21356 Set_Has_Pragma_Ordered (Base_Type (Typ));
21357 end Ordered;
21359 -------------------
21360 -- Overflow_Mode --
21361 -------------------
21363 -- pragma Overflow_Mode
21364 -- ([General => ] MODE [, [Assertions => ] MODE]);
21366 -- MODE := STRICT | MINIMIZED | ELIMINATED
21368 -- Note: ELIMINATED is allowed only if Long_Long_Integer'Size is 64
21369 -- since System.Bignums makes this assumption. This is true of nearly
21370 -- all (all?) targets.
21372 when Pragma_Overflow_Mode => Overflow_Mode : declare
21373 function Get_Overflow_Mode
21374 (Name : Name_Id;
21375 Arg : Node_Id) return Overflow_Mode_Type;
21376 -- Function to process one pragma argument, Arg. If an identifier
21377 -- is present, it must be Name. Mode type is returned if a valid
21378 -- argument exists, otherwise an error is signalled.
21380 -----------------------
21381 -- Get_Overflow_Mode --
21382 -----------------------
21384 function Get_Overflow_Mode
21385 (Name : Name_Id;
21386 Arg : Node_Id) return Overflow_Mode_Type
21388 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
21390 begin
21391 Check_Optional_Identifier (Arg, Name);
21392 Check_Arg_Is_Identifier (Argx);
21394 if Chars (Argx) = Name_Strict then
21395 return Strict;
21397 elsif Chars (Argx) = Name_Minimized then
21398 return Minimized;
21400 elsif Chars (Argx) = Name_Eliminated then
21401 if Ttypes.Standard_Long_Long_Integer_Size /= 64 then
21402 Error_Pragma_Arg
21403 ("Eliminated requires Long_Long_Integer'Size = 64",
21404 Argx);
21405 else
21406 return Eliminated;
21407 end if;
21409 else
21410 Error_Pragma_Arg ("invalid argument for pragma%", Argx);
21411 end if;
21412 end Get_Overflow_Mode;
21414 -- Start of processing for Overflow_Mode
21416 begin
21417 GNAT_Pragma;
21418 Check_At_Least_N_Arguments (1);
21419 Check_At_Most_N_Arguments (2);
21421 -- Process first argument
21423 Scope_Suppress.Overflow_Mode_General :=
21424 Get_Overflow_Mode (Name_General, Arg1);
21426 -- Case of only one argument
21428 if Arg_Count = 1 then
21429 Scope_Suppress.Overflow_Mode_Assertions :=
21430 Scope_Suppress.Overflow_Mode_General;
21432 -- Case of two arguments present
21434 else
21435 Scope_Suppress.Overflow_Mode_Assertions :=
21436 Get_Overflow_Mode (Name_Assertions, Arg2);
21437 end if;
21438 end Overflow_Mode;
21440 --------------------------
21441 -- Overriding Renamings --
21442 --------------------------
21444 -- pragma Overriding_Renamings;
21446 when Pragma_Overriding_Renamings =>
21447 GNAT_Pragma;
21448 Check_Arg_Count (0);
21449 Check_Valid_Configuration_Pragma;
21450 Overriding_Renamings := True;
21452 ----------
21453 -- Pack --
21454 ----------
21456 -- pragma Pack (first_subtype_LOCAL_NAME);
21458 when Pragma_Pack => Pack : declare
21459 Assoc : constant Node_Id := Arg1;
21460 Ctyp : Entity_Id;
21461 Ignore : Boolean := False;
21462 Typ : Entity_Id;
21463 Type_Id : Node_Id;
21465 begin
21466 Check_No_Identifiers;
21467 Check_Arg_Count (1);
21468 Check_Arg_Is_Local_Name (Arg1);
21469 Type_Id := Get_Pragma_Arg (Assoc);
21471 if not Is_Entity_Name (Type_Id)
21472 or else not Is_Type (Entity (Type_Id))
21473 then
21474 Error_Pragma_Arg
21475 ("argument for pragma% must be type or subtype", Arg1);
21476 end if;
21478 Find_Type (Type_Id);
21479 Typ := Entity (Type_Id);
21481 if Typ = Any_Type
21482 or else Rep_Item_Too_Early (Typ, N)
21483 then
21484 return;
21485 else
21486 Typ := Underlying_Type (Typ);
21487 end if;
21489 -- A pragma that applies to a Ghost entity becomes Ghost for the
21490 -- purposes of legality checks and removal of ignored Ghost code.
21492 Mark_Ghost_Pragma (N, Typ);
21494 if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
21495 Error_Pragma ("pragma% must specify array or record type");
21496 end if;
21498 Check_First_Subtype (Arg1);
21499 Check_Duplicate_Pragma (Typ);
21501 -- Array type
21503 if Is_Array_Type (Typ) then
21504 Ctyp := Component_Type (Typ);
21506 -- Ignore pack that does nothing
21508 if Known_Static_Esize (Ctyp)
21509 and then Known_Static_RM_Size (Ctyp)
21510 and then Esize (Ctyp) = RM_Size (Ctyp)
21511 and then Addressable (Esize (Ctyp))
21512 then
21513 Ignore := True;
21514 end if;
21516 -- Process OK pragma Pack. Note that if there is a separate
21517 -- component clause present, the Pack will be cancelled. This
21518 -- processing is in Freeze.
21520 if not Rep_Item_Too_Late (Typ, N) then
21522 -- In CodePeer mode, we do not need complex front-end
21523 -- expansions related to pragma Pack, so disable handling
21524 -- of pragma Pack.
21526 if CodePeer_Mode then
21527 null;
21529 -- Normal case where we do the pack action
21531 else
21532 if not Ignore then
21533 Set_Is_Packed (Base_Type (Typ));
21534 Set_Has_Non_Standard_Rep (Base_Type (Typ));
21535 end if;
21537 Set_Has_Pragma_Pack (Base_Type (Typ));
21538 end if;
21539 end if;
21541 -- For record types, the pack is always effective
21543 else pragma Assert (Is_Record_Type (Typ));
21544 if not Rep_Item_Too_Late (Typ, N) then
21545 Set_Is_Packed (Base_Type (Typ));
21546 Set_Has_Pragma_Pack (Base_Type (Typ));
21547 Set_Has_Non_Standard_Rep (Base_Type (Typ));
21548 end if;
21549 end if;
21550 end Pack;
21552 ----------
21553 -- Page --
21554 ----------
21556 -- pragma Page;
21558 -- There is nothing to do here, since we did all the processing for
21559 -- this pragma in Par.Prag (so that it works properly even in syntax
21560 -- only mode).
21562 when Pragma_Page =>
21563 null;
21565 -------------
21566 -- Part_Of --
21567 -------------
21569 -- pragma Part_Of (ABSTRACT_STATE);
21571 -- ABSTRACT_STATE ::= NAME
21573 when Pragma_Part_Of => Part_Of : declare
21574 procedure Propagate_Part_Of
21575 (Pack_Id : Entity_Id;
21576 State_Id : Entity_Id;
21577 Instance : Node_Id);
21578 -- Propagate the Part_Of indicator to all abstract states and
21579 -- objects declared in the visible state space of a package
21580 -- denoted by Pack_Id. State_Id is the encapsulating state.
21581 -- Instance is the package instantiation node.
21583 -----------------------
21584 -- Propagate_Part_Of --
21585 -----------------------
21587 procedure Propagate_Part_Of
21588 (Pack_Id : Entity_Id;
21589 State_Id : Entity_Id;
21590 Instance : Node_Id)
21592 Has_Item : Boolean := False;
21593 -- Flag set when the visible state space contains at least one
21594 -- abstract state or variable.
21596 procedure Propagate_Part_Of (Pack_Id : Entity_Id);
21597 -- Propagate the Part_Of indicator to all abstract states and
21598 -- objects declared in the visible state space of a package
21599 -- denoted by Pack_Id.
21601 -----------------------
21602 -- Propagate_Part_Of --
21603 -----------------------
21605 procedure Propagate_Part_Of (Pack_Id : Entity_Id) is
21606 Constits : Elist_Id;
21607 Item_Id : Entity_Id;
21609 begin
21610 -- Traverse the entity chain of the package and set relevant
21611 -- attributes of abstract states and objects declared in the
21612 -- visible state space of the package.
21614 Item_Id := First_Entity (Pack_Id);
21615 while Present (Item_Id)
21616 and then not In_Private_Part (Item_Id)
21617 loop
21618 -- Do not consider internally generated items
21620 if not Comes_From_Source (Item_Id) then
21621 null;
21623 -- Do not consider generic formals or their corresponding
21624 -- actuals because they are not part of a visible state.
21625 -- Note that both entities are marked as hidden.
21627 elsif Is_Hidden (Item_Id) then
21628 null;
21630 -- The Part_Of indicator turns an abstract state or an
21631 -- object into a constituent of the encapsulating state.
21632 -- Note that constants are considered here even though
21633 -- they may not depend on variable input. This check is
21634 -- left to the SPARK prover.
21636 elsif Ekind (Item_Id) in
21637 E_Abstract_State | E_Constant | E_Variable
21638 then
21639 Has_Item := True;
21640 Constits := Part_Of_Constituents (State_Id);
21642 if No (Constits) then
21643 Constits := New_Elmt_List;
21644 Set_Part_Of_Constituents (State_Id, Constits);
21645 end if;
21647 Append_Elmt (Item_Id, Constits);
21648 Set_Encapsulating_State (Item_Id, State_Id);
21650 -- Recursively handle nested packages and instantiations
21652 elsif Ekind (Item_Id) = E_Package then
21653 Propagate_Part_Of (Item_Id);
21654 end if;
21656 Next_Entity (Item_Id);
21657 end loop;
21658 end Propagate_Part_Of;
21660 -- Start of processing for Propagate_Part_Of
21662 begin
21663 Propagate_Part_Of (Pack_Id);
21665 -- Detect a package instantiation that is subject to a Part_Of
21666 -- indicator, but has no visible state.
21668 if not Has_Item then
21669 SPARK_Msg_NE
21670 ("package instantiation & has Part_Of indicator but "
21671 & "lacks visible state", Instance, Pack_Id);
21672 end if;
21673 end Propagate_Part_Of;
21675 -- Local variables
21677 Constits : Elist_Id;
21678 Encap : Node_Id;
21679 Encap_Id : Entity_Id;
21680 Item_Id : Entity_Id;
21681 Legal : Boolean;
21682 Stmt : Node_Id;
21684 -- Start of processing for Part_Of
21686 begin
21687 GNAT_Pragma;
21688 Check_No_Identifiers;
21689 Check_Arg_Count (1);
21691 Stmt := Find_Related_Context (N, Do_Checks => True);
21693 -- Object declaration
21695 if Nkind (Stmt) = N_Object_Declaration then
21696 null;
21698 -- Package instantiation
21700 elsif Nkind (Stmt) = N_Package_Instantiation then
21701 null;
21703 -- Single concurrent type declaration
21705 elsif Is_Single_Concurrent_Type_Declaration (Stmt) then
21706 null;
21708 -- Otherwise the pragma is associated with an illegal construct
21710 else
21711 Pragma_Misplaced;
21712 end if;
21714 -- Extract the entity of the related object declaration or package
21715 -- instantiation. In the case of the instantiation, use the entity
21716 -- of the instance spec.
21718 if Nkind (Stmt) = N_Package_Instantiation then
21719 Stmt := Instance_Spec (Stmt);
21720 end if;
21722 Item_Id := Defining_Entity (Stmt);
21724 -- A pragma that applies to a Ghost entity becomes Ghost for the
21725 -- purposes of legality checks and removal of ignored Ghost code.
21727 Mark_Ghost_Pragma (N, Item_Id);
21729 -- Chain the pragma on the contract for further processing by
21730 -- Analyze_Part_Of_In_Decl_Part or for completeness.
21732 Add_Contract_Item (N, Item_Id);
21734 -- A variable may act as constituent of a single concurrent type
21735 -- which in turn could be declared after the variable. Due to this
21736 -- discrepancy, the full analysis of indicator Part_Of is delayed
21737 -- until the end of the enclosing declarative region (see routine
21738 -- Analyze_Part_Of_In_Decl_Part).
21740 if Ekind (Item_Id) = E_Variable then
21741 null;
21743 -- Otherwise indicator Part_Of applies to a constant or a package
21744 -- instantiation.
21746 else
21747 Encap := Get_Pragma_Arg (Arg1);
21749 -- Detect any discrepancies between the placement of the
21750 -- constant or package instantiation with respect to state
21751 -- space and the encapsulating state.
21753 Analyze_Part_Of
21754 (Indic => N,
21755 Item_Id => Item_Id,
21756 Encap => Encap,
21757 Encap_Id => Encap_Id,
21758 Legal => Legal);
21760 if Legal then
21761 pragma Assert (Present (Encap_Id));
21763 if Ekind (Item_Id) = E_Constant then
21764 Constits := Part_Of_Constituents (Encap_Id);
21766 if No (Constits) then
21767 Constits := New_Elmt_List;
21768 Set_Part_Of_Constituents (Encap_Id, Constits);
21769 end if;
21771 Append_Elmt (Item_Id, Constits);
21772 Set_Encapsulating_State (Item_Id, Encap_Id);
21774 -- Propagate the Part_Of indicator to the visible state
21775 -- space of the package instantiation.
21777 else
21778 Propagate_Part_Of
21779 (Pack_Id => Item_Id,
21780 State_Id => Encap_Id,
21781 Instance => Stmt);
21782 end if;
21783 end if;
21784 end if;
21785 end Part_Of;
21787 ----------------------------------
21788 -- Partition_Elaboration_Policy --
21789 ----------------------------------
21791 -- pragma Partition_Elaboration_Policy (policy_IDENTIFIER);
21793 when Pragma_Partition_Elaboration_Policy => PEP : declare
21794 subtype PEP_Range is Name_Id
21795 range First_Partition_Elaboration_Policy_Name
21796 .. Last_Partition_Elaboration_Policy_Name;
21797 PEP_Val : PEP_Range;
21798 PEP : Character;
21800 begin
21801 Ada_2005_Pragma;
21802 Check_Arg_Count (1);
21803 Check_No_Identifiers;
21804 Check_Arg_Is_Partition_Elaboration_Policy (Arg1);
21805 Check_Valid_Configuration_Pragma;
21806 PEP_Val := Chars (Get_Pragma_Arg (Arg1));
21808 case PEP_Val is
21809 when Name_Concurrent => PEP := 'C';
21810 when Name_Sequential => PEP := 'S';
21811 end case;
21813 if Partition_Elaboration_Policy /= ' '
21814 and then Partition_Elaboration_Policy /= PEP
21815 then
21816 Error_Msg_Sloc := Partition_Elaboration_Policy_Sloc;
21817 Error_Pragma
21818 ("partition elaboration policy incompatible with policy#");
21820 -- Set new policy, but always preserve System_Location since we
21821 -- like the error message with the run time name.
21823 else
21824 Partition_Elaboration_Policy := PEP;
21826 if Partition_Elaboration_Policy_Sloc /= System_Location then
21827 Partition_Elaboration_Policy_Sloc := Loc;
21828 end if;
21830 if PEP_Val = Name_Sequential
21831 and then not Restriction_Active (No_Task_Hierarchy)
21832 then
21833 -- RM H.6(6) guarantees that No_Task_Hierarchy will be
21834 -- set eventually, so take advantage of that knowledge now.
21835 -- But we have to do this in a tricky way. If we simply
21836 -- set the No_Task_Hierarchy restriction here, then the
21837 -- assumption that the restriction will be set eventually
21838 -- becomes a self-fulfilling prophecy; the binder can
21839 -- then mistakenly conclude that the H.6(6) rule is
21840 -- satisified in cases where the post-compilation check
21841 -- should fail. So we invent a new restriction,
21842 -- No_Task_Hierarchy_Implicit, which is treated specially
21843 -- in the function Restriction_Active.
21845 Set_Restriction (No_Task_Hierarchy_Implicit, N);
21846 pragma Assert (Restriction_Active (No_Task_Hierarchy));
21847 end if;
21848 end if;
21849 end PEP;
21851 -------------
21852 -- Passive --
21853 -------------
21855 -- pragma Passive [(PASSIVE_FORM)];
21857 -- PASSIVE_FORM ::= Semaphore | No
21859 when Pragma_Passive =>
21860 GNAT_Pragma;
21862 if Nkind (Parent (N)) /= N_Task_Definition then
21863 Error_Pragma ("pragma% must be within task definition");
21864 end if;
21866 if Arg_Count /= 0 then
21867 Check_Arg_Count (1);
21868 Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
21869 end if;
21871 ----------------------------------
21872 -- Preelaborable_Initialization --
21873 ----------------------------------
21875 -- pragma Preelaborable_Initialization (DIRECT_NAME);
21877 when Pragma_Preelaborable_Initialization => Preelab_Init : declare
21878 Ent : Entity_Id;
21880 begin
21881 Ada_2005_Pragma;
21882 Check_Arg_Count (1);
21883 Check_No_Identifiers;
21884 Check_Arg_Is_Identifier (Arg1);
21885 Check_Arg_Is_Local_Name (Arg1);
21886 Check_First_Subtype (Arg1);
21887 Ent := Entity (Get_Pragma_Arg (Arg1));
21889 -- A pragma that applies to a Ghost entity becomes Ghost for the
21890 -- purposes of legality checks and removal of ignored Ghost code.
21892 Mark_Ghost_Pragma (N, Ent);
21894 -- The pragma may come from an aspect on a private declaration,
21895 -- even if the freeze point at which this is analyzed in the
21896 -- private part after the full view.
21898 if Has_Private_Declaration (Ent)
21899 and then From_Aspect_Specification (N)
21900 then
21901 null;
21903 -- Check appropriate type argument
21905 elsif Is_Private_Type (Ent)
21906 or else Is_Protected_Type (Ent)
21907 or else (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent))
21909 -- AI05-0028: The pragma applies to all composite types. Note
21910 -- that we apply this binding interpretation to earlier versions
21911 -- of Ada, so there is no Ada 2012 guard. Seems a reasonable
21912 -- choice since there are other compilers that do the same.
21914 or else Is_Composite_Type (Ent)
21915 then
21916 null;
21918 else
21919 Error_Pragma_Arg
21920 ("pragma % can only be applied to private, formal derived, "
21921 & "protected, or composite type", Arg1);
21922 end if;
21924 -- Give an error if the pragma is applied to a protected type that
21925 -- does not qualify (due to having entries, or due to components
21926 -- that do not qualify).
21928 if Is_Protected_Type (Ent)
21929 and then not Has_Preelaborable_Initialization (Ent)
21930 then
21931 Error_Msg_N
21932 ("protected type & does not have preelaborable "
21933 & "initialization", Ent);
21935 -- Otherwise mark the type as definitely having preelaborable
21936 -- initialization.
21938 else
21939 Set_Known_To_Have_Preelab_Init (Ent);
21940 end if;
21942 if Has_Pragma_Preelab_Init (Ent)
21943 and then Warn_On_Redundant_Constructs
21944 then
21945 Error_Pragma ("?r?duplicate pragma%!");
21946 else
21947 Set_Has_Pragma_Preelab_Init (Ent);
21948 end if;
21949 end Preelab_Init;
21951 --------------------
21952 -- Persistent_BSS --
21953 --------------------
21955 -- pragma Persistent_BSS [(object_NAME)];
21957 when Pragma_Persistent_BSS => Persistent_BSS : declare
21958 Decl : Node_Id;
21959 Ent : Entity_Id;
21960 Prag : Node_Id;
21962 begin
21963 GNAT_Pragma;
21964 Check_At_Most_N_Arguments (1);
21966 -- Case of application to specific object (one argument)
21968 if Arg_Count = 1 then
21969 Check_Arg_Is_Library_Level_Local_Name (Arg1);
21971 if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
21972 or else
21973 Ekind (Entity (Get_Pragma_Arg (Arg1))) not in
21974 E_Variable | E_Constant
21975 then
21976 Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
21977 end if;
21979 Ent := Entity (Get_Pragma_Arg (Arg1));
21981 -- A pragma that applies to a Ghost entity becomes Ghost for
21982 -- the purposes of legality checks and removal of ignored Ghost
21983 -- code.
21985 Mark_Ghost_Pragma (N, Ent);
21987 -- Check for duplication before inserting in list of
21988 -- representation items.
21990 Check_Duplicate_Pragma (Ent);
21992 if Rep_Item_Too_Late (Ent, N) then
21993 return;
21994 end if;
21996 Decl := Parent (Ent);
21998 if Present (Expression (Decl)) then
21999 -- Variables in Persistent_BSS cannot be initialized, so
22000 -- turn off any initialization that might be caused by
22001 -- pragmas Initialize_Scalars or Normalize_Scalars.
22003 if Kill_Range_Check (Expression (Decl)) then
22004 Prag :=
22005 Make_Pragma (Loc,
22006 Name_Suppress_Initialization,
22007 Pragma_Argument_Associations => New_List (
22008 Make_Pragma_Argument_Association (Loc,
22009 Expression => New_Occurrence_Of (Ent, Loc))));
22010 Insert_Before (N, Prag);
22011 Analyze (Prag);
22013 else
22014 Error_Pragma_Arg
22015 ("object for pragma% cannot have initialization", Arg1);
22016 end if;
22017 end if;
22019 if not Is_Potentially_Persistent_Type (Etype (Ent)) then
22020 Error_Pragma_Arg
22021 ("object type for pragma% is not potentially persistent",
22022 Arg1);
22023 end if;
22025 Prag :=
22026 Make_Linker_Section_Pragma
22027 (Ent, Loc, ".persistent.bss");
22028 Insert_After (N, Prag);
22029 Analyze (Prag);
22031 -- Case of use as configuration pragma with no arguments
22033 else
22034 Check_Valid_Configuration_Pragma;
22035 Persistent_BSS_Mode := True;
22036 end if;
22037 end Persistent_BSS;
22039 --------------------
22040 -- Rename_Pragma --
22041 --------------------
22043 -- pragma Rename_Pragma (
22044 -- [New_Name =>] IDENTIFIER,
22045 -- [Renamed =>] pragma_IDENTIFIER);
22047 when Pragma_Rename_Pragma => Rename_Pragma : declare
22048 New_Name : constant Node_Id := Get_Pragma_Arg (Arg1);
22049 Old_Name : constant Node_Id := Get_Pragma_Arg (Arg2);
22051 begin
22052 GNAT_Pragma;
22053 Check_Valid_Configuration_Pragma;
22054 Check_Arg_Count (2);
22055 Check_Optional_Identifier (Arg1, Name_New_Name);
22056 Check_Optional_Identifier (Arg2, Name_Renamed);
22058 if Nkind (New_Name) /= N_Identifier then
22059 Error_Pragma_Arg ("identifier expected", Arg1);
22060 end if;
22062 if Nkind (Old_Name) /= N_Identifier then
22063 Error_Pragma_Arg ("identifier expected", Arg2);
22064 end if;
22066 -- The New_Name arg should not be an existing pragma (but we allow
22067 -- it; it's just a warning). The Old_Name arg must be an existing
22068 -- pragma.
22070 if Is_Pragma_Name (Chars (New_Name)) then
22071 Error_Pragma_Arg ("??pragma is already defined", Arg1);
22072 end if;
22074 if not Is_Pragma_Name (Chars (Old_Name)) then
22075 Error_Pragma_Arg ("existing pragma name expected", Arg1);
22076 end if;
22078 Map_Pragma_Name (From => Chars (New_Name), To => Chars (Old_Name));
22079 end Rename_Pragma;
22081 -----------------------------------
22082 -- Post/Post_Class/Postcondition --
22083 -----------------------------------
22085 -- pragma Post (Boolean_EXPRESSION);
22086 -- pragma Post_Class (Boolean_EXPRESSION);
22087 -- pragma Postcondition ([Check =>] Boolean_EXPRESSION
22088 -- [,[Message =>] String_EXPRESSION]);
22090 -- Characteristics:
22092 -- * Analysis - The annotation undergoes initial checks to verify
22093 -- the legal placement and context. Secondary checks preanalyze the
22094 -- expression in:
22096 -- Analyze_Pre_Post_Condition_In_Decl_Part
22098 -- * Expansion - The annotation is expanded during the expansion of
22099 -- the related subprogram [body] contract as performed in:
22101 -- Expand_Subprogram_Contract
22103 -- * Template - The annotation utilizes the generic template of the
22104 -- related subprogram [body] when it is:
22106 -- aspect on subprogram declaration
22107 -- aspect on stand-alone subprogram body
22108 -- pragma on stand-alone subprogram body
22110 -- The annotation must prepare its own template when it is:
22112 -- pragma on subprogram declaration
22114 -- * Globals - Capture of global references must occur after full
22115 -- analysis.
22117 -- * Instance - The annotation is instantiated automatically when
22118 -- the related generic subprogram [body] is instantiated except for
22119 -- the "pragma on subprogram declaration" case. In that scenario
22120 -- the annotation must instantiate itself.
22122 when Pragma_Post
22123 | Pragma_Post_Class
22124 | Pragma_Postcondition
22126 Analyze_Pre_Post_Condition;
22128 --------------------------------
22129 -- Pre/Pre_Class/Precondition --
22130 --------------------------------
22132 -- pragma Pre (Boolean_EXPRESSION);
22133 -- pragma Pre_Class (Boolean_EXPRESSION);
22134 -- pragma Precondition ([Check =>] Boolean_EXPRESSION
22135 -- [,[Message =>] String_EXPRESSION]);
22137 -- Characteristics:
22139 -- * Analysis - The annotation undergoes initial checks to verify
22140 -- the legal placement and context. Secondary checks preanalyze the
22141 -- expression in:
22143 -- Analyze_Pre_Post_Condition_In_Decl_Part
22145 -- * Expansion - The annotation is expanded during the expansion of
22146 -- the related subprogram [body] contract as performed in:
22148 -- Expand_Subprogram_Contract
22150 -- * Template - The annotation utilizes the generic template of the
22151 -- related subprogram [body] when it is:
22153 -- aspect on subprogram declaration
22154 -- aspect on stand-alone subprogram body
22155 -- pragma on stand-alone subprogram body
22157 -- The annotation must prepare its own template when it is:
22159 -- pragma on subprogram declaration
22161 -- * Globals - Capture of global references must occur after full
22162 -- analysis.
22164 -- * Instance - The annotation is instantiated automatically when
22165 -- the related generic subprogram [body] is instantiated except for
22166 -- the "pragma on subprogram declaration" case. In that scenario
22167 -- the annotation must instantiate itself.
22169 when Pragma_Pre
22170 | Pragma_Pre_Class
22171 | Pragma_Precondition
22173 Analyze_Pre_Post_Condition;
22175 ---------------
22176 -- Predicate --
22177 ---------------
22179 -- pragma Predicate
22180 -- ([Entity =>] type_LOCAL_NAME,
22181 -- [Check =>] boolean_EXPRESSION);
22183 when Pragma_Predicate => Predicate : declare
22184 Discard : Boolean;
22185 Typ : Entity_Id;
22186 Type_Id : Node_Id;
22188 begin
22189 GNAT_Pragma;
22190 Check_Arg_Count (2);
22191 Check_Optional_Identifier (Arg1, Name_Entity);
22192 Check_Optional_Identifier (Arg2, Name_Check);
22194 Check_Arg_Is_Local_Name (Arg1);
22196 Type_Id := Get_Pragma_Arg (Arg1);
22197 Find_Type (Type_Id);
22198 Typ := Entity (Type_Id);
22200 if Typ = Any_Type then
22201 return;
22202 end if;
22204 -- A Ghost_Predicate aspect is always Ghost with a mode inherited
22205 -- from the context. A Predicate pragma that applies to a Ghost
22206 -- entity becomes Ghost for the purposes of legality checks and
22207 -- removal of ignored Ghost code.
22209 if From_Aspect_Specification (N)
22210 and then Get_Aspect_Id
22211 (Chars (Identifier (Corresponding_Aspect (N))))
22212 = Aspect_Ghost_Predicate
22213 then
22214 Mark_Ghost_Pragma
22215 (N, Name_To_Ghost_Mode (Policy_In_Effect (Name_Ghost)));
22216 else
22217 Mark_Ghost_Pragma (N, Typ);
22218 end if;
22220 -- The remaining processing is simply to link the pragma on to
22221 -- the rep item chain, for processing when the type is frozen.
22222 -- This is accomplished by a call to Rep_Item_Too_Late. We also
22223 -- mark the type as having predicates.
22225 -- If the current policy for predicate checking is Ignore mark the
22226 -- subtype accordingly. In the case of predicates we consider them
22227 -- enabled unless Ignore is specified (either directly or with a
22228 -- general Assertion_Policy pragma) to preserve existing warnings.
22230 Set_Has_Predicates (Typ);
22232 -- Indicate that the pragma must be processed at the point the
22233 -- type is frozen, as is done for the corresponding aspect.
22235 Set_Has_Delayed_Aspects (Typ);
22236 Set_Has_Delayed_Freeze (Typ);
22238 Set_Predicates_Ignored (Typ,
22239 Policy_In_Effect (Name_Dynamic_Predicate) = Name_Ignore);
22240 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
22241 end Predicate;
22243 -----------------------
22244 -- Predicate_Failure --
22245 -----------------------
22247 -- pragma Predicate_Failure
22248 -- ([Entity =>] type_LOCAL_NAME,
22249 -- [Message =>] string_EXPRESSION);
22251 when Pragma_Predicate_Failure => Predicate_Failure : declare
22252 Discard : Boolean;
22253 Typ : Entity_Id;
22254 Type_Id : Node_Id;
22256 begin
22257 GNAT_Pragma;
22258 Check_Arg_Count (2);
22259 Check_Optional_Identifier (Arg1, Name_Entity);
22260 Check_Optional_Identifier (Arg2, Name_Message);
22262 Check_Arg_Is_Local_Name (Arg1);
22264 Type_Id := Get_Pragma_Arg (Arg1);
22265 Find_Type (Type_Id);
22266 Typ := Entity (Type_Id);
22268 if Typ = Any_Type then
22269 return;
22270 end if;
22272 -- A pragma that applies to a Ghost entity becomes Ghost for the
22273 -- purposes of legality checks and removal of ignored Ghost code.
22275 Mark_Ghost_Pragma (N, Typ);
22277 -- The remaining processing is simply to link the pragma on to
22278 -- the rep item chain, for processing when the type is frozen.
22279 -- This is accomplished by a call to Rep_Item_Too_Late.
22281 Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
22282 end Predicate_Failure;
22284 ------------------
22285 -- Preelaborate --
22286 ------------------
22288 -- pragma Preelaborate [(library_unit_NAME)];
22290 -- Set the flag Is_Preelaborated of program unit name entity
22292 when Pragma_Preelaborate => Preelaborate : declare
22293 Pa : constant Node_Id := Parent (N);
22294 Pk : constant Node_Kind := Nkind (Pa);
22295 Ent : Entity_Id;
22297 begin
22298 Check_Ada_83_Warning;
22299 Check_Valid_Library_Unit_Pragma;
22301 -- If N was rewritten as a null statement there is nothing more
22302 -- to do.
22304 if Nkind (N) = N_Null_Statement then
22305 return;
22306 end if;
22308 Ent := Find_Lib_Unit_Name;
22310 -- A pragma that applies to a Ghost entity becomes Ghost for the
22311 -- purposes of legality checks and removal of ignored Ghost code.
22313 Mark_Ghost_Pragma (N, Ent);
22314 Check_Duplicate_Pragma (Ent);
22316 -- This filters out pragmas inside generic parents that show up
22317 -- inside instantiations. Pragmas that come from aspects in the
22318 -- unit are not ignored.
22320 if Present (Ent) then
22321 if Pk = N_Package_Specification
22322 and then Present (Generic_Parent (Pa))
22323 and then not From_Aspect_Specification (N)
22324 then
22325 null;
22327 else
22328 if not Debug_Flag_U then
22329 Set_Is_Preelaborated (Ent);
22331 if Legacy_Elaboration_Checks then
22332 Set_Suppress_Elaboration_Warnings (Ent);
22333 end if;
22334 end if;
22335 end if;
22336 end if;
22337 end Preelaborate;
22339 -------------------------------
22340 -- Prefix_Exception_Messages --
22341 -------------------------------
22343 -- pragma Prefix_Exception_Messages;
22345 when Pragma_Prefix_Exception_Messages =>
22346 GNAT_Pragma;
22347 Check_Valid_Configuration_Pragma;
22348 Check_Arg_Count (0);
22349 Prefix_Exception_Messages := True;
22351 --------------
22352 -- Priority --
22353 --------------
22355 -- pragma Priority (EXPRESSION);
22357 when Pragma_Priority => Priority : declare
22358 P : constant Node_Id := Parent (N);
22359 Arg : Node_Id;
22360 Ent : Entity_Id;
22362 begin
22363 Check_No_Identifiers;
22364 Check_Arg_Count (1);
22366 -- Subprogram case
22368 if Nkind (P) = N_Subprogram_Body then
22369 Check_In_Main_Program;
22371 Ent := Defining_Unit_Name (Specification (P));
22373 if Nkind (Ent) = N_Defining_Program_Unit_Name then
22374 Ent := Defining_Identifier (Ent);
22375 end if;
22377 Arg := Get_Pragma_Arg (Arg1);
22378 Analyze_And_Resolve (Arg, Standard_Integer);
22380 -- Must be static
22382 if not Is_OK_Static_Expression (Arg) then
22383 Flag_Non_Static_Expr
22384 ("main subprogram priority is not static!", Arg);
22385 raise Pragma_Exit;
22387 -- If constraint error, then we already signalled an error
22389 elsif Raises_Constraint_Error (Arg) then
22390 null;
22392 -- Otherwise check in range except if Relaxed_RM_Semantics
22393 -- where we ignore the value if out of range.
22395 else
22396 if not Relaxed_RM_Semantics
22397 and then not Is_In_Range (Arg, RTE (RE_Priority))
22398 then
22399 Error_Pragma_Arg
22400 ("main subprogram priority is out of range", Arg1);
22401 else
22402 Set_Main_Priority
22403 (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
22404 end if;
22405 end if;
22407 -- Load an arbitrary entity from System.Tasking.Stages or
22408 -- System.Tasking.Restricted.Stages (depending on the
22409 -- supported profile) to make sure that one of these packages
22410 -- is implicitly with'ed, since we need to have the tasking
22411 -- run time active for the pragma Priority to have any effect.
22412 -- Previously we with'ed the package System.Tasking, but this
22413 -- package does not trigger the required initialization of the
22414 -- run-time library.
22416 if Restricted_Profile then
22417 Discard_Node (RTE (RE_Activate_Restricted_Tasks));
22418 else
22419 Discard_Node (RTE (RE_Activate_Tasks));
22420 end if;
22422 -- Task or Protected, must be of type Integer
22424 elsif Nkind (P) in N_Protected_Definition | N_Task_Definition then
22425 Arg := Get_Pragma_Arg (Arg1);
22426 Ent := Defining_Identifier (Parent (P));
22428 -- The expression must be analyzed in the special manner
22429 -- described in "Handling of Default and Per-Object
22430 -- Expressions" in sem.ads.
22432 Preanalyze_Spec_Expression (Arg, RTE (RE_Any_Priority));
22434 if not Is_OK_Static_Expression (Arg) then
22435 Check_Restriction (Static_Priorities, Arg);
22436 end if;
22438 -- Anything else is incorrect
22440 else
22441 Pragma_Misplaced;
22442 end if;
22444 -- Check duplicate pragma before we chain the pragma in the Rep
22445 -- Item chain of Ent.
22447 Check_Duplicate_Pragma (Ent);
22448 Record_Rep_Item (Ent, N);
22449 end Priority;
22451 -----------------------------------
22452 -- Priority_Specific_Dispatching --
22453 -----------------------------------
22455 -- pragma Priority_Specific_Dispatching (
22456 -- policy_IDENTIFIER,
22457 -- first_priority_EXPRESSION,
22458 -- last_priority_EXPRESSION);
22460 when Pragma_Priority_Specific_Dispatching =>
22461 Priority_Specific_Dispatching : declare
22462 Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
22463 -- This is the entity System.Any_Priority;
22465 DP : Character;
22466 Lower_Bound : Node_Id;
22467 Upper_Bound : Node_Id;
22468 Lower_Val : Uint;
22469 Upper_Val : Uint;
22471 begin
22472 Ada_2005_Pragma;
22473 Check_Arg_Count (3);
22474 Check_No_Identifiers;
22475 Check_Arg_Is_Task_Dispatching_Policy (Arg1);
22476 Check_Valid_Configuration_Pragma;
22477 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
22478 DP := Fold_Upper (Name_Buffer (1));
22480 Lower_Bound := Get_Pragma_Arg (Arg2);
22481 Check_Arg_Is_OK_Static_Expression (Lower_Bound, Standard_Integer);
22482 Lower_Val := Expr_Value (Lower_Bound);
22484 Upper_Bound := Get_Pragma_Arg (Arg3);
22485 Check_Arg_Is_OK_Static_Expression (Upper_Bound, Standard_Integer);
22486 Upper_Val := Expr_Value (Upper_Bound);
22488 -- It is not allowed to use Task_Dispatching_Policy and
22489 -- Priority_Specific_Dispatching in the same partition.
22491 if Task_Dispatching_Policy /= ' ' then
22492 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
22493 Error_Pragma
22494 ("pragma% incompatible with Task_Dispatching_Policy#");
22496 -- Check lower bound in range
22498 elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
22499 or else
22500 Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
22501 then
22502 Error_Pragma_Arg
22503 ("first_priority is out of range", Arg2);
22505 -- Check upper bound in range
22507 elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
22508 or else
22509 Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
22510 then
22511 Error_Pragma_Arg
22512 ("last_priority is out of range", Arg3);
22514 -- Check that the priority range is valid
22516 elsif Lower_Val > Upper_Val then
22517 Error_Pragma
22518 ("last_priority_expression must be greater than or equal to "
22519 & "first_priority_expression");
22521 -- Store the new policy, but always preserve System_Location since
22522 -- we like the error message with the run-time name.
22524 else
22525 -- Check overlapping in the priority ranges specified in other
22526 -- Priority_Specific_Dispatching pragmas within the same
22527 -- partition. We can only check those we know about.
22529 for J in
22530 Specific_Dispatching.First .. Specific_Dispatching.Last
22531 loop
22532 if Specific_Dispatching.Table (J).First_Priority in
22533 UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
22534 or else Specific_Dispatching.Table (J).Last_Priority in
22535 UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
22536 then
22537 Error_Msg_Sloc :=
22538 Specific_Dispatching.Table (J).Pragma_Loc;
22539 Error_Pragma
22540 ("priority range overlaps with "
22541 & "Priority_Specific_Dispatching#");
22542 end if;
22543 end loop;
22545 -- The use of Priority_Specific_Dispatching is incompatible
22546 -- with Task_Dispatching_Policy.
22548 if Task_Dispatching_Policy /= ' ' then
22549 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
22550 Error_Pragma
22551 ("Priority_Specific_Dispatching incompatible "
22552 & "with Task_Dispatching_Policy#");
22553 end if;
22555 -- The use of Priority_Specific_Dispatching forces ceiling
22556 -- locking policy.
22558 if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
22559 Error_Msg_Sloc := Locking_Policy_Sloc;
22560 Error_Pragma
22561 ("Priority_Specific_Dispatching incompatible "
22562 & "with Locking_Policy#");
22564 -- Set the Ceiling_Locking policy, but preserve System_Location
22565 -- since we like the error message with the run time name.
22567 else
22568 Locking_Policy := 'C';
22570 if Locking_Policy_Sloc /= System_Location then
22571 Locking_Policy_Sloc := Loc;
22572 end if;
22573 end if;
22575 -- Add entry in the table
22577 Specific_Dispatching.Append
22578 ((Dispatching_Policy => DP,
22579 First_Priority => UI_To_Int (Lower_Val),
22580 Last_Priority => UI_To_Int (Upper_Val),
22581 Pragma_Loc => Loc));
22582 end if;
22583 end Priority_Specific_Dispatching;
22585 -------------
22586 -- Profile --
22587 -------------
22589 -- pragma Profile (profile_IDENTIFIER);
22591 -- profile_IDENTIFIER => Restricted | Ravenscar | Rational
22593 when Pragma_Profile =>
22594 Ada_2005_Pragma;
22595 Check_Arg_Count (1);
22596 Check_Valid_Configuration_Pragma;
22597 Check_No_Identifiers;
22599 declare
22600 Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
22602 begin
22603 if Nkind (Argx) /= N_Identifier then
22604 Error_Msg_N
22605 ("argument of pragma Profile must be an identifier", N);
22607 elsif Chars (Argx) = Name_Ravenscar then
22608 Set_Ravenscar_Profile (Ravenscar, N);
22610 elsif Chars (Argx) = Name_Jorvik then
22611 Set_Ravenscar_Profile (Jorvik, N);
22613 elsif Chars (Argx) = Name_Gnat_Extended_Ravenscar then
22614 Set_Ravenscar_Profile (GNAT_Extended_Ravenscar, N);
22616 elsif Chars (Argx) = Name_Gnat_Ravenscar_EDF then
22617 Set_Ravenscar_Profile (GNAT_Ravenscar_EDF, N);
22619 elsif Chars (Argx) = Name_Restricted then
22620 Set_Profile_Restrictions
22621 (Restricted,
22622 N, Warn => Treat_Restrictions_As_Warnings);
22624 elsif Chars (Argx) = Name_Rational then
22625 Set_Rational_Profile;
22627 elsif Chars (Argx) = Name_No_Implementation_Extensions then
22628 Set_Profile_Restrictions
22629 (No_Implementation_Extensions,
22630 N, Warn => Treat_Restrictions_As_Warnings);
22632 else
22633 Error_Pragma_Arg ("& is not a valid profile", Argx);
22634 end if;
22635 end;
22637 ----------------------
22638 -- Profile_Warnings --
22639 ----------------------
22641 -- pragma Profile_Warnings (profile_IDENTIFIER);
22643 -- profile_IDENTIFIER => Restricted | Ravenscar
22645 when Pragma_Profile_Warnings =>
22646 GNAT_Pragma;
22647 Check_Arg_Count (1);
22648 Check_Valid_Configuration_Pragma;
22649 Check_No_Identifiers;
22651 declare
22652 Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
22654 begin
22655 if Chars (Argx) = Name_Ravenscar then
22656 Set_Profile_Restrictions (Ravenscar, N, Warn => True);
22658 elsif Chars (Argx) = Name_Restricted then
22659 Set_Profile_Restrictions (Restricted, N, Warn => True);
22661 elsif Chars (Argx) = Name_No_Implementation_Extensions then
22662 Set_Profile_Restrictions
22663 (No_Implementation_Extensions, N, Warn => True);
22665 else
22666 Error_Pragma_Arg ("& is not a valid profile", Argx);
22667 end if;
22668 end;
22670 --------------------------
22671 -- Propagate_Exceptions --
22672 --------------------------
22674 -- pragma Propagate_Exceptions;
22676 -- Note: this pragma is obsolete and has no effect
22678 when Pragma_Propagate_Exceptions =>
22679 GNAT_Pragma;
22680 Check_Arg_Count (0);
22682 if Warn_On_Obsolescent_Feature then
22683 Error_Msg_N
22684 ("'G'N'A'T pragma Propagate'_Exceptions is now obsolete " &
22685 "and has no effect?j?", N);
22686 end if;
22688 -----------------------------
22689 -- Provide_Shift_Operators --
22690 -----------------------------
22692 -- pragma Provide_Shift_Operators (integer_subtype_LOCAL_NAME);
22694 when Pragma_Provide_Shift_Operators =>
22695 Provide_Shift_Operators : declare
22696 Ent : Entity_Id;
22698 procedure Declare_Shift_Operator (Nam : Name_Id);
22699 -- Insert declaration and pragma Instrinsic for named shift op
22701 ----------------------------
22702 -- Declare_Shift_Operator --
22703 ----------------------------
22705 procedure Declare_Shift_Operator (Nam : Name_Id) is
22706 Func : Node_Id;
22707 Import : Node_Id;
22709 begin
22710 Func :=
22711 Make_Subprogram_Declaration (Loc,
22712 Make_Function_Specification (Loc,
22713 Defining_Unit_Name =>
22714 Make_Defining_Identifier (Loc, Chars => Nam),
22716 Result_Definition =>
22717 Make_Identifier (Loc, Chars => Chars (Ent)),
22719 Parameter_Specifications => New_List (
22720 Make_Parameter_Specification (Loc,
22721 Defining_Identifier =>
22722 Make_Defining_Identifier (Loc, Name_Value),
22723 Parameter_Type =>
22724 Make_Identifier (Loc, Chars => Chars (Ent))),
22726 Make_Parameter_Specification (Loc,
22727 Defining_Identifier =>
22728 Make_Defining_Identifier (Loc, Name_Amount),
22729 Parameter_Type =>
22730 New_Occurrence_Of (Standard_Natural, Loc)))));
22732 Import :=
22733 Make_Pragma (Loc,
22734 Chars => Name_Import,
22735 Pragma_Argument_Associations => New_List (
22736 Make_Pragma_Argument_Association (Loc,
22737 Expression => Make_Identifier (Loc, Name_Intrinsic)),
22738 Make_Pragma_Argument_Association (Loc,
22739 Expression => Make_Identifier (Loc, Nam))));
22741 Insert_After (N, Import);
22742 Insert_After (N, Func);
22743 end Declare_Shift_Operator;
22745 -- Start of processing for Provide_Shift_Operators
22747 begin
22748 GNAT_Pragma;
22749 Check_Arg_Count (1);
22750 Check_Arg_Is_Local_Name (Arg1);
22752 Arg1 := Get_Pragma_Arg (Arg1);
22754 -- We must have an entity name
22756 if not Is_Entity_Name (Arg1) then
22757 Error_Pragma_Arg
22758 ("pragma % must apply to integer first subtype", Arg1);
22759 end if;
22761 -- If no Entity, means there was a prior error so ignore
22763 if Present (Entity (Arg1)) then
22764 Ent := Entity (Arg1);
22766 -- Apply error checks
22768 if not Is_First_Subtype (Ent) then
22769 Error_Pragma_Arg
22770 ("cannot apply pragma %",
22771 "\& is not a first subtype",
22772 Arg1);
22774 elsif not Is_Integer_Type (Ent) then
22775 Error_Pragma_Arg
22776 ("cannot apply pragma %",
22777 "\& is not an integer type",
22778 Arg1);
22780 elsif Has_Shift_Operator (Ent) then
22781 Error_Pragma_Arg
22782 ("cannot apply pragma %",
22783 "\& already has declared shift operators",
22784 Arg1);
22786 elsif Is_Frozen (Ent) then
22787 Error_Pragma_Arg
22788 ("pragma % appears too late",
22789 "\& is already frozen",
22790 Arg1);
22791 end if;
22793 -- Now declare the operators. We do this during analysis rather
22794 -- than expansion, since we want the operators available if we
22795 -- are operating in -gnatc mode.
22797 Declare_Shift_Operator (Name_Rotate_Left);
22798 Declare_Shift_Operator (Name_Rotate_Right);
22799 Declare_Shift_Operator (Name_Shift_Left);
22800 Declare_Shift_Operator (Name_Shift_Right);
22801 Declare_Shift_Operator (Name_Shift_Right_Arithmetic);
22802 end if;
22803 end Provide_Shift_Operators;
22805 ------------------
22806 -- Psect_Object --
22807 ------------------
22809 -- pragma Psect_Object (
22810 -- [Internal =>] LOCAL_NAME,
22811 -- [, [External =>] EXTERNAL_SYMBOL]
22812 -- [, [Size =>] EXTERNAL_SYMBOL]);
22814 when Pragma_Common_Object
22815 | Pragma_Psect_Object
22817 Psect_Object : declare
22818 Args : Args_List (1 .. 3);
22819 Names : constant Name_List (1 .. 3) := (
22820 Name_Internal,
22821 Name_External,
22822 Name_Size);
22824 Internal : Node_Id renames Args (1);
22825 External : Node_Id renames Args (2);
22826 Size : Node_Id renames Args (3);
22828 Def_Id : Entity_Id;
22830 procedure Check_Arg (Arg : Node_Id);
22831 -- Checks that argument is either a string literal or an
22832 -- identifier, and posts error message if not.
22834 ---------------
22835 -- Check_Arg --
22836 ---------------
22838 procedure Check_Arg (Arg : Node_Id) is
22839 begin
22840 if Nkind (Original_Node (Arg)) not in
22841 N_String_Literal | N_Identifier
22842 then
22843 Error_Pragma_Arg
22844 ("inappropriate argument for pragma %", Arg);
22845 end if;
22846 end Check_Arg;
22848 -- Start of processing for Common_Object/Psect_Object
22850 begin
22851 GNAT_Pragma;
22852 Gather_Associations (Names, Args);
22853 Process_Extended_Import_Export_Internal_Arg (Internal);
22855 Def_Id := Entity (Internal);
22857 if Ekind (Def_Id) not in E_Constant | E_Variable then
22858 Error_Pragma_Arg
22859 ("pragma% must designate an object", Internal);
22860 end if;
22862 Check_Arg (Internal);
22864 if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
22865 Error_Pragma_Arg
22866 ("cannot use pragma% for imported/exported object",
22867 Internal);
22868 end if;
22870 if Is_Concurrent_Type (Etype (Internal)) then
22871 Error_Pragma_Arg
22872 ("cannot specify pragma % for task/protected object",
22873 Internal);
22874 end if;
22876 if Has_Rep_Pragma (Def_Id, Name_Common_Object)
22877 or else
22878 Has_Rep_Pragma (Def_Id, Name_Psect_Object)
22879 then
22880 Error_Msg_N ("??duplicate Common/Psect_Object pragma", N);
22881 end if;
22883 if Ekind (Def_Id) = E_Constant then
22884 Error_Pragma_Arg
22885 ("cannot specify pragma % for a constant", Internal);
22886 end if;
22888 if Is_Record_Type (Etype (Internal)) then
22889 declare
22890 Ent : Entity_Id;
22891 Decl : Entity_Id;
22893 begin
22894 Ent := First_Entity (Etype (Internal));
22895 while Present (Ent) loop
22896 Decl := Declaration_Node (Ent);
22898 if Ekind (Ent) = E_Component
22899 and then Nkind (Decl) = N_Component_Declaration
22900 and then Present (Expression (Decl))
22901 and then Warn_On_Export_Import
22902 then
22903 Error_Msg_N
22904 ("?x?object for pragma % has defaults", Internal);
22905 exit;
22907 else
22908 Next_Entity (Ent);
22909 end if;
22910 end loop;
22911 end;
22912 end if;
22914 if Present (Size) then
22915 Check_Arg (Size);
22916 end if;
22918 if Present (External) then
22919 Check_Arg_Is_External_Name (External);
22920 end if;
22922 -- If all error tests pass, link pragma on to the rep item chain
22924 Record_Rep_Item (Def_Id, N);
22925 end Psect_Object;
22927 ----------
22928 -- Pure --
22929 ----------
22931 -- pragma Pure [(library_unit_NAME)];
22933 when Pragma_Pure => Pure : declare
22934 Ent : Entity_Id;
22936 begin
22937 Check_Ada_83_Warning;
22939 -- If the pragma comes from a subprogram instantiation, nothing to
22940 -- check, this can happen at any level of nesting.
22942 if Is_Wrapper_Package (Current_Scope) then
22943 return;
22944 end if;
22946 Check_Valid_Library_Unit_Pragma;
22948 -- If N was rewritten as a null statement there is nothing more
22949 -- to do.
22951 if Nkind (N) = N_Null_Statement then
22952 return;
22953 end if;
22955 Ent := Find_Lib_Unit_Name;
22957 -- A pragma that applies to a Ghost entity becomes Ghost for the
22958 -- purposes of legality checks and removal of ignored Ghost code.
22960 Mark_Ghost_Pragma (N, Ent);
22962 if not Debug_Flag_U then
22963 Set_Is_Pure (Ent);
22964 Set_Has_Pragma_Pure (Ent);
22966 if Legacy_Elaboration_Checks then
22967 Set_Suppress_Elaboration_Warnings (Ent);
22968 end if;
22969 end if;
22970 end Pure;
22972 -------------------
22973 -- Pure_Function --
22974 -------------------
22976 -- pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
22978 when Pragma_Pure_Function => Pure_Function : declare
22979 Def_Id : Entity_Id;
22980 E : Entity_Id;
22981 E_Id : Node_Id;
22982 Effective : Boolean := False;
22983 Orig_Def : Entity_Id;
22984 Same_Decl : Boolean := False;
22986 begin
22987 GNAT_Pragma;
22988 Check_Arg_Count (1);
22989 Check_Optional_Identifier (Arg1, Name_Entity);
22990 Check_Arg_Is_Local_Name (Arg1);
22991 E_Id := Get_Pragma_Arg (Arg1);
22993 if Etype (E_Id) = Any_Type then
22994 return;
22995 end if;
22997 -- Loop through homonyms (overloadings) of referenced entity
22999 E := Entity (E_Id);
23001 -- A pragma that applies to a Ghost entity becomes Ghost for the
23002 -- purposes of legality checks and removal of ignored Ghost code.
23004 Mark_Ghost_Pragma (N, E);
23006 if Present (E) then
23007 loop
23008 Def_Id := Get_Base_Subprogram (E);
23010 if Ekind (Def_Id) not in
23011 E_Function | E_Generic_Function | E_Operator
23012 then
23013 Error_Pragma_Arg
23014 ("pragma% requires a function name", Arg1);
23015 end if;
23017 -- When we have a generic function we must jump up a level
23018 -- to the declaration of the wrapper package itself.
23020 Orig_Def := Def_Id;
23022 if Is_Generic_Instance (Def_Id) then
23023 while Nkind (Orig_Def) /= N_Package_Declaration loop
23024 Orig_Def := Parent (Orig_Def);
23025 end loop;
23026 end if;
23028 if In_Same_Declarative_Part (Parent (N), Orig_Def) then
23029 Same_Decl := True;
23030 Set_Is_Pure (Def_Id);
23032 if not Has_Pragma_Pure_Function (Def_Id) then
23033 Set_Has_Pragma_Pure_Function (Def_Id);
23034 Effective := True;
23035 end if;
23036 end if;
23038 exit when From_Aspect_Specification (N);
23039 E := Homonym (E);
23040 exit when No (E) or else Scope (E) /= Current_Scope;
23041 end loop;
23043 if not Effective
23044 and then Warn_On_Redundant_Constructs
23045 then
23046 Error_Msg_NE
23047 ("pragma Pure_Function on& is redundant?r?",
23048 N, Entity (E_Id));
23050 elsif not Same_Decl then
23051 Error_Pragma_Arg
23052 ("pragma% argument must be in same declarative part",
23053 Arg1);
23054 end if;
23055 end if;
23056 end Pure_Function;
23058 --------------------
23059 -- Queuing_Policy --
23060 --------------------
23062 -- pragma Queuing_Policy (policy_IDENTIFIER);
23064 when Pragma_Queuing_Policy => declare
23065 QP : Character;
23067 begin
23068 Check_Ada_83_Warning;
23069 Check_Arg_Count (1);
23070 Check_No_Identifiers;
23071 Check_Arg_Is_Queuing_Policy (Arg1);
23072 Check_Valid_Configuration_Pragma;
23073 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
23074 QP := Fold_Upper (Name_Buffer (1));
23076 if Queuing_Policy /= ' '
23077 and then Queuing_Policy /= QP
23078 then
23079 Error_Msg_Sloc := Queuing_Policy_Sloc;
23080 Error_Pragma ("queuing policy incompatible with policy#");
23082 -- Set new policy, but always preserve System_Location since we
23083 -- like the error message with the run time name.
23085 else
23086 Queuing_Policy := QP;
23088 if Queuing_Policy_Sloc /= System_Location then
23089 Queuing_Policy_Sloc := Loc;
23090 end if;
23091 end if;
23092 end;
23094 --------------
23095 -- Rational --
23096 --------------
23098 -- pragma Rational, for compatibility with foreign compiler
23100 when Pragma_Rational =>
23101 Set_Rational_Profile;
23103 ---------------------
23104 -- Refined_Depends --
23105 ---------------------
23107 -- pragma Refined_Depends (DEPENDENCY_RELATION);
23109 -- DEPENDENCY_RELATION ::=
23110 -- null
23111 -- | (DEPENDENCY_CLAUSE {, DEPENDENCY_CLAUSE})
23113 -- DEPENDENCY_CLAUSE ::=
23114 -- OUTPUT_LIST =>[+] INPUT_LIST
23115 -- | NULL_DEPENDENCY_CLAUSE
23117 -- NULL_DEPENDENCY_CLAUSE ::= null => INPUT_LIST
23119 -- OUTPUT_LIST ::= OUTPUT | (OUTPUT {, OUTPUT})
23121 -- INPUT_LIST ::= null | INPUT | (INPUT {, INPUT})
23123 -- OUTPUT ::= NAME | FUNCTION_RESULT
23124 -- INPUT ::= NAME
23126 -- where FUNCTION_RESULT is a function Result attribute_reference
23128 -- Characteristics:
23130 -- * Analysis - The annotation undergoes initial checks to verify
23131 -- the legal placement and context. Secondary checks fully analyze
23132 -- the dependency clauses/global list in:
23134 -- Analyze_Refined_Depends_In_Decl_Part
23136 -- * Expansion - None.
23138 -- * Template - The annotation utilizes the generic template of the
23139 -- related subprogram body.
23141 -- * Globals - Capture of global references must occur after full
23142 -- analysis.
23144 -- * Instance - The annotation is instantiated automatically when
23145 -- the related generic subprogram body is instantiated.
23147 when Pragma_Refined_Depends => Refined_Depends : declare
23148 Body_Id : Entity_Id;
23149 Legal : Boolean;
23150 Spec_Id : Entity_Id;
23152 begin
23153 Analyze_Refined_Depends_Global_Post (Spec_Id, Body_Id, Legal);
23155 if Legal then
23157 -- Chain the pragma on the contract for further processing by
23158 -- Analyze_Refined_Depends_In_Decl_Part.
23160 Add_Contract_Item (N, Body_Id);
23162 -- The legality checks of pragmas Refined_Depends and
23163 -- Refined_Global are affected by the SPARK mode in effect and
23164 -- the volatility of the context. In addition these two pragmas
23165 -- are subject to an inherent order:
23167 -- 1) Refined_Global
23168 -- 2) Refined_Depends
23170 -- Analyze all these pragmas in the order outlined above
23172 Analyze_If_Present (Pragma_SPARK_Mode);
23173 Analyze_If_Present (Pragma_Volatile_Function);
23174 Analyze_If_Present (Pragma_Refined_Global);
23175 Analyze_Refined_Depends_In_Decl_Part (N);
23176 end if;
23177 end Refined_Depends;
23179 --------------------
23180 -- Refined_Global --
23181 --------------------
23183 -- pragma Refined_Global (GLOBAL_SPECIFICATION);
23185 -- GLOBAL_SPECIFICATION ::=
23186 -- null
23187 -- | (GLOBAL_LIST)
23188 -- | (MODED_GLOBAL_LIST {, MODED_GLOBAL_LIST})
23190 -- MODED_GLOBAL_LIST ::= MODE_SELECTOR => GLOBAL_LIST
23192 -- MODE_SELECTOR ::= In_Out | Input | Output | Proof_In
23193 -- GLOBAL_LIST ::= GLOBAL_ITEM | (GLOBAL_ITEM {, GLOBAL_ITEM})
23194 -- GLOBAL_ITEM ::= NAME
23196 -- Characteristics:
23198 -- * Analysis - The annotation undergoes initial checks to verify
23199 -- the legal placement and context. Secondary checks fully analyze
23200 -- the dependency clauses/global list in:
23202 -- Analyze_Refined_Global_In_Decl_Part
23204 -- * Expansion - None.
23206 -- * Template - The annotation utilizes the generic template of the
23207 -- related subprogram body.
23209 -- * Globals - Capture of global references must occur after full
23210 -- analysis.
23212 -- * Instance - The annotation is instantiated automatically when
23213 -- the related generic subprogram body is instantiated.
23215 when Pragma_Refined_Global => Refined_Global : declare
23216 Body_Id : Entity_Id;
23217 Legal : Boolean;
23218 Spec_Id : Entity_Id;
23220 begin
23221 Analyze_Refined_Depends_Global_Post (Spec_Id, Body_Id, Legal);
23223 if Legal then
23225 -- Chain the pragma on the contract for further processing by
23226 -- Analyze_Refined_Global_In_Decl_Part.
23228 Add_Contract_Item (N, Body_Id);
23230 -- The legality checks of pragmas Refined_Depends and
23231 -- Refined_Global are affected by the SPARK mode in effect and
23232 -- the volatility of the context. In addition these two pragmas
23233 -- are subject to an inherent order:
23235 -- 1) Refined_Global
23236 -- 2) Refined_Depends
23238 -- Analyze all these pragmas in the order outlined above
23240 Analyze_If_Present (Pragma_SPARK_Mode);
23241 Analyze_If_Present (Pragma_Volatile_Function);
23242 Analyze_Refined_Global_In_Decl_Part (N);
23243 Analyze_If_Present (Pragma_Refined_Depends);
23244 end if;
23245 end Refined_Global;
23247 ------------------
23248 -- Refined_Post --
23249 ------------------
23251 -- pragma Refined_Post (boolean_EXPRESSION);
23253 -- Characteristics:
23255 -- * Analysis - The annotation is fully analyzed immediately upon
23256 -- elaboration as it cannot forward reference entities.
23258 -- * Expansion - The annotation is expanded during the expansion of
23259 -- the related subprogram body contract as performed in:
23261 -- Expand_Subprogram_Contract
23263 -- * Template - The annotation utilizes the generic template of the
23264 -- related subprogram body.
23266 -- * Globals - Capture of global references must occur after full
23267 -- analysis.
23269 -- * Instance - The annotation is instantiated automatically when
23270 -- the related generic subprogram body is instantiated.
23272 when Pragma_Refined_Post => Refined_Post : declare
23273 Body_Id : Entity_Id;
23274 Legal : Boolean;
23275 Spec_Id : Entity_Id;
23277 begin
23278 Analyze_Refined_Depends_Global_Post (Spec_Id, Body_Id, Legal);
23280 -- Fully analyze the pragma when it appears inside a subprogram
23281 -- body because it cannot benefit from forward references.
23283 if Legal then
23285 -- Chain the pragma on the contract for completeness
23287 Add_Contract_Item (N, Body_Id);
23289 -- The legality checks of pragma Refined_Post are affected by
23290 -- the SPARK mode in effect and the volatility of the context.
23291 -- Analyze all pragmas in a specific order.
23293 Analyze_If_Present (Pragma_SPARK_Mode);
23294 Analyze_If_Present (Pragma_Volatile_Function);
23295 Analyze_Pre_Post_Condition_In_Decl_Part (N);
23297 -- Currently it is not possible to inline pre/postconditions on
23298 -- a subprogram subject to pragma Inline_Always.
23300 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
23301 end if;
23302 end Refined_Post;
23304 -------------------
23305 -- Refined_State --
23306 -------------------
23308 -- pragma Refined_State (REFINEMENT_LIST);
23310 -- REFINEMENT_LIST ::=
23311 -- (REFINEMENT_CLAUSE {, REFINEMENT_CLAUSE})
23313 -- REFINEMENT_CLAUSE ::= state_NAME => CONSTITUENT_LIST
23315 -- CONSTITUENT_LIST ::=
23316 -- null
23317 -- | CONSTITUENT
23318 -- | (CONSTITUENT {, CONSTITUENT})
23320 -- CONSTITUENT ::= object_NAME | state_NAME
23322 -- Characteristics:
23324 -- * Analysis - The annotation undergoes initial checks to verify
23325 -- the legal placement and context. Secondary checks preanalyze the
23326 -- refinement clauses in:
23328 -- Analyze_Refined_State_In_Decl_Part
23330 -- * Expansion - None.
23332 -- * Template - The annotation utilizes the template of the related
23333 -- package body.
23335 -- * Globals - Capture of global references must occur after full
23336 -- analysis.
23338 -- * Instance - The annotation is instantiated automatically when
23339 -- the related generic package body is instantiated.
23341 when Pragma_Refined_State => Refined_State : declare
23342 Pack_Decl : Node_Id;
23343 Spec_Id : Entity_Id;
23345 begin
23346 GNAT_Pragma;
23347 Check_No_Identifiers;
23348 Check_Arg_Count (1);
23350 Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
23352 if Nkind (Pack_Decl) /= N_Package_Body then
23353 Pragma_Misplaced;
23354 end if;
23356 Spec_Id := Corresponding_Spec (Pack_Decl);
23358 -- A pragma that applies to a Ghost entity becomes Ghost for the
23359 -- purposes of legality checks and removal of ignored Ghost code.
23361 Mark_Ghost_Pragma (N, Spec_Id);
23363 -- Chain the pragma on the contract for further processing by
23364 -- Analyze_Refined_State_In_Decl_Part.
23366 Add_Contract_Item (N, Defining_Entity (Pack_Decl));
23368 -- The legality checks of pragma Refined_State are affected by the
23369 -- SPARK mode in effect. Analyze all pragmas in a specific order.
23371 Analyze_If_Present (Pragma_SPARK_Mode);
23373 -- State refinement is allowed only when the corresponding package
23374 -- declaration has non-null pragma Abstract_State. Refinement not
23375 -- enforced when SPARK checks are suppressed (SPARK RM 7.2.2(3)).
23377 if SPARK_Mode /= Off
23378 and then
23379 (No (Abstract_States (Spec_Id))
23380 or else Has_Null_Abstract_State (Spec_Id))
23381 then
23382 Error_Msg_NE
23383 ("useless refinement, package & does not define abstract "
23384 & "states", N, Spec_Id);
23385 return;
23386 end if;
23387 end Refined_State;
23389 -----------------------
23390 -- Relative_Deadline --
23391 -----------------------
23393 -- pragma Relative_Deadline (time_span_EXPRESSION);
23395 when Pragma_Relative_Deadline => Relative_Deadline : declare
23396 P : constant Node_Id := Parent (N);
23397 Arg : Node_Id;
23399 begin
23400 Ada_2005_Pragma;
23401 Check_No_Identifiers;
23402 Check_Arg_Count (1);
23404 Arg := Get_Pragma_Arg (Arg1);
23406 -- The expression must be analyzed in the special manner described
23407 -- in "Handling of Default and Per-Object Expressions" in sem.ads.
23409 Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
23411 -- Subprogram case
23413 if Nkind (P) = N_Subprogram_Body then
23414 Check_In_Main_Program;
23416 -- Only Task and subprogram cases allowed
23418 elsif Nkind (P) /= N_Task_Definition then
23419 Pragma_Misplaced;
23420 end if;
23422 -- Check duplicate pragma before we set the corresponding flag
23424 if Has_Relative_Deadline_Pragma (P) then
23425 Error_Pragma ("duplicate pragma% not allowed");
23426 end if;
23428 -- Set Has_Relative_Deadline_Pragma only for tasks. Note that
23429 -- Relative_Deadline pragma node cannot be inserted in the Rep
23430 -- Item chain of Ent since it is rewritten by the expander as a
23431 -- procedure call statement that will break the chain.
23433 Set_Has_Relative_Deadline_Pragma (P);
23434 end Relative_Deadline;
23436 ------------------------
23437 -- Remote_Access_Type --
23438 ------------------------
23440 -- pragma Remote_Access_Type ([Entity =>] formal_type_LOCAL_NAME);
23442 when Pragma_Remote_Access_Type => Remote_Access_Type : declare
23443 E : Entity_Id;
23445 begin
23446 GNAT_Pragma;
23447 Check_Arg_Count (1);
23448 Check_Optional_Identifier (Arg1, Name_Entity);
23449 Check_Arg_Is_Local_Name (Arg1);
23451 E := Entity (Get_Pragma_Arg (Arg1));
23453 -- A pragma that applies to a Ghost entity becomes Ghost for the
23454 -- purposes of legality checks and removal of ignored Ghost code.
23456 Mark_Ghost_Pragma (N, E);
23458 if Nkind (Parent (E)) = N_Formal_Type_Declaration
23459 and then Ekind (E) = E_General_Access_Type
23460 and then Is_Class_Wide_Type (Directly_Designated_Type (E))
23461 and then Scope (Root_Type (Directly_Designated_Type (E)))
23462 = Scope (E)
23463 and then Is_Valid_Remote_Object_Type
23464 (Root_Type (Directly_Designated_Type (E)))
23465 then
23466 Set_Is_Remote_Types (E);
23468 else
23469 Error_Pragma_Arg
23470 ("pragma% applies only to formal access-to-class-wide types",
23471 Arg1);
23472 end if;
23473 end Remote_Access_Type;
23475 ---------------------------
23476 -- Remote_Call_Interface --
23477 ---------------------------
23479 -- pragma Remote_Call_Interface [(library_unit_NAME)];
23481 when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
23482 Cunit_Node : Node_Id;
23483 Cunit_Ent : Entity_Id;
23484 K : Node_Kind;
23486 begin
23487 Check_Ada_83_Warning;
23488 Check_Valid_Library_Unit_Pragma;
23490 -- If N was rewritten as a null statement there is nothing more
23491 -- to do.
23493 if Nkind (N) = N_Null_Statement then
23494 return;
23495 end if;
23497 Cunit_Node := Cunit (Current_Sem_Unit);
23498 K := Nkind (Unit (Cunit_Node));
23499 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
23501 -- A pragma that applies to a Ghost entity becomes Ghost for the
23502 -- purposes of legality checks and removal of ignored Ghost code.
23504 Mark_Ghost_Pragma (N, Cunit_Ent);
23506 if K = N_Package_Declaration
23507 or else K = N_Generic_Package_Declaration
23508 or else K = N_Subprogram_Declaration
23509 or else K = N_Generic_Subprogram_Declaration
23510 or else (K = N_Subprogram_Body
23511 and then Acts_As_Spec (Unit (Cunit_Node)))
23512 then
23513 null;
23514 else
23515 Error_Pragma (
23516 "pragma% must apply to package or subprogram declaration");
23517 end if;
23519 Set_Is_Remote_Call_Interface (Cunit_Ent);
23520 end Remote_Call_Interface;
23522 ------------------
23523 -- Remote_Types --
23524 ------------------
23526 -- pragma Remote_Types [(library_unit_NAME)];
23528 when Pragma_Remote_Types => Remote_Types : declare
23529 Cunit_Node : Node_Id;
23530 Cunit_Ent : Entity_Id;
23532 begin
23533 Check_Ada_83_Warning;
23534 Check_Valid_Library_Unit_Pragma;
23536 -- If N was rewritten as a null statement there is nothing more
23537 -- to do.
23539 if Nkind (N) = N_Null_Statement then
23540 return;
23541 end if;
23543 Cunit_Node := Cunit (Current_Sem_Unit);
23544 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
23546 -- A pragma that applies to a Ghost entity becomes Ghost for the
23547 -- purposes of legality checks and removal of ignored Ghost code.
23549 Mark_Ghost_Pragma (N, Cunit_Ent);
23551 if Nkind (Unit (Cunit_Node)) not in
23552 N_Package_Declaration | N_Generic_Package_Declaration
23553 then
23554 Error_Pragma
23555 ("pragma% can only apply to a package declaration");
23556 end if;
23558 Set_Is_Remote_Types (Cunit_Ent);
23559 end Remote_Types;
23561 ---------------
23562 -- Ravenscar --
23563 ---------------
23565 -- pragma Ravenscar;
23567 when Pragma_Ravenscar =>
23568 GNAT_Pragma;
23569 Check_Arg_Count (0);
23570 Check_Valid_Configuration_Pragma;
23571 Set_Ravenscar_Profile (Ravenscar, N);
23573 if Warn_On_Obsolescent_Feature then
23574 Error_Msg_N
23575 ("pragma Ravenscar is an obsolescent feature?j?", N);
23576 Error_Msg_N
23577 ("|use pragma Profile (Ravenscar) instead?j?", N);
23578 end if;
23580 -------------------------
23581 -- Restricted_Run_Time --
23582 -------------------------
23584 -- pragma Restricted_Run_Time;
23586 when Pragma_Restricted_Run_Time =>
23587 GNAT_Pragma;
23588 Check_Arg_Count (0);
23589 Check_Valid_Configuration_Pragma;
23590 Set_Profile_Restrictions
23591 (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
23593 if Warn_On_Obsolescent_Feature then
23594 Error_Msg_N
23595 ("pragma Restricted_Run_Time is an obsolescent feature?j?",
23597 Error_Msg_N
23598 ("|use pragma Profile (Restricted) instead?j?", N);
23599 end if;
23601 ------------------
23602 -- Restrictions --
23603 ------------------
23605 -- pragma Restrictions (RESTRICTION {, RESTRICTION});
23607 -- RESTRICTION ::=
23608 -- restriction_IDENTIFIER
23609 -- | restriction_parameter_IDENTIFIER => EXPRESSION
23611 when Pragma_Restrictions =>
23612 Process_Restrictions_Or_Restriction_Warnings
23613 (Warn => Treat_Restrictions_As_Warnings);
23615 --------------------------
23616 -- Restriction_Warnings --
23617 --------------------------
23619 -- pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
23621 -- RESTRICTION ::=
23622 -- restriction_IDENTIFIER
23623 -- | restriction_parameter_IDENTIFIER => EXPRESSION
23625 when Pragma_Restriction_Warnings =>
23626 GNAT_Pragma;
23627 Process_Restrictions_Or_Restriction_Warnings (Warn => True);
23629 ----------------
23630 -- Reviewable --
23631 ----------------
23633 -- pragma Reviewable;
23635 when Pragma_Reviewable =>
23636 Check_Ada_83_Warning;
23637 Check_Arg_Count (0);
23639 -- Call dummy debugging function rv. This is done to assist front
23640 -- end debugging. By placing a Reviewable pragma in the source
23641 -- program, a breakpoint on rv catches this place in the source,
23642 -- allowing convenient stepping to the point of interest.
23646 --------------------------
23647 -- Secondary_Stack_Size --
23648 --------------------------
23650 -- pragma Secondary_Stack_Size (EXPRESSION);
23652 when Pragma_Secondary_Stack_Size => Secondary_Stack_Size : declare
23653 P : constant Node_Id := Parent (N);
23654 Arg : Node_Id;
23655 Ent : Entity_Id;
23657 begin
23658 GNAT_Pragma;
23659 Check_No_Identifiers;
23660 Check_Arg_Count (1);
23662 if Nkind (P) = N_Task_Definition then
23663 Arg := Get_Pragma_Arg (Arg1);
23664 Ent := Defining_Identifier (Parent (P));
23666 -- The expression must be analyzed in the special manner
23667 -- described in "Handling of Default Expressions" in sem.ads.
23669 Preanalyze_Spec_Expression (Arg, Any_Integer);
23671 -- The pragma cannot appear if the No_Secondary_Stack
23672 -- restriction is in effect.
23674 Check_Restriction (No_Secondary_Stack, Arg);
23676 -- Anything else is incorrect
23678 else
23679 Pragma_Misplaced;
23680 end if;
23682 -- Check duplicate pragma before we chain the pragma in the Rep
23683 -- Item chain of Ent.
23685 Check_Duplicate_Pragma (Ent);
23686 Record_Rep_Item (Ent, N);
23687 end Secondary_Stack_Size;
23689 --------------------------
23690 -- Short_Circuit_And_Or --
23691 --------------------------
23693 -- pragma Short_Circuit_And_Or;
23695 when Pragma_Short_Circuit_And_Or =>
23696 GNAT_Pragma;
23697 Check_Arg_Count (0);
23698 Check_Valid_Configuration_Pragma;
23699 Short_Circuit_And_Or := True;
23701 -------------------
23702 -- Share_Generic --
23703 -------------------
23705 -- pragma Share_Generic (GNAME {, GNAME});
23707 -- GNAME ::= generic_unit_NAME | generic_instance_NAME
23709 when Pragma_Share_Generic =>
23710 GNAT_Pragma;
23711 Process_Generic_List;
23713 ------------
23714 -- Shared --
23715 ------------
23717 -- pragma Shared (LOCAL_NAME);
23719 when Pragma_Shared =>
23720 GNAT_Pragma;
23721 Process_Atomic_Independent_Shared_Volatile;
23723 --------------------
23724 -- Shared_Passive --
23725 --------------------
23727 -- pragma Shared_Passive [(library_unit_NAME)];
23729 -- Set the flag Is_Shared_Passive of program unit name entity
23731 when Pragma_Shared_Passive => Shared_Passive : declare
23732 Cunit_Node : Node_Id;
23733 Cunit_Ent : Entity_Id;
23735 begin
23736 Check_Ada_83_Warning;
23737 Check_Valid_Library_Unit_Pragma;
23739 -- If N was rewritten as a null statement there is nothing more
23740 -- to do.
23742 if Nkind (N) = N_Null_Statement then
23743 return;
23744 end if;
23746 Cunit_Node := Cunit (Current_Sem_Unit);
23747 Cunit_Ent := Cunit_Entity (Current_Sem_Unit);
23749 -- A pragma that applies to a Ghost entity becomes Ghost for the
23750 -- purposes of legality checks and removal of ignored Ghost code.
23752 Mark_Ghost_Pragma (N, Cunit_Ent);
23754 if Nkind (Unit (Cunit_Node)) not in
23755 N_Package_Declaration | N_Generic_Package_Declaration
23756 then
23757 Error_Pragma
23758 ("pragma% can only apply to a package declaration");
23759 end if;
23761 Set_Is_Shared_Passive (Cunit_Ent);
23762 end Shared_Passive;
23764 -----------------------
23765 -- Short_Descriptors --
23766 -----------------------
23768 -- pragma Short_Descriptors;
23770 -- Recognize and validate, but otherwise ignore
23772 when Pragma_Short_Descriptors =>
23773 GNAT_Pragma;
23774 Check_Arg_Count (0);
23775 Check_Valid_Configuration_Pragma;
23777 ------------------------------
23778 -- Simple_Storage_Pool_Type --
23779 ------------------------------
23781 -- pragma Simple_Storage_Pool_Type (type_LOCAL_NAME);
23783 when Pragma_Simple_Storage_Pool_Type =>
23784 Simple_Storage_Pool_Type : declare
23785 Typ : Entity_Id;
23786 Type_Id : Node_Id;
23788 begin
23789 GNAT_Pragma;
23790 Check_Arg_Count (1);
23791 Check_Arg_Is_Library_Level_Local_Name (Arg1);
23793 Type_Id := Get_Pragma_Arg (Arg1);
23794 Find_Type (Type_Id);
23795 Typ := Entity (Type_Id);
23797 if Typ = Any_Type then
23798 return;
23799 end if;
23801 -- A pragma that applies to a Ghost entity becomes Ghost for the
23802 -- purposes of legality checks and removal of ignored Ghost code.
23804 Mark_Ghost_Pragma (N, Typ);
23806 -- We require the pragma to apply to a type declared in a package
23807 -- declaration, but not (immediately) within a package body.
23809 if Ekind (Current_Scope) /= E_Package
23810 or else In_Package_Body (Current_Scope)
23811 then
23812 Error_Pragma
23813 ("pragma% can only apply to type declared immediately "
23814 & "within a package declaration");
23815 end if;
23817 -- A simple storage pool type must be an immutably limited record
23818 -- or private type. If the pragma is given for a private type,
23819 -- the full type is similarly restricted (which is checked later
23820 -- in Freeze_Entity).
23822 if Is_Record_Type (Typ)
23823 and then not Is_Limited_View (Typ)
23824 then
23825 Error_Pragma
23826 ("pragma% can only apply to explicitly limited record type");
23828 elsif Is_Private_Type (Typ) and then not Is_Limited_Type (Typ) then
23829 Error_Pragma
23830 ("pragma% can only apply to a private type that is limited");
23832 elsif not Is_Record_Type (Typ)
23833 and then not Is_Private_Type (Typ)
23834 then
23835 Error_Pragma
23836 ("pragma% can only apply to limited record or private type");
23837 end if;
23839 Record_Rep_Item (Typ, N);
23840 end Simple_Storage_Pool_Type;
23842 ----------------------
23843 -- Source_File_Name --
23844 ----------------------
23846 -- There are five forms for this pragma:
23848 -- pragma Source_File_Name (
23849 -- [UNIT_NAME =>] unit_NAME,
23850 -- BODY_FILE_NAME => STRING_LITERAL
23851 -- [, [INDEX =>] INTEGER_LITERAL]);
23853 -- pragma Source_File_Name (
23854 -- [UNIT_NAME =>] unit_NAME,
23855 -- SPEC_FILE_NAME => STRING_LITERAL
23856 -- [, [INDEX =>] INTEGER_LITERAL]);
23858 -- pragma Source_File_Name (
23859 -- BODY_FILE_NAME => STRING_LITERAL
23860 -- [, DOT_REPLACEMENT => STRING_LITERAL]
23861 -- [, CASING => CASING_SPEC]);
23863 -- pragma Source_File_Name (
23864 -- SPEC_FILE_NAME => STRING_LITERAL
23865 -- [, DOT_REPLACEMENT => STRING_LITERAL]
23866 -- [, CASING => CASING_SPEC]);
23868 -- pragma Source_File_Name (
23869 -- SUBUNIT_FILE_NAME => STRING_LITERAL
23870 -- [, DOT_REPLACEMENT => STRING_LITERAL]
23871 -- [, CASING => CASING_SPEC]);
23873 -- CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
23875 -- Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
23876 -- Source_File_Name (SFN), however their usage is exclusive: SFN can
23877 -- only be used when no project file is used, while SFNP can only be
23878 -- used when a project file is used.
23880 -- No processing here. Processing was completed during parsing, since
23881 -- we need to have file names set as early as possible. Units are
23882 -- loaded well before semantic processing starts.
23884 -- The only processing we defer to this point is the check for
23885 -- correct placement.
23887 when Pragma_Source_File_Name =>
23888 GNAT_Pragma;
23889 Check_Valid_Configuration_Pragma;
23891 ------------------------------
23892 -- Source_File_Name_Project --
23893 ------------------------------
23895 -- See Source_File_Name for syntax
23897 -- No processing here. Processing was completed during parsing, since
23898 -- we need to have file names set as early as possible. Units are
23899 -- loaded well before semantic processing starts.
23901 -- The only processing we defer to this point is the check for
23902 -- correct placement.
23904 when Pragma_Source_File_Name_Project =>
23905 GNAT_Pragma;
23906 Check_Valid_Configuration_Pragma;
23908 -- Check that a pragma Source_File_Name_Project is used only in a
23909 -- configuration pragmas file.
23911 -- Pragmas Source_File_Name_Project should only be generated by
23912 -- the Project Manager in configuration pragmas files.
23914 -- This is really an ugly test. It seems to depend on some
23915 -- accidental and undocumented property. At the very least it
23916 -- needs to be documented, but it would be better to have a
23917 -- clean way of testing if we are in a configuration file???
23919 if Present (Parent (N)) then
23920 Error_Pragma
23921 ("pragma% can only appear in a configuration pragmas file");
23922 end if;
23924 ----------------------
23925 -- Source_Reference --
23926 ----------------------
23928 -- pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
23930 -- Nothing to do, all processing completed in Par.Prag, since we need
23931 -- the information for possible parser messages that are output.
23933 when Pragma_Source_Reference =>
23934 GNAT_Pragma;
23936 ----------------
23937 -- SPARK_Mode --
23938 ----------------
23940 -- pragma SPARK_Mode [(Auto | On | Off)];
23942 when Pragma_SPARK_Mode => Do_SPARK_Mode : declare
23943 Mode_Id : SPARK_Mode_Type;
23945 procedure Check_Pragma_Conformance
23946 (Context_Pragma : Node_Id;
23947 Entity : Entity_Id;
23948 Entity_Pragma : Node_Id);
23949 -- Subsidiary to routines Process_xxx. Verify the SPARK_Mode
23950 -- conformance of pragma N depending the following scenarios:
23952 -- If pragma Context_Pragma is not Empty, verify that pragma N is
23953 -- compatible with the pragma Context_Pragma that was inherited
23954 -- from the context:
23955 -- * If the mode of Context_Pragma is ON, then the new mode can
23956 -- be anything.
23957 -- * If the mode of Context_Pragma is OFF, then the only allowed
23958 -- new mode is also OFF. Emit error if this is not the case.
23960 -- If Entity is not Empty, verify that pragma N is compatible with
23961 -- pragma Entity_Pragma that belongs to Entity.
23962 -- * If Entity_Pragma is Empty, always issue an error as this
23963 -- corresponds to the case where a previous section of Entity
23964 -- has no SPARK_Mode set.
23965 -- * If the mode of Entity_Pragma is ON, then the new mode can
23966 -- be anything.
23967 -- * If the mode of Entity_Pragma is OFF, then the only allowed
23968 -- new mode is also OFF. Emit error if this is not the case.
23970 procedure Check_Library_Level_Entity (E : Entity_Id);
23971 -- Subsidiary to routines Process_xxx. Verify that the related
23972 -- entity E subject to pragma SPARK_Mode is library-level.
23974 procedure Process_Body (Decl : Node_Id);
23975 -- Verify the legality of pragma SPARK_Mode when it appears as the
23976 -- top of the body declarations of entry, package, protected unit,
23977 -- subprogram or task unit body denoted by Decl.
23979 procedure Process_Overloadable (Decl : Node_Id);
23980 -- Verify the legality of pragma SPARK_Mode when it applies to an
23981 -- entry or [generic] subprogram declaration denoted by Decl.
23983 procedure Process_Private_Part (Decl : Node_Id);
23984 -- Verify the legality of pragma SPARK_Mode when it appears at the
23985 -- top of the private declarations of a package spec, protected or
23986 -- task unit declaration denoted by Decl.
23988 procedure Process_Statement_Part (Decl : Node_Id);
23989 -- Verify the legality of pragma SPARK_Mode when it appears at the
23990 -- top of the statement sequence of a package body denoted by node
23991 -- Decl.
23993 procedure Process_Visible_Part (Decl : Node_Id);
23994 -- Verify the legality of pragma SPARK_Mode when it appears at the
23995 -- top of the visible declarations of a package spec, protected or
23996 -- task unit declaration denoted by Decl. The routine is also used
23997 -- on protected or task units declared without a definition.
23999 procedure Set_SPARK_Context;
24000 -- Subsidiary to routines Process_xxx. Set the global variables
24001 -- which represent the mode of the context from pragma N. Ensure
24002 -- that Dynamic_Elaboration_Checks are off if the new mode is On.
24004 ------------------------------
24005 -- Check_Pragma_Conformance --
24006 ------------------------------
24008 procedure Check_Pragma_Conformance
24009 (Context_Pragma : Node_Id;
24010 Entity : Entity_Id;
24011 Entity_Pragma : Node_Id)
24013 Err_Id : Entity_Id;
24014 Err_N : Node_Id;
24016 begin
24017 -- The current pragma may appear without an argument. If this
24018 -- is the case, associate all error messages with the pragma
24019 -- itself.
24021 if Present (Arg1) then
24022 Err_N := Arg1;
24023 else
24024 Err_N := N;
24025 end if;
24027 -- The mode of the current pragma is compared against that of
24028 -- an enclosing context.
24030 if Present (Context_Pragma) then
24031 pragma Assert (Nkind (Context_Pragma) = N_Pragma);
24033 -- Issue an error if the new mode is less restrictive than
24034 -- that of the context.
24036 if Get_SPARK_Mode_From_Annotation (Context_Pragma) = Off
24037 and then Get_SPARK_Mode_From_Annotation (N) = On
24038 then
24039 Error_Msg_N
24040 ("cannot change SPARK_Mode from Off to On", Err_N);
24041 Error_Msg_Sloc := Sloc (SPARK_Mode_Pragma);
24042 Error_Msg_N ("\SPARK_Mode was set to Off#", Err_N);
24043 raise Pragma_Exit;
24044 end if;
24045 end if;
24047 -- The mode of the current pragma is compared against that of
24048 -- an initial package, protected type, subprogram or task type
24049 -- declaration.
24051 if Present (Entity) then
24053 -- A simple protected or task type is transformed into an
24054 -- anonymous type whose name cannot be used to issue error
24055 -- messages. Recover the original entity of the type.
24057 if Ekind (Entity) in E_Protected_Type | E_Task_Type then
24058 Err_Id :=
24059 Defining_Entity
24060 (Original_Node (Unit_Declaration_Node (Entity)));
24061 else
24062 Err_Id := Entity;
24063 end if;
24065 -- Both the initial declaration and the completion carry
24066 -- SPARK_Mode pragmas.
24068 if Present (Entity_Pragma) then
24069 pragma Assert (Nkind (Entity_Pragma) = N_Pragma);
24071 -- Issue an error if the new mode is less restrictive
24072 -- than that of the initial declaration.
24074 if Get_SPARK_Mode_From_Annotation (Entity_Pragma) = Off
24075 and then Get_SPARK_Mode_From_Annotation (N) = On
24076 then
24077 Error_Msg_N ("incorrect use of SPARK_Mode", Err_N);
24078 Error_Msg_Sloc := Sloc (Entity_Pragma);
24079 Error_Msg_NE
24080 ("\value Off was set for SPARK_Mode on&#",
24081 Err_N, Err_Id);
24082 raise Pragma_Exit;
24083 end if;
24085 -- Otherwise the initial declaration lacks a SPARK_Mode
24086 -- pragma in which case the current pragma is illegal as
24087 -- it cannot "complete".
24089 elsif Get_SPARK_Mode_From_Annotation (N) = Off
24090 and then (Is_Generic_Unit (Entity) or else In_Instance)
24091 then
24092 null;
24094 else
24095 Error_Msg_N ("incorrect use of SPARK_Mode", Err_N);
24096 Error_Msg_Sloc := Sloc (Err_Id);
24097 Error_Msg_NE
24098 ("\no value was set for SPARK_Mode on&#",
24099 Err_N, Err_Id);
24100 raise Pragma_Exit;
24101 end if;
24102 end if;
24103 end Check_Pragma_Conformance;
24105 --------------------------------
24106 -- Check_Library_Level_Entity --
24107 --------------------------------
24109 procedure Check_Library_Level_Entity (E : Entity_Id) is
24110 procedure Add_Entity_To_Name_Buffer;
24111 -- Add the E_Kind of entity E to the name buffer
24113 -------------------------------
24114 -- Add_Entity_To_Name_Buffer --
24115 -------------------------------
24117 procedure Add_Entity_To_Name_Buffer is
24118 begin
24119 if Ekind (E) in E_Entry | E_Entry_Family then
24120 Add_Str_To_Name_Buffer ("entry");
24122 elsif Ekind (E) in E_Generic_Package
24123 | E_Package
24124 | E_Package_Body
24125 then
24126 Add_Str_To_Name_Buffer ("package");
24128 elsif Ekind (E) in E_Protected_Body | E_Protected_Type then
24129 Add_Str_To_Name_Buffer ("protected type");
24131 elsif Ekind (E) in E_Function
24132 | E_Generic_Function
24133 | E_Generic_Procedure
24134 | E_Procedure
24135 | E_Subprogram_Body
24136 then
24137 Add_Str_To_Name_Buffer ("subprogram");
24139 else
24140 pragma Assert (Ekind (E) in E_Task_Body | E_Task_Type);
24141 Add_Str_To_Name_Buffer ("task type");
24142 end if;
24143 end Add_Entity_To_Name_Buffer;
24145 -- Local variables
24147 Msg_1 : constant String :=
24148 "incorrect placement of pragma% with value ""On"" '[[]']";
24149 Msg_2 : Name_Id;
24151 -- Start of processing for Check_Library_Level_Entity
24153 begin
24154 -- A SPARK_Mode of On shall only apply to library-level
24155 -- entities, except for those in generic instances, which are
24156 -- ignored (even if the entity gets SPARK_Mode pragma attached
24157 -- in the AST, its effect is not taken into account unless the
24158 -- context already provides SPARK_Mode of On in GNATprove).
24160 if Get_SPARK_Mode_From_Annotation (N) = On
24161 and then not Is_Library_Level_Entity (E)
24162 and then Instantiation_Location (Sloc (N)) = No_Location
24163 then
24164 Error_Msg_Name_1 := Pname;
24165 Error_Msg_Code := GEC_SPARK_Mode_On_Not_Library_Level;
24166 Error_Msg_N (Fix_Error (Msg_1), N);
24168 Name_Len := 0;
24169 Add_Str_To_Name_Buffer ("\& is not a library-level ");
24170 Add_Entity_To_Name_Buffer;
24172 Msg_2 := Name_Find;
24173 Error_Msg_NE (Get_Name_String (Msg_2), N, E);
24175 raise Pragma_Exit;
24176 end if;
24177 end Check_Library_Level_Entity;
24179 ------------------
24180 -- Process_Body --
24181 ------------------
24183 procedure Process_Body (Decl : Node_Id) is
24184 Body_Id : constant Entity_Id := Defining_Entity (Decl);
24185 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Decl);
24187 begin
24188 -- Ignore pragma when applied to the special body created
24189 -- for inlining, recognized by its internal name _Parent; or
24190 -- when applied to the special body created for contracts,
24191 -- recognized by its internal name _Wrapped_Statements.
24193 if Chars (Body_Id) in Name_uParent
24194 | Name_uWrapped_Statements
24195 then
24196 return;
24197 end if;
24199 Check_Library_Level_Entity (Body_Id);
24201 -- For entry bodies, verify the legality against:
24202 -- * The mode of the context
24203 -- * The mode of the spec (if any)
24205 if Nkind (Decl) in N_Entry_Body | N_Subprogram_Body then
24207 -- A stand-alone subprogram body
24209 if Body_Id = Spec_Id then
24210 Check_Pragma_Conformance
24211 (Context_Pragma => SPARK_Pragma (Body_Id),
24212 Entity => Empty,
24213 Entity_Pragma => Empty);
24215 -- An entry or subprogram body that completes a previous
24216 -- declaration.
24218 else
24219 Check_Pragma_Conformance
24220 (Context_Pragma => SPARK_Pragma (Body_Id),
24221 Entity => Spec_Id,
24222 Entity_Pragma => SPARK_Pragma (Spec_Id));
24223 end if;
24225 Set_SPARK_Context;
24226 Set_SPARK_Pragma (Body_Id, N);
24227 Set_SPARK_Pragma_Inherited (Body_Id, False);
24229 -- For package bodies, verify the legality against:
24230 -- * The mode of the context
24231 -- * The mode of the private part
24233 -- This case is separated from protected and task bodies
24234 -- because the statement part of the package body inherits
24235 -- the mode of the body declarations.
24237 elsif Nkind (Decl) = N_Package_Body then
24238 Check_Pragma_Conformance
24239 (Context_Pragma => SPARK_Pragma (Body_Id),
24240 Entity => Spec_Id,
24241 Entity_Pragma => SPARK_Aux_Pragma (Spec_Id));
24243 Set_SPARK_Context;
24244 Set_SPARK_Pragma (Body_Id, N);
24245 Set_SPARK_Pragma_Inherited (Body_Id, False);
24246 Set_SPARK_Aux_Pragma (Body_Id, N);
24247 Set_SPARK_Aux_Pragma_Inherited (Body_Id, True);
24249 -- For protected and task bodies, verify the legality against:
24250 -- * The mode of the context
24251 -- * The mode of the private part
24253 else
24254 pragma Assert
24255 (Nkind (Decl) in N_Protected_Body | N_Task_Body);
24257 Check_Pragma_Conformance
24258 (Context_Pragma => SPARK_Pragma (Body_Id),
24259 Entity => Spec_Id,
24260 Entity_Pragma => SPARK_Aux_Pragma (Spec_Id));
24262 Set_SPARK_Context;
24263 Set_SPARK_Pragma (Body_Id, N);
24264 Set_SPARK_Pragma_Inherited (Body_Id, False);
24265 end if;
24266 end Process_Body;
24268 --------------------------
24269 -- Process_Overloadable --
24270 --------------------------
24272 procedure Process_Overloadable (Decl : Node_Id) is
24273 Spec_Id : constant Entity_Id := Defining_Entity (Decl);
24274 Spec_Typ : constant Entity_Id := Etype (Spec_Id);
24276 begin
24277 Check_Library_Level_Entity (Spec_Id);
24279 -- Verify the legality against:
24280 -- * The mode of the context
24282 Check_Pragma_Conformance
24283 (Context_Pragma => SPARK_Pragma (Spec_Id),
24284 Entity => Empty,
24285 Entity_Pragma => Empty);
24287 Set_SPARK_Pragma (Spec_Id, N);
24288 Set_SPARK_Pragma_Inherited (Spec_Id, False);
24290 -- When the pragma applies to the anonymous object created for
24291 -- a single task type, decorate the type as well. This scenario
24292 -- arises when the single task type lacks a task definition,
24293 -- therefore there is no issue with respect to a potential
24294 -- pragma SPARK_Mode in the private part.
24296 -- task type Anon_Task_Typ;
24297 -- Obj : Anon_Task_Typ;
24298 -- pragma SPARK_Mode ...;
24300 if Is_Single_Task_Object (Spec_Id) then
24301 Set_SPARK_Pragma (Spec_Typ, N);
24302 Set_SPARK_Pragma_Inherited (Spec_Typ, False);
24303 Set_SPARK_Aux_Pragma (Spec_Typ, N);
24304 Set_SPARK_Aux_Pragma_Inherited (Spec_Typ, True);
24305 end if;
24306 end Process_Overloadable;
24308 --------------------------
24309 -- Process_Private_Part --
24310 --------------------------
24312 procedure Process_Private_Part (Decl : Node_Id) is
24313 Spec_Id : constant Entity_Id := Defining_Entity (Decl);
24315 begin
24316 Check_Library_Level_Entity (Spec_Id);
24318 -- Verify the legality against:
24319 -- * The mode of the visible declarations
24321 Check_Pragma_Conformance
24322 (Context_Pragma => Empty,
24323 Entity => Spec_Id,
24324 Entity_Pragma => SPARK_Pragma (Spec_Id));
24326 Set_SPARK_Context;
24327 Set_SPARK_Aux_Pragma (Spec_Id, N);
24328 Set_SPARK_Aux_Pragma_Inherited (Spec_Id, False);
24329 end Process_Private_Part;
24331 ----------------------------
24332 -- Process_Statement_Part --
24333 ----------------------------
24335 procedure Process_Statement_Part (Decl : Node_Id) is
24336 Body_Id : constant Entity_Id := Defining_Entity (Decl);
24338 begin
24339 Check_Library_Level_Entity (Body_Id);
24341 -- Verify the legality against:
24342 -- * The mode of the body declarations
24344 Check_Pragma_Conformance
24345 (Context_Pragma => Empty,
24346 Entity => Body_Id,
24347 Entity_Pragma => SPARK_Pragma (Body_Id));
24349 Set_SPARK_Context;
24350 Set_SPARK_Aux_Pragma (Body_Id, N);
24351 Set_SPARK_Aux_Pragma_Inherited (Body_Id, False);
24352 end Process_Statement_Part;
24354 --------------------------
24355 -- Process_Visible_Part --
24356 --------------------------
24358 procedure Process_Visible_Part (Decl : Node_Id) is
24359 Spec_Id : constant Entity_Id := Defining_Entity (Decl);
24360 Obj_Id : Entity_Id;
24362 begin
24363 Check_Library_Level_Entity (Spec_Id);
24365 -- Verify the legality against:
24366 -- * The mode of the context
24368 Check_Pragma_Conformance
24369 (Context_Pragma => SPARK_Pragma (Spec_Id),
24370 Entity => Empty,
24371 Entity_Pragma => Empty);
24373 -- A task unit declared without a definition does not set the
24374 -- SPARK_Mode of the context because the task does not have any
24375 -- entries that could inherit the mode.
24377 if Nkind (Decl) not in
24378 N_Single_Task_Declaration | N_Task_Type_Declaration
24379 then
24380 Set_SPARK_Context;
24381 end if;
24383 Set_SPARK_Pragma (Spec_Id, N);
24384 Set_SPARK_Pragma_Inherited (Spec_Id, False);
24385 Set_SPARK_Aux_Pragma (Spec_Id, N);
24386 Set_SPARK_Aux_Pragma_Inherited (Spec_Id, True);
24388 -- When the pragma applies to a single protected or task type,
24389 -- decorate the corresponding anonymous object as well.
24391 -- protected Anon_Prot_Typ is
24392 -- pragma SPARK_Mode ...;
24393 -- ...
24394 -- end Anon_Prot_Typ;
24396 -- Obj : Anon_Prot_Typ;
24398 if Is_Single_Concurrent_Type (Spec_Id) then
24399 Obj_Id := Anonymous_Object (Spec_Id);
24401 Set_SPARK_Pragma (Obj_Id, N);
24402 Set_SPARK_Pragma_Inherited (Obj_Id, False);
24403 end if;
24404 end Process_Visible_Part;
24406 -----------------------
24407 -- Set_SPARK_Context --
24408 -----------------------
24410 procedure Set_SPARK_Context is
24411 begin
24412 SPARK_Mode := Mode_Id;
24413 SPARK_Mode_Pragma := N;
24414 end Set_SPARK_Context;
24416 -- Local variables
24418 Context : Node_Id;
24419 Mode : Name_Id;
24420 Stmt : Node_Id;
24422 -- Start of processing for Do_SPARK_Mode
24424 begin
24425 GNAT_Pragma;
24426 Check_No_Identifiers;
24427 Check_At_Most_N_Arguments (1);
24429 -- Check the legality of the mode (no argument = ON)
24431 if Arg_Count = 1 then
24432 Check_Arg_Is_One_Of (Arg1, Name_Auto, Name_On, Name_Off);
24433 Mode := Chars (Get_Pragma_Arg (Arg1));
24434 else
24435 Mode := Name_On;
24436 end if;
24438 Mode_Id := Get_SPARK_Mode_Type (Mode);
24439 Context := Parent (N);
24441 -- When a SPARK_Mode pragma appears inside an instantiation whose
24442 -- enclosing context has SPARK_Mode set to "off", the pragma has
24443 -- no semantic effect.
24445 if Ignore_SPARK_Mode_Pragmas_In_Instance
24446 and then Mode_Id /= Off
24447 then
24448 Rewrite (N, Make_Null_Statement (Loc));
24449 Analyze (N);
24450 return;
24451 end if;
24453 -- The pragma appears in a configuration file
24455 if No (Context) then
24456 Check_Valid_Configuration_Pragma;
24458 if Present (SPARK_Mode_Pragma) then
24459 Duplication_Error
24460 (Prag => N,
24461 Prev => SPARK_Mode_Pragma);
24462 raise Pragma_Exit;
24463 end if;
24465 Set_SPARK_Context;
24467 -- The pragma acts as a configuration pragma in a compilation unit
24469 -- pragma SPARK_Mode ...;
24470 -- package Pack is ...;
24472 elsif Nkind (Context) = N_Compilation_Unit
24473 and then List_Containing (N) = Context_Items (Context)
24474 then
24475 Check_Valid_Configuration_Pragma;
24476 Set_SPARK_Context;
24478 -- Otherwise the placement of the pragma within the tree dictates
24479 -- its associated construct. Inspect the declarative list where
24480 -- the pragma resides to find a potential construct.
24482 else
24483 -- An explicit mode of Auto is only allowed as a configuration
24484 -- pragma. Escape "pragma" to avoid replacement with "aspect".
24486 if Mode_Id = None then
24487 Error_Pragma_Arg
24488 ("only configuration 'p'r'a'g'm'a% can have value &",
24489 Arg1);
24490 end if;
24492 Stmt := Prev (N);
24493 while Present (Stmt) loop
24495 -- Skip prior pragmas, but check for duplicates. Note that
24496 -- this also takes care of pragmas generated for aspects.
24498 if Nkind (Stmt) = N_Pragma then
24499 if Pragma_Name (Stmt) = Pname then
24500 Duplication_Error
24501 (Prag => N,
24502 Prev => Stmt);
24503 raise Pragma_Exit;
24504 end if;
24506 -- The pragma applies to an expression function that has
24507 -- already been rewritten into a subprogram declaration.
24509 -- function Expr_Func return ... is (...);
24510 -- pragma SPARK_Mode ...;
24512 elsif Nkind (Stmt) = N_Subprogram_Declaration
24513 and then Nkind (Original_Node (Stmt)) =
24514 N_Expression_Function
24515 then
24516 Process_Overloadable (Stmt);
24517 return;
24519 -- The pragma applies to the anonymous object created for a
24520 -- single concurrent type.
24522 -- protected type Anon_Prot_Typ ...;
24523 -- Obj : Anon_Prot_Typ;
24524 -- pragma SPARK_Mode ...;
24526 elsif Nkind (Stmt) = N_Object_Declaration
24527 and then Is_Single_Concurrent_Object
24528 (Defining_Entity (Stmt))
24529 then
24530 Process_Overloadable (Stmt);
24531 return;
24533 -- Skip internally generated code
24535 elsif not Comes_From_Source (Stmt) then
24536 null;
24538 -- The pragma applies to an entry or [generic] subprogram
24539 -- declaration.
24541 -- entry Ent ...;
24542 -- pragma SPARK_Mode ...;
24544 -- [generic]
24545 -- procedure Proc ...;
24546 -- pragma SPARK_Mode ...;
24548 elsif Nkind (Stmt) in N_Generic_Subprogram_Declaration
24549 | N_Subprogram_Declaration
24550 or else (Nkind (Stmt) = N_Entry_Declaration
24551 and then Is_Protected_Type
24552 (Scope (Defining_Entity (Stmt))))
24553 then
24554 Process_Overloadable (Stmt);
24555 return;
24557 -- Otherwise the pragma does not apply to a legal construct
24558 -- or it does not appear at the top of a declarative or a
24559 -- statement list. Issue an error and stop the analysis.
24561 else
24562 Pragma_Misplaced;
24563 end if;
24565 Prev (Stmt);
24566 end loop;
24568 -- The pragma applies to a package or a subprogram that acts as
24569 -- a compilation unit.
24571 -- procedure Proc ...;
24572 -- pragma SPARK_Mode ...;
24574 if Nkind (Context) = N_Compilation_Unit_Aux then
24575 Context := Unit (Parent (Context));
24576 end if;
24578 -- The pragma appears at the top of entry, package, protected
24579 -- unit, subprogram or task unit body declarations.
24581 -- entry Ent when ... is
24582 -- pragma SPARK_Mode ...;
24584 -- package body Pack is
24585 -- pragma SPARK_Mode ...;
24587 -- procedure Proc ... is
24588 -- pragma SPARK_Mode;
24590 -- protected body Prot is
24591 -- pragma SPARK_Mode ...;
24593 if Nkind (Context) in N_Entry_Body
24594 | N_Package_Body
24595 | N_Protected_Body
24596 | N_Subprogram_Body
24597 | N_Task_Body
24598 then
24599 Process_Body (Context);
24601 -- The pragma appears at the top of the visible or private
24602 -- declaration of a package spec, protected or task unit.
24604 -- package Pack is
24605 -- pragma SPARK_Mode ...;
24606 -- private
24607 -- pragma SPARK_Mode ...;
24609 -- protected [type] Prot is
24610 -- pragma SPARK_Mode ...;
24611 -- private
24612 -- pragma SPARK_Mode ...;
24614 elsif Nkind (Context) in N_Package_Specification
24615 | N_Protected_Definition
24616 | N_Task_Definition
24617 then
24618 if List_Containing (N) = Visible_Declarations (Context) then
24619 Process_Visible_Part (Parent (Context));
24620 else
24621 Process_Private_Part (Parent (Context));
24622 end if;
24624 -- The pragma appears at the top of package body statements
24626 -- package body Pack is
24627 -- begin
24628 -- pragma SPARK_Mode;
24630 elsif Nkind (Context) = N_Handled_Sequence_Of_Statements
24631 and then Nkind (Parent (Context)) = N_Package_Body
24632 then
24633 Process_Statement_Part (Parent (Context));
24635 -- The pragma appeared as an aspect of a [generic] subprogram
24636 -- declaration that acts as a compilation unit.
24638 -- [generic]
24639 -- procedure Proc ...;
24640 -- pragma SPARK_Mode ...;
24642 elsif Nkind (Context) in N_Generic_Subprogram_Declaration
24643 | N_Subprogram_Declaration
24644 then
24645 Process_Overloadable (Context);
24647 -- The pragma does not apply to a legal construct, issue error
24649 else
24650 Pragma_Misplaced;
24651 end if;
24652 end if;
24653 end Do_SPARK_Mode;
24655 --------------------------------
24656 -- Static_Elaboration_Desired --
24657 --------------------------------
24659 -- pragma Static_Elaboration_Desired (DIRECT_NAME);
24661 when Pragma_Static_Elaboration_Desired =>
24662 GNAT_Pragma;
24663 Check_At_Most_N_Arguments (1);
24665 if Is_Compilation_Unit (Current_Scope)
24666 and then Ekind (Current_Scope) = E_Package
24667 then
24668 Set_Static_Elaboration_Desired (Current_Scope, True);
24669 else
24670 Error_Pragma ("pragma% must apply to a library-level package");
24671 end if;
24673 ------------------
24674 -- Storage_Size --
24675 ------------------
24677 -- pragma Storage_Size (EXPRESSION);
24679 when Pragma_Storage_Size => Storage_Size : declare
24680 P : constant Node_Id := Parent (N);
24681 Arg : Node_Id;
24683 begin
24684 Check_No_Identifiers;
24685 Check_Arg_Count (1);
24687 -- The expression must be analyzed in the special manner described
24688 -- in "Handling of Default Expressions" in sem.ads.
24690 Arg := Get_Pragma_Arg (Arg1);
24691 Preanalyze_Spec_Expression (Arg, Any_Integer);
24693 if not Is_OK_Static_Expression (Arg) then
24694 Check_Restriction (Static_Storage_Size, Arg);
24695 end if;
24697 if Nkind (P) /= N_Task_Definition then
24698 Pragma_Misplaced;
24700 else
24701 if Has_Storage_Size_Pragma (P) then
24702 Error_Pragma ("duplicate pragma% not allowed");
24703 else
24704 Set_Has_Storage_Size_Pragma (P, True);
24705 end if;
24707 Record_Rep_Item (Defining_Identifier (Parent (P)), N);
24708 end if;
24709 end Storage_Size;
24711 ------------------
24712 -- Storage_Unit --
24713 ------------------
24715 -- pragma Storage_Unit (NUMERIC_LITERAL);
24717 -- Only permitted argument is System'Storage_Unit value
24719 when Pragma_Storage_Unit =>
24720 Check_No_Identifiers;
24721 Check_Arg_Count (1);
24722 Check_Arg_Is_Integer_Literal (Arg1);
24724 if Intval (Get_Pragma_Arg (Arg1)) /=
24725 UI_From_Int (Ttypes.System_Storage_Unit)
24726 then
24727 Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
24728 Error_Pragma_Arg
24729 ("the only allowed argument for pragma% is ^", Arg1);
24730 end if;
24732 --------------------
24733 -- Stream_Convert --
24734 --------------------
24736 -- pragma Stream_Convert (
24737 -- [Entity =>] type_LOCAL_NAME,
24738 -- [Read =>] function_NAME,
24739 -- [Write =>] function NAME);
24741 when Pragma_Stream_Convert => Stream_Convert : declare
24742 procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
24743 -- Check that the given argument is the name of a local function
24744 -- of one argument that is not overloaded earlier in the current
24745 -- local scope. A check is also made that the argument is a
24746 -- function with one parameter.
24748 --------------------------------------
24749 -- Check_OK_Stream_Convert_Function --
24750 --------------------------------------
24752 procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
24753 Ent : Entity_Id;
24755 begin
24756 Check_Arg_Is_Local_Name (Arg);
24757 Ent := Entity (Get_Pragma_Arg (Arg));
24759 if Has_Homonym (Ent) then
24760 Error_Pragma_Arg
24761 ("argument for pragma% may not be overloaded", Arg);
24762 end if;
24764 if Ekind (Ent) /= E_Function
24765 or else No (First_Formal (Ent))
24766 or else Present (Next_Formal (First_Formal (Ent)))
24767 then
24768 Error_Pragma_Arg
24769 ("argument for pragma% must be function of one argument",
24770 Arg);
24771 elsif Is_Abstract_Subprogram (Ent) then
24772 Error_Pragma_Arg
24773 ("argument for pragma% cannot be abstract", Arg);
24774 end if;
24775 end Check_OK_Stream_Convert_Function;
24777 -- Start of processing for Stream_Convert
24779 begin
24780 GNAT_Pragma;
24781 Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
24782 Check_Arg_Count (3);
24783 Check_Optional_Identifier (Arg1, Name_Entity);
24784 Check_Optional_Identifier (Arg2, Name_Read);
24785 Check_Optional_Identifier (Arg3, Name_Write);
24786 Check_Arg_Is_Local_Name (Arg1);
24787 Check_OK_Stream_Convert_Function (Arg2);
24788 Check_OK_Stream_Convert_Function (Arg3);
24790 declare
24791 Typ : constant Entity_Id :=
24792 Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
24793 Read : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
24794 Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
24796 begin
24797 Check_First_Subtype (Arg1);
24799 -- Check for too early or too late. Note that we don't enforce
24800 -- the rule about primitive operations in this case, since, as
24801 -- is the case for explicit stream attributes themselves, these
24802 -- restrictions are not appropriate. Note that the chaining of
24803 -- the pragma by Rep_Item_Too_Late is actually the critical
24804 -- processing done for this pragma.
24806 if Rep_Item_Too_Early (Typ, N)
24807 or else
24808 Rep_Item_Too_Late (Typ, N, FOnly => True)
24809 then
24810 return;
24811 end if;
24813 -- Return if previous error
24815 if Etype (Typ) = Any_Type
24816 or else
24817 Etype (Read) = Any_Type
24818 or else
24819 Etype (Write) = Any_Type
24820 then
24821 return;
24822 end if;
24824 -- Error checks
24826 if Underlying_Type (Etype (Read)) /= Typ then
24827 Error_Pragma_Arg
24828 ("incorrect return type for function&", Arg2);
24829 end if;
24831 if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
24832 Error_Pragma_Arg
24833 ("incorrect parameter type for function&", Arg3);
24834 end if;
24836 if Underlying_Type (Etype (First_Formal (Read))) /=
24837 Underlying_Type (Etype (Write))
24838 then
24839 Error_Pragma_Arg
24840 ("result type of & does not match Read parameter type",
24841 Arg3);
24842 end if;
24843 end;
24844 end Stream_Convert;
24846 ------------------
24847 -- Style_Checks --
24848 ------------------
24850 -- pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
24852 -- This is processed by the parser since some of the style checks
24853 -- take place during source scanning and parsing. This means that
24854 -- we don't need to issue error messages here.
24856 when Pragma_Style_Checks => Style_Checks : declare
24857 A : constant Node_Id := Get_Pragma_Arg (Arg1);
24858 S : String_Id;
24859 C : Char_Code;
24861 begin
24862 GNAT_Pragma;
24863 Check_No_Identifiers;
24865 -- Two argument form
24867 if Arg_Count = 2 then
24868 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
24870 declare
24871 E_Id : Node_Id;
24872 E : Entity_Id;
24874 begin
24875 E_Id := Get_Pragma_Arg (Arg2);
24876 Analyze (E_Id);
24878 if not Is_Entity_Name (E_Id) then
24879 Error_Pragma_Arg
24880 ("second argument of pragma% must be entity name",
24881 Arg2);
24882 end if;
24884 E := Entity (E_Id);
24886 if not Ignore_Style_Checks_Pragmas then
24887 if E = Any_Id then
24888 return;
24889 else
24890 loop
24891 Set_Suppress_Style_Checks
24892 (E, Chars (Get_Pragma_Arg (Arg1)) = Name_Off);
24893 exit when No (Homonym (E));
24894 E := Homonym (E);
24895 end loop;
24896 end if;
24897 end if;
24898 end;
24900 -- One argument form
24902 else
24903 Check_Arg_Count (1);
24905 if Nkind (A) = N_String_Literal then
24906 S := Strval (A);
24908 declare
24909 Slen : constant Natural := Natural (String_Length (S));
24910 Options : String (1 .. Slen);
24911 J : Positive;
24913 begin
24914 J := 1;
24915 loop
24916 C := Get_String_Char (S, Pos (J));
24917 exit when not In_Character_Range (C);
24918 Options (J) := Get_Character (C);
24920 -- If at end of string, set options. As per discussion
24921 -- above, no need to check for errors, since we issued
24922 -- them in the parser.
24924 if J = Slen then
24925 if not Ignore_Style_Checks_Pragmas then
24926 Set_Style_Check_Options (Options);
24927 end if;
24929 exit;
24930 end if;
24932 J := J + 1;
24933 end loop;
24934 end;
24936 elsif Nkind (A) = N_Identifier then
24937 if Chars (A) = Name_All_Checks then
24938 if not Ignore_Style_Checks_Pragmas then
24939 if GNAT_Mode then
24940 Set_GNAT_Style_Check_Options;
24941 else
24942 Set_Default_Style_Check_Options;
24943 end if;
24944 end if;
24946 elsif Chars (A) = Name_On then
24947 if not Ignore_Style_Checks_Pragmas then
24948 Style_Check := True;
24949 end if;
24951 elsif Chars (A) = Name_Off then
24952 if not Ignore_Style_Checks_Pragmas then
24953 Style_Check := False;
24954 end if;
24955 end if;
24956 end if;
24957 end if;
24958 end Style_Checks;
24960 ------------------------
24961 -- Subprogram_Variant --
24962 ------------------------
24964 -- pragma Subprogram_Variant ( SUBPROGRAM_VARIANT_LIST );
24966 -- SUBPROGRAM_VARIANT_LIST ::= STRUCTURAL_SUBPROGRAM_VARIANT_ITEM
24967 -- | NUMERIC_SUBPROGRAM_VARIANT_ITEMS
24968 -- NUMERIC_SUBPROGRAM_VARIANT_ITEMS ::=
24969 -- NUMERIC_SUBPROGRAM_VARIANT_ITEM
24970 -- {, NUMERIC_SUBPROGRAM_VARIANT_ITEM}
24971 -- NUMERIC_SUBPROGRAM_VARIANT_ITEM ::= CHANGE_DIRECTION => EXPRESSION
24972 -- STRUCTURAL_SUBPROGRAM_VARIANT_ITEM ::= Structural => EXPRESSION
24973 -- CHANGE_DIRECTION ::= Increases | Decreases
24975 -- Characteristics:
24977 -- * Analysis - The annotation undergoes initial checks to verify
24978 -- the legal placement and context. Secondary checks preanalyze the
24979 -- expressions in:
24981 -- Analyze_Subprogram_Variant_In_Decl_Part
24983 -- * Expansion - The annotation is expanded during the expansion of
24984 -- the related subprogram [body] contract as performed in:
24986 -- Expand_Subprogram_Contract
24988 -- * Template - The annotation utilizes the generic template of the
24989 -- related subprogram [body] when it is:
24991 -- aspect on subprogram declaration
24992 -- aspect on stand-alone subprogram body
24993 -- pragma on stand-alone subprogram body
24995 -- The annotation must prepare its own template when it is:
24997 -- pragma on subprogram declaration
24999 -- * Globals - Capture of global references must occur after full
25000 -- analysis.
25002 -- * Instance - The annotation is instantiated automatically when
25003 -- the related generic subprogram [body] is instantiated except for
25004 -- the "pragma on subprogram declaration" case. In that scenario
25005 -- the annotation must instantiate itself.
25007 when Pragma_Subprogram_Variant => Subprogram_Variant : declare
25008 Spec_Id : Entity_Id;
25009 Subp_Decl : Node_Id;
25010 Subp_Spec : Node_Id;
25012 begin
25013 GNAT_Pragma;
25014 Check_No_Identifiers;
25015 Check_Arg_Count (1);
25017 -- Ensure the proper placement of the pragma. Subprogram_Variant
25018 -- must be associated with a subprogram declaration or a body that
25019 -- acts as a spec.
25021 Subp_Decl :=
25022 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
25024 -- Generic subprogram
25026 if Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
25027 null;
25029 -- Body acts as spec
25031 elsif Nkind (Subp_Decl) = N_Subprogram_Body
25032 and then No (Corresponding_Spec (Subp_Decl))
25033 then
25034 null;
25036 -- Body stub acts as spec
25038 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
25039 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
25040 then
25041 null;
25043 -- Subprogram
25045 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
25046 Subp_Spec := Specification (Subp_Decl);
25048 -- Pragma Subprogram_Variant is forbidden on null procedures,
25049 -- as this may lead to potential ambiguities in behavior when
25050 -- interface null procedures are involved. Also, it just
25051 -- wouldn't make sense, because null procedure is not
25052 -- recursive.
25054 if Nkind (Subp_Spec) = N_Procedure_Specification
25055 and then Null_Present (Subp_Spec)
25056 then
25057 Error_Msg_N (Fix_Error
25058 ("pragma % cannot apply to null procedure"), N);
25059 return;
25060 end if;
25062 else
25063 Pragma_Misplaced;
25064 end if;
25066 Spec_Id := Unique_Defining_Entity (Subp_Decl);
25068 -- A pragma that applies to a Ghost entity becomes Ghost for the
25069 -- purposes of legality checks and removal of ignored Ghost code.
25071 Mark_Ghost_Pragma (N, Spec_Id);
25072 Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
25074 -- Chain the pragma on the contract for further processing by
25075 -- Analyze_Subprogram_Variant_In_Decl_Part.
25077 Add_Contract_Item (N, Defining_Entity (Subp_Decl));
25079 -- Fully analyze the pragma when it appears inside a subprogram
25080 -- body because it cannot benefit from forward references.
25082 if Nkind (Subp_Decl) in N_Subprogram_Body
25083 | N_Subprogram_Body_Stub
25084 then
25085 -- The legality checks of pragma Subprogram_Variant are
25086 -- affected by the SPARK mode in effect and the volatility
25087 -- of the context. Analyze all pragmas in a specific order.
25089 Analyze_If_Present (Pragma_SPARK_Mode);
25090 Analyze_If_Present (Pragma_Volatile_Function);
25091 Analyze_Subprogram_Variant_In_Decl_Part (N);
25092 end if;
25093 end Subprogram_Variant;
25095 --------------
25096 -- Subtitle --
25097 --------------
25099 -- pragma Subtitle ([Subtitle =>] STRING_LITERAL);
25101 when Pragma_Subtitle =>
25102 GNAT_Pragma;
25103 Check_Arg_Count (1);
25104 Check_Optional_Identifier (Arg1, Name_Subtitle);
25105 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
25106 Store_Note (N);
25108 --------------
25109 -- Suppress --
25110 --------------
25112 -- pragma Suppress (IDENTIFIER [, [On =>] NAME]);
25114 when Pragma_Suppress =>
25115 Process_Suppress_Unsuppress (Suppress_Case => True);
25117 ------------------
25118 -- Suppress_All --
25119 ------------------
25121 -- pragma Suppress_All;
25123 -- The only check made here is that the pragma has no arguments.
25124 -- There are no placement rules, and the processing required (setting
25125 -- the Has_Pragma_Suppress_All flag in the compilation unit node was
25126 -- taken care of by the parser). Process_Compilation_Unit_Pragmas
25127 -- then creates and inserts a pragma Suppress (All_Checks).
25129 when Pragma_Suppress_All =>
25130 GNAT_Pragma;
25131 Check_Arg_Count (0);
25133 -------------------------
25134 -- Suppress_Debug_Info --
25135 -------------------------
25137 -- pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
25139 when Pragma_Suppress_Debug_Info => Suppress_Debug_Info : declare
25140 Nam_Id : Entity_Id;
25142 begin
25143 GNAT_Pragma;
25144 Check_Arg_Count (1);
25145 Check_Optional_Identifier (Arg1, Name_Entity);
25146 Check_Arg_Is_Local_Name (Arg1);
25148 Nam_Id := Entity (Get_Pragma_Arg (Arg1));
25150 -- A pragma that applies to a Ghost entity becomes Ghost for the
25151 -- purposes of legality checks and removal of ignored Ghost code.
25153 Mark_Ghost_Pragma (N, Nam_Id);
25154 Set_Debug_Info_Off (Nam_Id);
25155 end Suppress_Debug_Info;
25157 ----------------------------------
25158 -- Suppress_Exception_Locations --
25159 ----------------------------------
25161 -- pragma Suppress_Exception_Locations;
25163 when Pragma_Suppress_Exception_Locations =>
25164 GNAT_Pragma;
25165 Check_Arg_Count (0);
25166 Check_Valid_Configuration_Pragma;
25167 Exception_Locations_Suppressed := True;
25169 -----------------------------
25170 -- Suppress_Initialization --
25171 -----------------------------
25173 -- pragma Suppress_Initialization ([Entity =>] type_Name);
25175 when Pragma_Suppress_Initialization => Suppress_Init : declare
25176 E : Entity_Id;
25177 E_Id : Node_Id;
25179 begin
25180 GNAT_Pragma;
25181 Check_Arg_Count (1);
25182 Check_Optional_Identifier (Arg1, Name_Entity);
25183 Check_Arg_Is_Local_Name (Arg1);
25185 E_Id := Get_Pragma_Arg (Arg1);
25187 if Etype (E_Id) = Any_Type then
25188 return;
25189 end if;
25191 E := Entity (E_Id);
25193 -- A pragma that applies to a Ghost entity becomes Ghost for the
25194 -- purposes of legality checks and removal of ignored Ghost code.
25196 Mark_Ghost_Pragma (N, E);
25198 if not Is_Type (E) and then Ekind (E) /= E_Variable then
25199 Error_Pragma_Arg
25200 ("pragma% requires variable, type or subtype", Arg1);
25201 end if;
25203 if Rep_Item_Too_Early (E, N)
25204 or else
25205 Rep_Item_Too_Late (E, N, FOnly => True)
25206 then
25207 return;
25208 end if;
25210 -- For incomplete/private type, set flag on full view
25212 if Is_Incomplete_Or_Private_Type (E) then
25213 if No (Full_View (Base_Type (E))) then
25214 Error_Pragma_Arg
25215 ("argument of pragma% cannot be an incomplete type", Arg1);
25216 else
25217 Set_Suppress_Initialization (Full_View (E));
25218 end if;
25220 -- For first subtype, set flag on base type
25222 elsif Is_First_Subtype (E) then
25223 Set_Suppress_Initialization (Base_Type (E));
25225 -- For other than first subtype, set flag on subtype or variable
25227 else
25228 Set_Suppress_Initialization (E);
25229 end if;
25230 end Suppress_Init;
25232 -----------------
25233 -- System_Name --
25234 -----------------
25236 -- pragma System_Name (DIRECT_NAME);
25238 -- Syntax check: one argument, which must be the identifier GNAT or
25239 -- the identifier GCC, no other identifiers are acceptable.
25241 when Pragma_System_Name =>
25242 GNAT_Pragma;
25243 Check_No_Identifiers;
25244 Check_Arg_Count (1);
25245 Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
25247 -----------------------------
25248 -- Task_Dispatching_Policy --
25249 -----------------------------
25251 -- pragma Task_Dispatching_Policy (policy_IDENTIFIER);
25253 when Pragma_Task_Dispatching_Policy => declare
25254 DP : Character;
25256 begin
25257 Check_Ada_83_Warning;
25258 Check_Arg_Count (1);
25259 Check_No_Identifiers;
25260 Check_Arg_Is_Task_Dispatching_Policy (Arg1);
25261 Check_Valid_Configuration_Pragma;
25262 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
25263 DP := Fold_Upper (Name_Buffer (1));
25265 if Task_Dispatching_Policy /= ' '
25266 and then Task_Dispatching_Policy /= DP
25267 then
25268 Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
25269 Error_Pragma
25270 ("task dispatching policy incompatible with policy#");
25272 -- Set new policy, but always preserve System_Location since we
25273 -- like the error message with the run time name.
25275 else
25276 Task_Dispatching_Policy := DP;
25278 if Task_Dispatching_Policy_Sloc /= System_Location then
25279 Task_Dispatching_Policy_Sloc := Loc;
25280 end if;
25281 end if;
25282 end;
25284 ---------------
25285 -- Task_Info --
25286 ---------------
25288 -- pragma Task_Info (EXPRESSION);
25290 when Pragma_Task_Info => Task_Info : declare
25291 P : constant Node_Id := Parent (N);
25292 Ent : Entity_Id;
25294 begin
25295 GNAT_Pragma;
25297 if Warn_On_Obsolescent_Feature then
25298 Error_Msg_N
25299 ("'G'N'A'T pragma Task_Info is now obsolete, use 'C'P'U "
25300 & "instead?j?", N);
25301 end if;
25303 if Nkind (P) /= N_Task_Definition then
25304 Error_Pragma ("pragma% must appear in task definition");
25305 end if;
25307 Check_No_Identifiers;
25308 Check_Arg_Count (1);
25310 Analyze_And_Resolve
25311 (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
25313 if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
25314 return;
25315 end if;
25317 Ent := Defining_Identifier (Parent (P));
25319 -- Check duplicate pragma before we chain the pragma in the Rep
25320 -- Item chain of Ent.
25322 if Has_Rep_Pragma
25323 (Ent, Name_Task_Info, Check_Parents => False)
25324 then
25325 Error_Pragma ("duplicate pragma% not allowed");
25326 end if;
25328 Record_Rep_Item (Ent, N);
25329 end Task_Info;
25331 ---------------
25332 -- Task_Name --
25333 ---------------
25335 -- pragma Task_Name (string_EXPRESSION);
25337 when Pragma_Task_Name => Task_Name : declare
25338 P : constant Node_Id := Parent (N);
25339 Arg : Node_Id;
25340 Ent : Entity_Id;
25342 begin
25343 Check_No_Identifiers;
25344 Check_Arg_Count (1);
25346 Arg := Get_Pragma_Arg (Arg1);
25348 -- The expression is used in the call to Create_Task, and must be
25349 -- expanded there, not in the context of the current spec. It must
25350 -- however be analyzed to capture global references, in case it
25351 -- appears in a generic context.
25353 Preanalyze_And_Resolve (Arg, Standard_String);
25355 if Nkind (P) /= N_Task_Definition then
25356 Pragma_Misplaced;
25357 end if;
25359 Ent := Defining_Identifier (Parent (P));
25361 -- Check duplicate pragma before we chain the pragma in the Rep
25362 -- Item chain of Ent.
25364 if Has_Rep_Pragma
25365 (Ent, Name_Task_Name, Check_Parents => False)
25366 then
25367 Error_Pragma ("duplicate pragma% not allowed");
25368 end if;
25370 Record_Rep_Item (Ent, N);
25371 end Task_Name;
25373 ------------------
25374 -- Task_Storage --
25375 ------------------
25377 -- pragma Task_Storage (
25378 -- [Task_Type =>] LOCAL_NAME,
25379 -- [Top_Guard =>] static_integer_EXPRESSION);
25381 when Pragma_Task_Storage => Task_Storage : declare
25382 Args : Args_List (1 .. 2);
25383 Names : constant Name_List (1 .. 2) := (
25384 Name_Task_Type,
25385 Name_Top_Guard);
25387 Task_Type : Node_Id renames Args (1);
25388 Top_Guard : Node_Id renames Args (2);
25390 Ent : Entity_Id;
25392 begin
25393 GNAT_Pragma;
25394 Gather_Associations (Names, Args);
25396 if No (Task_Type) then
25397 Error_Pragma
25398 ("missing task_type argument for pragma%");
25399 end if;
25401 Check_Arg_Is_Local_Name (Task_Type);
25403 Ent := Entity (Task_Type);
25405 if not Is_Task_Type (Ent) then
25406 Error_Pragma_Arg
25407 ("argument for pragma% must be task type", Task_Type);
25408 end if;
25410 if No (Top_Guard) then
25411 Error_Pragma_Arg
25412 ("pragma% takes two arguments", Task_Type);
25413 else
25414 Check_Arg_Is_OK_Static_Expression (Top_Guard, Any_Integer);
25415 end if;
25417 Check_First_Subtype (Task_Type);
25419 if Rep_Item_Too_Late (Ent, N) then
25420 return;
25421 end if;
25422 end Task_Storage;
25424 ---------------
25425 -- Test_Case --
25426 ---------------
25428 -- pragma Test_Case
25429 -- ([Name =>] Static_String_EXPRESSION
25430 -- ,[Mode =>] MODE_TYPE
25431 -- [, Requires => Boolean_EXPRESSION]
25432 -- [, Ensures => Boolean_EXPRESSION]);
25434 -- MODE_TYPE ::= Nominal | Robustness
25436 -- Characteristics:
25438 -- * Analysis - The annotation undergoes initial checks to verify
25439 -- the legal placement and context. Secondary checks preanalyze the
25440 -- expressions in:
25442 -- Analyze_Test_Case_In_Decl_Part
25444 -- * Expansion - None.
25446 -- * Template - The annotation utilizes the generic template of the
25447 -- related subprogram when it is:
25449 -- aspect on subprogram declaration
25451 -- The annotation must prepare its own template when it is:
25453 -- pragma on subprogram declaration
25455 -- * Globals - Capture of global references must occur after full
25456 -- analysis.
25458 -- * Instance - The annotation is instantiated automatically when
25459 -- the related generic subprogram is instantiated except for the
25460 -- "pragma on subprogram declaration" case. In that scenario the
25461 -- annotation must instantiate itself.
25463 when Pragma_Test_Case => Test_Case : declare
25464 procedure Check_Distinct_Name (Subp_Id : Entity_Id);
25465 -- Ensure that the contract of subprogram Subp_Id does not contain
25466 -- another Test_Case pragma with the same Name as the current one.
25468 -------------------------
25469 -- Check_Distinct_Name --
25470 -------------------------
25472 procedure Check_Distinct_Name (Subp_Id : Entity_Id) is
25473 Items : constant Node_Id := Contract (Subp_Id);
25474 Name : constant String_Id := Get_Name_From_CTC_Pragma (N);
25475 Prag : Node_Id;
25477 begin
25478 -- Inspect all Test_Case pragma of the related subprogram
25479 -- looking for one with a duplicate "Name" argument.
25481 if Present (Items) then
25482 Prag := Contract_Test_Cases (Items);
25483 while Present (Prag) loop
25484 if Pragma_Name (Prag) = Name_Test_Case
25485 and then Prag /= N
25486 and then String_Equal
25487 (Name, Get_Name_From_CTC_Pragma (Prag))
25488 then
25489 Error_Msg_Sloc := Sloc (Prag);
25490 Error_Pragma ("name for pragma % is already used #");
25491 end if;
25493 Prag := Next_Pragma (Prag);
25494 end loop;
25495 end if;
25496 end Check_Distinct_Name;
25498 -- Local variables
25500 Pack_Decl : constant Node_Id := Unit (Cunit (Current_Sem_Unit));
25501 Asp_Arg : Node_Id;
25502 Context : Node_Id;
25503 Subp_Decl : Node_Id;
25504 Subp_Id : Entity_Id;
25506 -- Start of processing for Test_Case
25508 begin
25509 GNAT_Pragma;
25510 Check_At_Least_N_Arguments (2);
25511 Check_At_Most_N_Arguments (4);
25512 Check_Arg_Order
25513 ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
25515 -- Argument "Name"
25517 Check_Optional_Identifier (Arg1, Name_Name);
25518 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
25520 -- Argument "Mode"
25522 Check_Optional_Identifier (Arg2, Name_Mode);
25523 Check_Arg_Is_One_Of (Arg2, Name_Nominal, Name_Robustness);
25525 -- Arguments "Requires" and "Ensures"
25527 if Present (Arg3) then
25528 if Present (Arg4) then
25529 Check_Identifier (Arg3, Name_Requires);
25530 Check_Identifier (Arg4, Name_Ensures);
25531 else
25532 Check_Identifier_Is_One_Of
25533 (Arg3, Name_Requires, Name_Ensures);
25534 end if;
25535 end if;
25537 -- Pragma Test_Case must be associated with a subprogram declared
25538 -- in a library-level package. First determine whether the current
25539 -- compilation unit is a legal context.
25541 if Nkind (Pack_Decl) in N_Package_Declaration
25542 | N_Generic_Package_Declaration
25543 then
25544 null;
25546 -- Otherwise the placement is illegal
25548 else
25549 Error_Pragma
25550 ("pragma % must be specified within a package declaration");
25551 end if;
25553 Subp_Decl := Find_Related_Declaration_Or_Body (N);
25555 -- Find the enclosing context
25557 Context := Parent (Subp_Decl);
25559 if Present (Context) then
25560 Context := Parent (Context);
25561 end if;
25563 -- Verify the placement of the pragma
25565 if Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
25566 Error_Pragma
25567 ("pragma % cannot be applied to abstract subprogram");
25569 elsif Nkind (Subp_Decl) = N_Entry_Declaration then
25570 Error_Pragma ("pragma % cannot be applied to entry");
25572 -- The context is a [generic] subprogram declared at the top level
25573 -- of the [generic] package unit.
25575 elsif Nkind (Subp_Decl) in N_Generic_Subprogram_Declaration
25576 | N_Subprogram_Declaration
25577 and then Present (Context)
25578 and then Nkind (Context) in N_Generic_Package_Declaration
25579 | N_Package_Declaration
25580 then
25581 null;
25583 -- Otherwise the placement is illegal
25585 else
25586 Error_Pragma
25587 ("pragma % must be applied to a library-level subprogram "
25588 & "declaration");
25589 end if;
25591 Subp_Id := Defining_Entity (Subp_Decl);
25593 -- A pragma that applies to a Ghost entity becomes Ghost for the
25594 -- purposes of legality checks and removal of ignored Ghost code.
25596 Mark_Ghost_Pragma (N, Subp_Id);
25598 -- Chain the pragma on the contract for further processing by
25599 -- Analyze_Test_Case_In_Decl_Part.
25601 Add_Contract_Item (N, Subp_Id);
25603 -- Preanalyze the original aspect argument "Name" for a generic
25604 -- subprogram to properly capture global references.
25606 if Is_Generic_Subprogram (Subp_Id) then
25607 Asp_Arg := Test_Case_Arg (N, Name_Name, From_Aspect => True);
25609 if Present (Asp_Arg) then
25611 -- The argument appears with an identifier in association
25612 -- form.
25614 if Nkind (Asp_Arg) = N_Component_Association then
25615 Asp_Arg := Expression (Asp_Arg);
25616 end if;
25618 Check_Expr_Is_OK_Static_Expression
25619 (Asp_Arg, Standard_String);
25620 end if;
25621 end if;
25623 -- Ensure that the all Test_Case pragmas of the related subprogram
25624 -- have distinct names.
25626 Check_Distinct_Name (Subp_Id);
25628 -- Fully analyze the pragma when it appears inside an entry
25629 -- or subprogram body because it cannot benefit from forward
25630 -- references.
25632 if Nkind (Subp_Decl) in N_Entry_Body
25633 | N_Subprogram_Body
25634 | N_Subprogram_Body_Stub
25635 then
25636 -- The legality checks of pragma Test_Case are affected by the
25637 -- SPARK mode in effect and the volatility of the context.
25638 -- Analyze all pragmas in a specific order.
25640 Analyze_If_Present (Pragma_SPARK_Mode);
25641 Analyze_If_Present (Pragma_Volatile_Function);
25642 Analyze_Test_Case_In_Decl_Part (N);
25643 end if;
25644 end Test_Case;
25646 --------------------------
25647 -- Thread_Local_Storage --
25648 --------------------------
25650 -- pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
25652 when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
25653 E : Entity_Id;
25654 Id : Node_Id;
25656 begin
25657 GNAT_Pragma;
25658 Check_Arg_Count (1);
25659 Check_Optional_Identifier (Arg1, Name_Entity);
25660 Check_Arg_Is_Library_Level_Local_Name (Arg1);
25662 Id := Get_Pragma_Arg (Arg1);
25664 if not Is_Entity_Name (Id)
25665 or else Ekind (Entity (Id)) /= E_Variable
25666 then
25667 Error_Pragma_Arg ("local variable name required", Arg1);
25668 end if;
25670 E := Entity (Id);
25672 -- A pragma that applies to a Ghost entity becomes Ghost for the
25673 -- purposes of legality checks and removal of ignored Ghost code.
25675 Mark_Ghost_Pragma (N, E);
25677 if Rep_Item_Too_Early (E, N)
25678 or else
25679 Rep_Item_Too_Late (E, N)
25680 then
25681 return;
25682 end if;
25684 Set_Has_Pragma_Thread_Local_Storage (E);
25685 Set_Has_Gigi_Rep_Item (E);
25686 end Thread_Local_Storage;
25688 ----------------
25689 -- Time_Slice --
25690 ----------------
25692 -- pragma Time_Slice (static_duration_EXPRESSION);
25694 when Pragma_Time_Slice => Time_Slice : declare
25695 Val : Ureal;
25696 Nod : Node_Id;
25698 begin
25699 GNAT_Pragma;
25700 Check_Arg_Count (1);
25701 Check_No_Identifiers;
25702 Check_In_Main_Program;
25703 Check_Arg_Is_OK_Static_Expression (Arg1, Standard_Duration);
25705 if not Error_Posted (Arg1) then
25706 Nod := Next (N);
25707 while Present (Nod) loop
25708 if Nkind (Nod) = N_Pragma
25709 and then Pragma_Name (Nod) = Name_Time_Slice
25710 then
25711 Error_Msg_Name_1 := Pname;
25712 Error_Msg_N ("duplicate pragma% not permitted", Nod);
25713 end if;
25715 Next (Nod);
25716 end loop;
25717 end if;
25719 -- Process only if in main unit
25721 if Get_Source_Unit (Loc) = Main_Unit then
25722 Opt.Time_Slice_Set := True;
25723 Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
25725 if Val <= Ureal_0 then
25726 Opt.Time_Slice_Value := 0;
25728 elsif Val > UR_From_Uint (UI_From_Int (1000)) then
25729 Opt.Time_Slice_Value := 1_000_000_000;
25731 else
25732 Opt.Time_Slice_Value :=
25733 UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
25734 end if;
25735 end if;
25736 end Time_Slice;
25738 -----------
25739 -- Title --
25740 -----------
25742 -- pragma Title (TITLING_OPTION [, TITLING OPTION]);
25744 -- TITLING_OPTION ::=
25745 -- [Title =>] STRING_LITERAL
25746 -- | [Subtitle =>] STRING_LITERAL
25748 when Pragma_Title => Title : declare
25749 Args : Args_List (1 .. 2);
25750 Names : constant Name_List (1 .. 2) := (
25751 Name_Title,
25752 Name_Subtitle);
25754 begin
25755 GNAT_Pragma;
25756 Gather_Associations (Names, Args);
25757 Store_Note (N);
25759 for J in 1 .. 2 loop
25760 if Present (Args (J)) then
25761 Check_Arg_Is_OK_Static_Expression
25762 (Args (J), Standard_String);
25763 end if;
25764 end loop;
25765 end Title;
25767 ----------------------------
25768 -- Type_Invariant[_Class] --
25769 ----------------------------
25771 -- pragma Type_Invariant[_Class]
25772 -- ([Entity =>] type_LOCAL_NAME,
25773 -- [Check =>] EXPRESSION);
25775 when Pragma_Type_Invariant
25776 | Pragma_Type_Invariant_Class
25778 Type_Invariant : declare
25779 I_Pragma : Node_Id;
25781 begin
25782 Check_Arg_Count (2);
25784 -- Rewrite Type_Invariant[_Class] pragma as an Invariant pragma,
25785 -- setting Class_Present for the Type_Invariant_Class case.
25787 Set_Class_Present (N, Prag_Id = Pragma_Type_Invariant_Class);
25788 I_Pragma := New_Copy (N);
25789 Set_Pragma_Identifier
25790 (I_Pragma, Make_Identifier (Loc, Name_Invariant));
25791 Rewrite (N, I_Pragma);
25792 Set_Analyzed (N, False);
25793 Analyze (N);
25794 end Type_Invariant;
25796 ---------------------
25797 -- Unchecked_Union --
25798 ---------------------
25800 -- pragma Unchecked_Union (first_subtype_LOCAL_NAME)
25802 when Pragma_Unchecked_Union => Unchecked_Union : declare
25803 Assoc : constant Node_Id := Arg1;
25804 Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
25805 Clist : Node_Id;
25806 Comp : Node_Id;
25807 Tdef : Node_Id;
25808 Typ : Entity_Id;
25809 Variant : Node_Id;
25810 Vpart : Node_Id;
25812 begin
25813 Ada_2005_Pragma;
25814 Check_No_Identifiers;
25815 Check_Arg_Count (1);
25816 Check_Arg_Is_Local_Name (Arg1);
25818 Find_Type (Type_Id);
25820 Typ := Entity (Type_Id);
25822 -- A pragma that applies to a Ghost entity becomes Ghost for the
25823 -- purposes of legality checks and removal of ignored Ghost code.
25825 Mark_Ghost_Pragma (N, Typ);
25827 if Typ = Any_Type
25828 or else Rep_Item_Too_Early (Typ, N)
25829 then
25830 return;
25831 else
25832 Typ := Underlying_Type (Typ);
25833 end if;
25835 if Rep_Item_Too_Late (Typ, N) then
25836 return;
25837 end if;
25839 Check_First_Subtype (Arg1);
25841 -- Note remaining cases are references to a type in the current
25842 -- declarative part. If we find an error, we post the error on
25843 -- the relevant type declaration at an appropriate point.
25845 if not Is_Record_Type (Typ) then
25846 Error_Msg_N ("unchecked union must be record type", Typ);
25847 return;
25849 elsif Is_Tagged_Type (Typ) then
25850 Error_Msg_N ("unchecked union must not be tagged", Typ);
25851 return;
25853 elsif not Has_Discriminants (Typ) then
25854 Error_Msg_N
25855 ("unchecked union must have one discriminant", Typ);
25856 return;
25858 -- Note: in previous versions of GNAT we used to check for limited
25859 -- types and give an error, but in fact the standard does allow
25860 -- Unchecked_Union on limited types, so this check was removed.
25862 -- Similarly, GNAT used to require that all discriminants have
25863 -- default values, but this is not mandated by the RM.
25865 -- Proceed with basic error checks completed
25867 else
25868 Tdef := Type_Definition (Declaration_Node (Typ));
25869 Clist := Component_List (Tdef);
25871 -- Check presence of component list and variant part
25873 if No (Clist) or else No (Variant_Part (Clist)) then
25874 Error_Msg_N
25875 ("unchecked union must have variant part", Tdef);
25876 return;
25877 end if;
25879 -- Check components
25881 Comp := First_Non_Pragma (Component_Items (Clist));
25882 while Present (Comp) loop
25883 Check_Component (Comp, Typ);
25884 Next_Non_Pragma (Comp);
25885 end loop;
25887 -- Check variant part
25889 Vpart := Variant_Part (Clist);
25891 Variant := First_Non_Pragma (Variants (Vpart));
25892 while Present (Variant) loop
25893 Check_Variant (Variant, Typ);
25894 Next_Non_Pragma (Variant);
25895 end loop;
25896 end if;
25898 Set_Is_Unchecked_Union (Typ);
25899 Set_Convention (Typ, Convention_C);
25900 Set_Has_Unchecked_Union (Base_Type (Typ));
25901 Set_Is_Unchecked_Union (Base_Type (Typ));
25902 end Unchecked_Union;
25904 ----------------------------
25905 -- Unevaluated_Use_Of_Old --
25906 ----------------------------
25908 -- pragma Unevaluated_Use_Of_Old (Error | Warn | Allow);
25910 when Pragma_Unevaluated_Use_Of_Old =>
25911 GNAT_Pragma;
25912 Check_Arg_Count (1);
25913 Check_No_Identifiers;
25914 Check_Arg_Is_One_Of (Arg1, Name_Error, Name_Warn, Name_Allow);
25916 -- Suppress/Unsuppress can appear as a configuration pragma, or in
25917 -- a declarative part or a package spec.
25919 if not Is_Configuration_Pragma then
25920 Check_Is_In_Decl_Part_Or_Package_Spec;
25921 end if;
25923 -- Store proper setting of Uneval_Old
25925 Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
25926 Uneval_Old := Fold_Upper (Name_Buffer (1));
25928 ------------------------
25929 -- Unimplemented_Unit --
25930 ------------------------
25932 -- pragma Unimplemented_Unit;
25934 -- Note: this only gives an error if we are generating code, or if
25935 -- we are in a generic library unit (where the pragma appears in the
25936 -- body, not in the spec).
25938 when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
25939 Cunitent : constant Entity_Id :=
25940 Cunit_Entity (Get_Source_Unit (Loc));
25942 begin
25943 GNAT_Pragma;
25944 Check_Arg_Count (0);
25946 if Operating_Mode = Generate_Code
25947 or else Is_Generic_Unit (Cunitent)
25948 then
25949 Get_Name_String (Chars (Cunitent));
25950 Set_Casing (Mixed_Case);
25951 Write_Str (Name_Buffer (1 .. Name_Len));
25952 Write_Str (" is not supported in this configuration");
25953 Write_Eol;
25954 raise Unrecoverable_Error;
25955 end if;
25956 end Unimplemented_Unit;
25958 ------------------------
25959 -- Universal_Aliasing --
25960 ------------------------
25962 -- pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
25964 when Pragma_Universal_Aliasing => Universal_Alias : declare
25965 E : Entity_Id;
25966 E_Id : Node_Id;
25968 begin
25969 GNAT_Pragma;
25970 Check_Arg_Count (1);
25971 Check_Optional_Identifier (Arg2, Name_Entity);
25972 Check_Arg_Is_Local_Name (Arg1);
25973 E_Id := Get_Pragma_Arg (Arg1);
25975 if Etype (E_Id) = Any_Type then
25976 return;
25977 end if;
25979 E := Entity (E_Id);
25981 if not Is_Type (E) then
25982 Error_Pragma_Arg ("pragma% requires type", Arg1);
25983 end if;
25985 -- A pragma that applies to a Ghost entity becomes Ghost for the
25986 -- purposes of legality checks and removal of ignored Ghost code.
25988 Mark_Ghost_Pragma (N, E);
25989 Set_Universal_Aliasing (Base_Type (E));
25990 Record_Rep_Item (E, N);
25991 end Universal_Alias;
25993 ----------------
25994 -- Unmodified --
25995 ----------------
25997 -- pragma Unmodified (LOCAL_NAME {, LOCAL_NAME});
25999 when Pragma_Unmodified =>
26000 Analyze_Unmodified_Or_Unused;
26002 ------------------
26003 -- Unreferenced --
26004 ------------------
26006 -- pragma Unreferenced (LOCAL_NAME {, LOCAL_NAME});
26008 -- or when used in a context clause:
26010 -- pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
26012 when Pragma_Unreferenced =>
26013 Analyze_Unreferenced_Or_Unused;
26015 --------------------------
26016 -- Unreferenced_Objects --
26017 --------------------------
26019 -- pragma Unreferenced_Objects (LOCAL_NAME {, LOCAL_NAME});
26021 when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
26022 Arg : Node_Id;
26023 Arg_Expr : Node_Id;
26024 Arg_Id : Entity_Id;
26026 Ghost_Error_Posted : Boolean := False;
26027 -- Flag set when an error concerning the illegal mix of Ghost and
26028 -- non-Ghost types is emitted.
26030 Ghost_Id : Entity_Id := Empty;
26031 -- The entity of the first Ghost type encountered while processing
26032 -- the arguments of the pragma.
26034 begin
26035 GNAT_Pragma;
26036 Check_At_Least_N_Arguments (1);
26038 Arg := Arg1;
26039 while Present (Arg) loop
26040 Check_No_Identifier (Arg);
26041 Check_Arg_Is_Local_Name (Arg);
26042 Arg_Expr := Get_Pragma_Arg (Arg);
26044 if Is_Entity_Name (Arg_Expr) then
26045 Arg_Id := Entity (Arg_Expr);
26047 if Is_Type (Arg_Id) then
26048 Set_Has_Pragma_Unreferenced_Objects (Arg_Id);
26050 -- A pragma that applies to a Ghost entity becomes Ghost
26051 -- for the purposes of legality checks and removal of
26052 -- ignored Ghost code.
26054 Mark_Ghost_Pragma (N, Arg_Id);
26056 -- Capture the entity of the first Ghost type being
26057 -- processed for error detection purposes.
26059 if Is_Ghost_Entity (Arg_Id) then
26060 if No (Ghost_Id) then
26061 Ghost_Id := Arg_Id;
26062 end if;
26064 -- Otherwise the type is non-Ghost. It is illegal to mix
26065 -- references to Ghost and non-Ghost entities
26066 -- (SPARK RM 6.9).
26068 elsif Present (Ghost_Id)
26069 and then not Ghost_Error_Posted
26070 then
26071 Ghost_Error_Posted := True;
26073 Error_Msg_Name_1 := Pname;
26074 Error_Msg_N
26075 ("pragma % cannot mention ghost and non-ghost types",
26078 Error_Msg_Sloc := Sloc (Ghost_Id);
26079 Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
26081 Error_Msg_Sloc := Sloc (Arg_Id);
26082 Error_Msg_NE ("\& # declared as non-ghost", N, Arg_Id);
26083 end if;
26084 else
26085 Error_Pragma_Arg
26086 ("argument for pragma% must be type or subtype", Arg);
26087 end if;
26088 else
26089 Error_Pragma_Arg
26090 ("argument for pragma% must be type or subtype", Arg);
26091 end if;
26093 Next (Arg);
26094 end loop;
26095 end Unreferenced_Objects;
26097 ------------------------------
26098 -- Unreserve_All_Interrupts --
26099 ------------------------------
26101 -- pragma Unreserve_All_Interrupts;
26103 when Pragma_Unreserve_All_Interrupts =>
26104 GNAT_Pragma;
26105 Check_Arg_Count (0);
26107 if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
26108 Unreserve_All_Interrupts := True;
26109 end if;
26111 ----------------
26112 -- Unsuppress --
26113 ----------------
26115 -- pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
26117 when Pragma_Unsuppress =>
26118 Ada_2005_Pragma;
26119 Process_Suppress_Unsuppress (Suppress_Case => False);
26121 ------------
26122 -- Unused --
26123 ------------
26125 -- pragma Unused (LOCAL_NAME {, LOCAL_NAME});
26127 when Pragma_Unused =>
26128 Analyze_Unmodified_Or_Unused (Is_Unused => True);
26129 Analyze_Unreferenced_Or_Unused (Is_Unused => True);
26131 -------------------
26132 -- Use_VADS_Size --
26133 -------------------
26135 -- pragma Use_VADS_Size;
26137 when Pragma_Use_VADS_Size =>
26138 GNAT_Pragma;
26139 Check_Arg_Count (0);
26140 Check_Valid_Configuration_Pragma;
26141 Use_VADS_Size := True;
26143 ---------------------
26144 -- Validity_Checks --
26145 ---------------------
26147 -- pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
26149 when Pragma_Validity_Checks => Validity_Checks : declare
26150 A : constant Node_Id := Get_Pragma_Arg (Arg1);
26151 S : String_Id;
26152 C : Char_Code;
26154 begin
26155 GNAT_Pragma;
26156 Check_Arg_Count (1);
26157 Check_No_Identifiers;
26159 -- Pragma always active unless in CodePeer or GNATprove modes,
26160 -- which use a fixed configuration of validity checks.
26162 if not (CodePeer_Mode or GNATprove_Mode) then
26163 if Nkind (A) = N_String_Literal then
26164 S := Strval (A);
26166 declare
26167 Slen : constant Natural := Natural (String_Length (S));
26168 Options : String (1 .. Slen);
26169 J : Positive;
26171 begin
26172 -- Couldn't we use a for loop here over Options'Range???
26174 J := 1;
26175 loop
26176 C := Get_String_Char (S, Pos (J));
26178 -- This is a weird test, it skips setting validity
26179 -- checks entirely if any element of S is out of
26180 -- range of Character, what is that about ???
26182 exit when not In_Character_Range (C);
26183 Options (J) := Get_Character (C);
26185 if J = Slen then
26186 Set_Validity_Check_Options (Options);
26187 exit;
26188 else
26189 J := J + 1;
26190 end if;
26191 end loop;
26192 end;
26194 elsif Nkind (A) = N_Identifier then
26195 if Chars (A) = Name_All_Checks then
26196 Set_Validity_Check_Options ("a");
26197 elsif Chars (A) = Name_On then
26198 Validity_Checks_On := True;
26199 elsif Chars (A) = Name_Off then
26200 Validity_Checks_On := False;
26201 end if;
26202 end if;
26203 end if;
26204 end Validity_Checks;
26206 --------------
26207 -- Volatile --
26208 --------------
26210 -- pragma Volatile (LOCAL_NAME);
26212 when Pragma_Volatile =>
26213 Process_Atomic_Independent_Shared_Volatile;
26215 -------------------------
26216 -- Volatile_Components --
26217 -------------------------
26219 -- pragma Volatile_Components (array_LOCAL_NAME);
26221 -- Volatile is handled by the same circuit as Atomic_Components
26223 --------------------------
26224 -- Volatile_Full_Access --
26225 --------------------------
26227 -- pragma Volatile_Full_Access (LOCAL_NAME);
26229 when Pragma_Volatile_Full_Access =>
26230 GNAT_Pragma;
26231 Process_Atomic_Independent_Shared_Volatile;
26233 -----------------------
26234 -- Volatile_Function --
26235 -----------------------
26237 -- pragma Volatile_Function [ (boolean_EXPRESSION) ];
26239 when Pragma_Volatile_Function => Volatile_Function : declare
26240 Over_Id : Entity_Id;
26241 Spec_Id : Entity_Id;
26242 Subp_Decl : Node_Id;
26244 begin
26245 GNAT_Pragma;
26246 Check_No_Identifiers;
26247 Check_At_Most_N_Arguments (1);
26249 Subp_Decl :=
26250 Find_Related_Declaration_Or_Body (N, Do_Checks => True);
26252 -- Generic subprogram
26254 if Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
26255 null;
26257 -- Body acts as spec
26259 elsif Nkind (Subp_Decl) = N_Subprogram_Body
26260 and then No (Corresponding_Spec (Subp_Decl))
26261 then
26262 null;
26264 -- Body stub acts as spec
26266 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
26267 and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
26268 then
26269 null;
26271 -- Subprogram
26273 elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
26274 null;
26276 else
26277 Pragma_Misplaced;
26278 end if;
26280 Spec_Id := Unique_Defining_Entity (Subp_Decl);
26282 if Ekind (Spec_Id) not in E_Function | E_Generic_Function then
26283 Pragma_Misplaced;
26284 end if;
26286 -- A pragma that applies to a Ghost entity becomes Ghost for the
26287 -- purposes of legality checks and removal of ignored Ghost code.
26289 Mark_Ghost_Pragma (N, Spec_Id);
26291 -- Chain the pragma on the contract for completeness
26293 Add_Contract_Item (N, Spec_Id);
26295 -- The legality checks of pragma Volatile_Function are affected by
26296 -- the SPARK mode in effect. Analyze all pragmas in a specific
26297 -- order.
26299 Analyze_If_Present (Pragma_SPARK_Mode);
26301 -- A volatile function cannot override a non-volatile function
26302 -- (SPARK RM 7.1.2(15)). Overriding checks are usually performed
26303 -- in New_Overloaded_Entity, however at that point the pragma has
26304 -- not been processed yet.
26306 Over_Id := Overridden_Operation (Spec_Id);
26308 if Present (Over_Id)
26309 and then not Is_Volatile_Function (Over_Id)
26310 then
26311 Error_Msg_N
26312 ("incompatible volatile function values in effect", Spec_Id);
26314 Error_Msg_Sloc := Sloc (Over_Id);
26315 Error_Msg_N
26316 ("\& declared # with Volatile_Function value False",
26317 Spec_Id);
26319 Error_Msg_Sloc := Sloc (Spec_Id);
26320 Error_Msg_N
26321 ("\overridden # with Volatile_Function value True",
26322 Spec_Id);
26323 end if;
26325 -- Analyze the Boolean expression (if any)
26327 if Present (Arg1) then
26328 Check_Static_Boolean_Expression (Get_Pragma_Arg (Arg1));
26329 end if;
26330 end Volatile_Function;
26332 ----------------------
26333 -- Warning_As_Error --
26334 ----------------------
26336 -- pragma Warning_As_Error (static_string_EXPRESSION);
26338 when Pragma_Warning_As_Error =>
26339 GNAT_Pragma;
26340 Check_Arg_Count (1);
26341 Check_No_Identifiers;
26342 Check_Valid_Configuration_Pragma;
26344 if not Is_Static_String_Expression (Arg1) then
26345 Error_Pragma_Arg
26346 ("argument of pragma% must be static string expression",
26347 Arg1);
26349 -- OK static string expression
26351 else
26352 Warnings_As_Errors_Count := Warnings_As_Errors_Count + 1;
26353 Warnings_As_Errors (Warnings_As_Errors_Count) :=
26354 new String'(Acquire_Warning_Match_String
26355 (Expr_Value_S (Get_Pragma_Arg (Arg1))));
26356 end if;
26358 --------------
26359 -- Warnings --
26360 --------------
26362 -- pragma Warnings ([TOOL_NAME,] DETAILS [, REASON]);
26364 -- DETAILS ::= On | Off
26365 -- DETAILS ::= On | Off, local_NAME
26366 -- DETAILS ::= static_string_EXPRESSION
26367 -- DETAILS ::= On | Off, static_string_EXPRESSION
26369 -- TOOL_NAME ::= GNAT | GNATprove
26371 -- REASON ::= Reason => STRING_LITERAL {& STRING_LITERAL}
26373 -- Note: If the first argument matches an allowed tool name, it is
26374 -- always considered to be a tool name, even if there is a string
26375 -- variable of that name.
26377 -- Note if the second argument of DETAILS is a local_NAME then the
26378 -- second form is always understood. If the intention is to use
26379 -- the fourth form, then you can write NAME & "" to force the
26380 -- intepretation as a static_string_EXPRESSION.
26382 when Pragma_Warnings => Warnings : declare
26383 Reason : String_Id;
26385 begin
26386 GNAT_Pragma;
26387 Check_At_Least_N_Arguments (1);
26389 -- See if last argument is labeled Reason. If so, make sure we
26390 -- have a string literal or a concatenation of string literals,
26391 -- and acquire the REASON string. Then remove the REASON argument
26392 -- by decreasing Num_Args by one; Remaining processing looks only
26393 -- at first Num_Args arguments).
26395 declare
26396 Last_Arg : constant Node_Id :=
26397 Last (Pragma_Argument_Associations (N));
26399 begin
26400 if Nkind (Last_Arg) = N_Pragma_Argument_Association
26401 and then Chars (Last_Arg) = Name_Reason
26402 then
26403 Start_String;
26404 Get_Reason_String (Get_Pragma_Arg (Last_Arg));
26405 Reason := End_String;
26406 Arg_Count := Arg_Count - 1;
26408 -- No REASON string, set null string as reason
26410 else
26411 Reason := Null_String_Id;
26412 end if;
26413 end;
26415 -- Now proceed with REASON taken care of and eliminated
26417 Check_No_Identifiers;
26419 -- If debug flag -gnatd.i is set, pragma is ignored
26421 if Debug_Flag_Dot_I then
26422 return;
26423 end if;
26425 -- Process various forms of the pragma
26427 declare
26428 Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
26429 Shifted_Args : List_Id;
26431 begin
26432 -- See if first argument is a tool name, currently either
26433 -- GNAT or GNATprove. If so, either ignore the pragma if the
26434 -- tool used does not match, or continue as if no tool name
26435 -- was given otherwise, by shifting the arguments.
26437 if Nkind (Argx) = N_Identifier
26438 and then Chars (Argx) in Name_Gnat | Name_Gnatprove
26439 then
26440 if Chars (Argx) = Name_Gnat then
26441 if CodePeer_Mode or GNATprove_Mode then
26442 Rewrite (N, Make_Null_Statement (Loc));
26443 Analyze (N);
26444 return;
26445 end if;
26447 elsif Chars (Argx) = Name_Gnatprove then
26448 if not GNATprove_Mode then
26449 Rewrite (N, Make_Null_Statement (Loc));
26450 Analyze (N);
26451 return;
26452 end if;
26453 else
26454 raise Program_Error;
26455 end if;
26457 -- At this point, the pragma Warnings applies to the tool,
26458 -- so continue with shifted arguments.
26460 Arg_Count := Arg_Count - 1;
26462 if Arg_Count = 1 then
26463 Shifted_Args := New_List (New_Copy (Arg2));
26464 elsif Arg_Count = 2 then
26465 Shifted_Args := New_List (New_Copy (Arg2),
26466 New_Copy (Arg3));
26467 elsif Arg_Count = 3 then
26468 Shifted_Args := New_List (New_Copy (Arg2),
26469 New_Copy (Arg3),
26470 New_Copy (Arg4));
26471 else
26472 raise Program_Error;
26473 end if;
26475 Rewrite (N,
26476 Make_Pragma (Loc,
26477 Chars => Name_Warnings,
26478 Pragma_Argument_Associations => Shifted_Args));
26479 Analyze (N);
26480 return;
26481 end if;
26483 -- One argument case
26485 if Arg_Count = 1 then
26487 -- On/Off one argument case was processed by parser
26489 if Nkind (Argx) = N_Identifier
26490 and then Chars (Argx) in Name_On | Name_Off
26491 then
26492 null;
26494 -- One argument case must be ON/OFF or static string expr
26496 elsif not Is_Static_String_Expression (Arg1) then
26497 Error_Pragma_Arg
26498 ("argument of pragma% must be On/Off or static string "
26499 & "expression", Arg1);
26501 -- Use of pragma Warnings to set warning switches is
26502 -- ignored in GNATprove mode, as these switches apply to
26503 -- the compiler only.
26505 elsif GNATprove_Mode then
26506 null;
26508 -- One argument string expression case
26510 else
26511 declare
26512 Lit : constant Node_Id := Expr_Value_S (Argx);
26513 Str : constant String_Id := Strval (Lit);
26514 Len : constant Nat := String_Length (Str);
26515 C : Char_Code;
26516 J : Nat;
26517 OK : Boolean;
26518 Chr : Character;
26520 begin
26521 J := 1;
26522 while J <= Len loop
26523 C := Get_String_Char (Str, J);
26524 OK := In_Character_Range (C);
26526 if OK then
26527 Chr := Get_Character (C);
26529 -- Dash case: only -Wxxx is accepted
26531 if J = 1
26532 and then J < Len
26533 and then Chr = '-'
26534 then
26535 J := J + 1;
26536 C := Get_String_Char (Str, J);
26537 Chr := Get_Character (C);
26538 exit when Chr = 'W';
26539 OK := False;
26541 -- Dot case
26543 elsif J < Len and then Chr = '.' then
26544 J := J + 1;
26545 C := Get_String_Char (Str, J);
26546 Chr := Get_Character (C);
26548 if not Set_Warning_Switch ('.', Chr) then
26549 Error_Pragma_Arg
26550 ("invalid warning switch character "
26551 & '.' & Chr, Arg1);
26552 end if;
26554 -- Non-Dot case
26556 else
26557 OK := Set_Warning_Switch (Plain, Chr);
26558 end if;
26560 if not OK then
26561 Error_Pragma_Arg
26562 ("invalid warning switch character " & Chr,
26563 Arg1);
26564 end if;
26566 else
26567 Error_Pragma_Arg
26568 ("invalid wide character in warning switch ",
26569 Arg1);
26570 end if;
26572 J := J + 1;
26573 end loop;
26574 end;
26575 end if;
26577 -- Two or more arguments (must be two)
26579 else
26580 Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
26581 Check_Arg_Count (2);
26583 declare
26584 E_Id : Node_Id;
26585 E : Entity_Id;
26586 Err : Boolean;
26588 begin
26589 E_Id := Get_Pragma_Arg (Arg2);
26590 Analyze (E_Id);
26592 -- In the expansion of an inlined body, a reference to
26593 -- the formal may be wrapped in a conversion if the
26594 -- actual is a conversion. Retrieve the real entity name.
26596 if (In_Instance_Body or In_Inlined_Body)
26597 and then Nkind (E_Id) = N_Unchecked_Type_Conversion
26598 then
26599 E_Id := Expression (E_Id);
26600 end if;
26602 -- Entity name case
26604 if Is_Entity_Name (E_Id) then
26605 E := Entity (E_Id);
26607 if E = Any_Id then
26608 return;
26609 else
26610 loop
26611 Set_Warnings_Off
26612 (E, (Chars (Get_Pragma_Arg (Arg1)) =
26613 Name_Off));
26615 -- Suppress elaboration warnings if the entity
26616 -- denotes an elaboration target.
26618 if Is_Elaboration_Target (E) then
26619 Set_Is_Elaboration_Warnings_OK_Id (E, False);
26620 end if;
26622 -- For OFF case, make entry in warnings off
26623 -- pragma table for later processing. But we do
26624 -- not do that within an instance, since these
26625 -- warnings are about what is needed in the
26626 -- template, not an instance of it.
26628 if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
26629 and then Warn_On_Warnings_Off
26630 and then not In_Instance
26631 then
26632 Warnings_Off_Pragmas.Append ((N, E, Reason));
26633 end if;
26635 if Is_Enumeration_Type (E) then
26636 declare
26637 Lit : Entity_Id;
26638 begin
26639 Lit := First_Literal (E);
26640 while Present (Lit) loop
26641 Set_Warnings_Off (Lit);
26642 Next_Literal (Lit);
26643 end loop;
26644 end;
26645 end if;
26647 exit when No (Homonym (E));
26648 E := Homonym (E);
26649 end loop;
26650 end if;
26652 -- Error if not entity or static string expression case
26654 elsif not Is_Static_String_Expression (Arg2) then
26655 Error_Pragma_Arg
26656 ("second argument of pragma% must be entity name "
26657 & "or static string expression", Arg2);
26659 -- Static string expression case
26661 else
26662 -- Note on configuration pragma case: If this is a
26663 -- configuration pragma, then for an OFF pragma, we
26664 -- just set Config True in the call, which is all
26665 -- that needs to be done. For the case of ON, this
26666 -- is normally an error, unless it is canceling the
26667 -- effect of a previous OFF pragma in the same file.
26668 -- In any other case, an error will be signalled (ON
26669 -- with no matching OFF).
26671 -- Note: We set Used if we are inside a generic to
26672 -- disable the test that the non-config case actually
26673 -- cancels a warning. That's because we can't be sure
26674 -- there isn't an instantiation in some other unit
26675 -- where a warning is suppressed.
26677 -- We could do a little better here by checking if the
26678 -- generic unit we are inside is public, but for now
26679 -- we don't bother with that refinement.
26681 declare
26682 Message : constant String :=
26683 Acquire_Warning_Match_String
26684 (Expr_Value_S (Get_Pragma_Arg (Arg2)));
26685 begin
26686 if Chars (Argx) = Name_Off then
26687 Set_Specific_Warning_Off
26688 (Loc, Message, Reason,
26689 Config => Is_Configuration_Pragma,
26690 Used => Inside_A_Generic or else In_Instance);
26692 elsif Chars (Argx) = Name_On then
26693 Set_Specific_Warning_On (Loc, Message, Err);
26695 if Err then
26696 Error_Msg_N
26697 ("??pragma Warnings On with no matching "
26698 & "Warnings Off", N);
26699 end if;
26700 end if;
26701 end;
26702 end if;
26703 end;
26704 end if;
26705 end;
26706 end Warnings;
26708 -------------------
26709 -- Weak_External --
26710 -------------------
26712 -- pragma Weak_External ([Entity =>] LOCAL_NAME);
26714 when Pragma_Weak_External => Weak_External : declare
26715 Ent : Entity_Id;
26717 begin
26718 GNAT_Pragma;
26719 Check_Arg_Count (1);
26720 Check_Optional_Identifier (Arg1, Name_Entity);
26721 Check_Arg_Is_Library_Level_Local_Name (Arg1);
26722 Ent := Entity (Get_Pragma_Arg (Arg1));
26724 if Rep_Item_Too_Early (Ent, N) then
26725 return;
26726 else
26727 Ent := Underlying_Type (Ent);
26728 end if;
26730 -- The pragma applies to entities with addresses
26732 if Is_Type (Ent) then
26733 Error_Pragma ("pragma applies to objects and subprograms");
26734 end if;
26736 -- The only processing required is to link this item on to the
26737 -- list of rep items for the given entity. This is accomplished
26738 -- by the call to Rep_Item_Too_Late (when no error is detected
26739 -- and False is returned).
26741 if Rep_Item_Too_Late (Ent, N) then
26742 return;
26743 else
26744 Set_Has_Gigi_Rep_Item (Ent);
26745 end if;
26746 end Weak_External;
26748 -----------------------------
26749 -- Wide_Character_Encoding --
26750 -----------------------------
26752 -- pragma Wide_Character_Encoding (IDENTIFIER);
26754 when Pragma_Wide_Character_Encoding =>
26755 GNAT_Pragma;
26757 -- Nothing to do, handled in parser. Note that we do not enforce
26758 -- configuration pragma placement, this pragma can appear at any
26759 -- place in the source, allowing mixed encodings within a single
26760 -- source program.
26762 null;
26764 --------------------
26765 -- Unknown_Pragma --
26766 --------------------
26768 -- Should be impossible, since the case of an unknown pragma is
26769 -- separately processed before the case statement is entered.
26771 when Unknown_Pragma =>
26772 raise Program_Error;
26773 end case;
26775 -- AI05-0144: detect dangerous order dependence. Disabled for now,
26776 -- until AI is formally approved.
26778 -- Check_Order_Dependence;
26780 exception
26781 when Pragma_Exit => null;
26782 end Analyze_Pragma;
26784 ---------------------------------------------
26785 -- Analyze_Pre_Post_Condition_In_Decl_Part --
26786 ---------------------------------------------
26788 -- WARNING: This routine manages Ghost regions. Return statements must be
26789 -- replaced by gotos which jump to the end of the routine and restore the
26790 -- Ghost mode.
26792 procedure Analyze_Pre_Post_Condition_In_Decl_Part
26793 (N : Node_Id;
26794 Freeze_Id : Entity_Id := Empty)
26796 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
26797 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
26799 Disp_Typ : Entity_Id;
26800 -- The dispatching type of the subprogram subject to the pre- or
26801 -- postcondition.
26803 function Check_References (Nod : Node_Id) return Traverse_Result;
26804 -- Check that expression Nod does not mention non-primitives of the
26805 -- type, global objects of the type, or other illegalities described
26806 -- and implied by AI12-0113.
26808 ----------------------
26809 -- Check_References --
26810 ----------------------
26812 function Check_References (Nod : Node_Id) return Traverse_Result is
26813 begin
26814 if Nkind (Nod) = N_Function_Call
26815 and then Is_Entity_Name (Name (Nod))
26816 then
26817 declare
26818 Func : constant Entity_Id := Entity (Name (Nod));
26819 Form : Entity_Id;
26821 begin
26822 -- An operation of the type must be a primitive
26824 if No (Find_Dispatching_Type (Func)) then
26825 Form := First_Formal (Func);
26826 while Present (Form) loop
26827 if Etype (Form) = Disp_Typ then
26828 Error_Msg_NE
26829 ("operation in class-wide condition must be "
26830 & "primitive of &", Nod, Disp_Typ);
26831 end if;
26833 Next_Formal (Form);
26834 end loop;
26836 -- A return object of the type is illegal as well
26838 if Etype (Func) = Disp_Typ
26839 or else Etype (Func) = Class_Wide_Type (Disp_Typ)
26840 then
26841 Error_Msg_NE
26842 ("operation in class-wide condition must be primitive "
26843 & "of &", Nod, Disp_Typ);
26844 end if;
26845 end if;
26846 end;
26848 elsif Is_Entity_Name (Nod)
26849 and then
26850 (Etype (Nod) = Disp_Typ
26851 or else Etype (Nod) = Class_Wide_Type (Disp_Typ))
26852 and then Ekind (Entity (Nod)) in E_Constant | E_Variable
26853 then
26854 Error_Msg_NE
26855 ("object in class-wide condition must be formal of type &",
26856 Nod, Disp_Typ);
26858 elsif Nkind (Nod) = N_Explicit_Dereference
26859 and then (Etype (Nod) = Disp_Typ
26860 or else Etype (Nod) = Class_Wide_Type (Disp_Typ))
26861 and then (not Is_Entity_Name (Prefix (Nod))
26862 or else not Is_Formal (Entity (Prefix (Nod))))
26863 then
26864 Error_Msg_NE
26865 ("operation in class-wide condition must be primitive of &",
26866 Nod, Disp_Typ);
26867 end if;
26869 return OK;
26870 end Check_References;
26872 procedure Check_Class_Wide_Condition is
26873 new Traverse_Proc (Check_References);
26875 -- Local variables
26877 Expr : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
26879 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
26880 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
26881 -- Save the Ghost-related attributes to restore on exit
26883 Errors : Nat;
26884 Restore_Scope : Boolean := False;
26886 -- Start of processing for Analyze_Pre_Post_Condition_In_Decl_Part
26888 begin
26889 -- Do not analyze the pragma multiple times
26891 if Is_Analyzed_Pragma (N) then
26892 return;
26893 end if;
26895 -- Set the Ghost mode in effect from the pragma. Due to the delayed
26896 -- analysis of the pragma, the Ghost mode at point of declaration and
26897 -- point of analysis may not necessarily be the same. Use the mode in
26898 -- effect at the point of declaration.
26900 Set_Ghost_Mode (N);
26902 -- Ensure that the subprogram and its formals are visible when analyzing
26903 -- the expression of the pragma.
26905 if not In_Open_Scopes (Spec_Id) then
26906 Restore_Scope := True;
26908 if Is_Generic_Subprogram (Spec_Id) then
26909 Push_Scope (Spec_Id);
26910 Install_Generic_Formals (Spec_Id);
26911 elsif Is_Access_Subprogram_Type (Spec_Id) then
26912 Push_Scope (Designated_Type (Spec_Id));
26913 Install_Formals (Designated_Type (Spec_Id));
26914 else
26915 Push_Scope (Spec_Id);
26916 Install_Formals (Spec_Id);
26917 end if;
26918 end if;
26920 Errors := Serious_Errors_Detected;
26921 Preanalyze_Assert_Expression (Expr, Standard_Boolean);
26923 -- Emit a clarification message when the expression contains at least
26924 -- one undefined reference, possibly due to contract freezing.
26926 if Errors /= Serious_Errors_Detected
26927 and then Present (Freeze_Id)
26928 and then Has_Undefined_Reference (Expr)
26929 then
26930 Contract_Freeze_Error (Spec_Id, Freeze_Id);
26931 end if;
26933 if Class_Present (N) then
26935 -- Verify that a class-wide condition is legal, i.e. the operation is
26936 -- a primitive of a tagged type.
26938 if not Is_Dispatching_Operation (Spec_Id) then
26939 Error_Msg_Name_1 := Original_Aspect_Pragma_Name (N);
26941 if From_Aspect_Specification (N) then
26942 Error_Msg_N
26943 ("aspect % can only be specified for a primitive operation "
26944 & "of a tagged type", Corresponding_Aspect (N));
26946 -- The pragma is a source construct
26948 else
26949 Error_Msg_N
26950 ("pragma % can only be specified for a primitive operation "
26951 & "of a tagged type", N);
26952 end if;
26954 -- Remaining semantic checks require a full tree traversal
26956 else
26957 Disp_Typ := Find_Dispatching_Type (Spec_Id);
26958 Check_Class_Wide_Condition (Expr);
26959 end if;
26961 end if;
26963 if Restore_Scope then
26964 End_Scope;
26965 end if;
26967 -- Currently it is not possible to inline pre/postconditions on a
26968 -- subprogram subject to pragma Inline_Always.
26970 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
26971 Set_Is_Analyzed_Pragma (N);
26973 Restore_Ghost_Region (Saved_GM, Saved_IGR);
26974 end Analyze_Pre_Post_Condition_In_Decl_Part;
26976 ------------------------------------------
26977 -- Analyze_Refined_Depends_In_Decl_Part --
26978 ------------------------------------------
26980 procedure Analyze_Refined_Depends_In_Decl_Part (N : Node_Id) is
26981 procedure Check_Dependency_Clause
26982 (Spec_Id : Entity_Id;
26983 Dep_Clause : Node_Id;
26984 Dep_States : Elist_Id;
26985 Refinements : List_Id;
26986 Matched_Items : in out Elist_Id);
26987 -- Try to match a single dependency clause Dep_Clause against one or
26988 -- more refinement clauses found in list Refinements. Each successful
26989 -- match eliminates at least one refinement clause from Refinements.
26990 -- Spec_Id denotes the entity of the related subprogram. Dep_States
26991 -- denotes the entities of all abstract states which appear in pragma
26992 -- Depends. Matched_Items contains the entities of all successfully
26993 -- matched items found in pragma Depends.
26995 procedure Check_Output_States
26996 (Spec_Inputs : Elist_Id;
26997 Spec_Outputs : Elist_Id;
26998 Body_Inputs : Elist_Id;
26999 Body_Outputs : Elist_Id);
27000 -- Determine whether pragma Depends contains an output state with a
27001 -- visible refinement and if so, ensure that pragma Refined_Depends
27002 -- mentions all its constituents as outputs. Spec_Inputs and
27003 -- Spec_Outputs denote the inputs and outputs of the subprogram spec
27004 -- synthesized from pragma Depends. Body_Inputs and Body_Outputs denote
27005 -- the inputs and outputs of the subprogram body synthesized from pragma
27006 -- Refined_Depends.
27008 function Collect_States (Clauses : List_Id) return Elist_Id;
27009 -- Given a normalized list of dependencies obtained from calling
27010 -- Normalize_Clauses, return a list containing the entities of all
27011 -- states appearing in dependencies. It helps in checking refinements
27012 -- involving a state and a corresponding constituent which is not a
27013 -- direct constituent of the state.
27015 procedure Normalize_Clauses (Clauses : List_Id);
27016 -- Given a list of dependence or refinement clauses Clauses, normalize
27017 -- each clause by creating multiple dependencies with exactly one input
27018 -- and one output.
27020 procedure Remove_Extra_Clauses
27021 (Clauses : List_Id;
27022 Matched_Items : Elist_Id);
27023 -- Given a list of refinement clauses Clauses, remove all clauses whose
27024 -- inputs and/or outputs have been previously matched. See the body for
27025 -- all special cases. Matched_Items contains the entities of all matched
27026 -- items found in pragma Depends.
27028 procedure Report_Extra_Clauses (Clauses : List_Id);
27029 -- Emit an error for each extra clause found in list Clauses
27031 -----------------------------
27032 -- Check_Dependency_Clause --
27033 -----------------------------
27035 procedure Check_Dependency_Clause
27036 (Spec_Id : Entity_Id;
27037 Dep_Clause : Node_Id;
27038 Dep_States : Elist_Id;
27039 Refinements : List_Id;
27040 Matched_Items : in out Elist_Id)
27042 Dep_Input : constant Node_Id := Expression (Dep_Clause);
27043 Dep_Output : constant Node_Id := First (Choices (Dep_Clause));
27045 function Is_Already_Matched (Dep_Item : Node_Id) return Boolean;
27046 -- Determine whether dependency item Dep_Item has been matched in a
27047 -- previous clause.
27049 function Is_In_Out_State_Clause return Boolean;
27050 -- Determine whether dependence clause Dep_Clause denotes an abstract
27051 -- state that depends on itself (State => State).
27053 function Is_Null_Refined_State (Item : Node_Id) return Boolean;
27054 -- Determine whether item Item denotes an abstract state with visible
27055 -- null refinement.
27057 procedure Match_Items
27058 (Dep_Item : Node_Id;
27059 Ref_Item : Node_Id;
27060 Matched : out Boolean);
27061 -- Try to match dependence item Dep_Item against refinement item
27062 -- Ref_Item. To match against a possible null refinement (see 2, 9),
27063 -- set Ref_Item to Empty. Flag Matched is set to True when one of
27064 -- the following conformance scenarios is in effect:
27065 -- 1) Both items denote null
27066 -- 2) Dep_Item denotes null and Ref_Item is Empty (special case)
27067 -- 3) Both items denote attribute 'Result
27068 -- 4) Both items denote the same object
27069 -- 5) Both items denote the same formal parameter
27070 -- 6) Both items denote the same current instance of a type
27071 -- 7) Both items denote the same discriminant
27072 -- 8) Dep_Item is an abstract state with visible null refinement
27073 -- and Ref_Item denotes null.
27074 -- 9) Dep_Item is an abstract state with visible null refinement
27075 -- and Ref_Item is Empty (special case).
27076 -- 10) Dep_Item is an abstract state with full or partial visible
27077 -- non-null refinement and Ref_Item denotes one of its
27078 -- constituents.
27079 -- 11) Dep_Item is an abstract state without a full visible
27080 -- refinement and Ref_Item denotes the same state.
27081 -- When scenario 10 is in effect, the entity of the abstract state
27082 -- denoted by Dep_Item is added to list Refined_States.
27084 procedure Record_Item (Item_Id : Entity_Id);
27085 -- Store the entity of an item denoted by Item_Id in Matched_Items
27087 ------------------------
27088 -- Is_Already_Matched --
27089 ------------------------
27091 function Is_Already_Matched (Dep_Item : Node_Id) return Boolean is
27092 Item_Id : Entity_Id := Empty;
27094 begin
27095 -- When the dependency item denotes attribute 'Result, check for
27096 -- the entity of the related subprogram.
27098 if Is_Attribute_Result (Dep_Item) then
27099 Item_Id := Spec_Id;
27101 elsif Is_Entity_Name (Dep_Item) then
27102 Item_Id := Available_View (Entity_Of (Dep_Item));
27103 end if;
27105 return
27106 Present (Item_Id) and then Contains (Matched_Items, Item_Id);
27107 end Is_Already_Matched;
27109 ----------------------------
27110 -- Is_In_Out_State_Clause --
27111 ----------------------------
27113 function Is_In_Out_State_Clause return Boolean is
27114 Dep_Input_Id : Entity_Id;
27115 Dep_Output_Id : Entity_Id;
27117 begin
27118 -- Detect the following clause:
27119 -- State => State
27121 if Is_Entity_Name (Dep_Input)
27122 and then Is_Entity_Name (Dep_Output)
27123 then
27124 -- Handle abstract views generated for limited with clauses
27126 Dep_Input_Id := Available_View (Entity_Of (Dep_Input));
27127 Dep_Output_Id := Available_View (Entity_Of (Dep_Output));
27129 return
27130 Ekind (Dep_Input_Id) = E_Abstract_State
27131 and then Dep_Input_Id = Dep_Output_Id;
27132 else
27133 return False;
27134 end if;
27135 end Is_In_Out_State_Clause;
27137 ---------------------------
27138 -- Is_Null_Refined_State --
27139 ---------------------------
27141 function Is_Null_Refined_State (Item : Node_Id) return Boolean is
27142 Item_Id : Entity_Id;
27144 begin
27145 if Is_Entity_Name (Item) then
27147 -- Handle abstract views generated for limited with clauses
27149 Item_Id := Available_View (Entity_Of (Item));
27151 return
27152 Ekind (Item_Id) = E_Abstract_State
27153 and then Has_Null_Visible_Refinement (Item_Id);
27154 else
27155 return False;
27156 end if;
27157 end Is_Null_Refined_State;
27159 -----------------
27160 -- Match_Items --
27161 -----------------
27163 procedure Match_Items
27164 (Dep_Item : Node_Id;
27165 Ref_Item : Node_Id;
27166 Matched : out Boolean)
27168 Dep_Item_Id : Entity_Id;
27169 Ref_Item_Id : Entity_Id;
27171 begin
27172 -- Assume that the two items do not match
27174 Matched := False;
27176 -- A null matches null or Empty (special case)
27178 if Nkind (Dep_Item) = N_Null
27179 and then (No (Ref_Item) or else Nkind (Ref_Item) = N_Null)
27180 then
27181 Matched := True;
27183 -- Attribute 'Result matches attribute 'Result
27185 elsif Is_Attribute_Result (Dep_Item)
27186 and then Is_Attribute_Result (Ref_Item)
27187 then
27188 -- Put the entity of the related function on the list of
27189 -- matched items because attribute 'Result does not carry
27190 -- an entity similar to states and constituents.
27192 Record_Item (Spec_Id);
27193 Matched := True;
27195 -- Abstract states, current instances of concurrent types,
27196 -- discriminants, formal parameters and objects.
27198 elsif Is_Entity_Name (Dep_Item) then
27200 -- Handle abstract views generated for limited with clauses
27202 Dep_Item_Id := Available_View (Entity_Of (Dep_Item));
27204 if Ekind (Dep_Item_Id) = E_Abstract_State then
27206 -- An abstract state with visible null refinement matches
27207 -- null or Empty (special case).
27209 if Has_Null_Visible_Refinement (Dep_Item_Id)
27210 and then (No (Ref_Item) or else Nkind (Ref_Item) = N_Null)
27211 then
27212 Record_Item (Dep_Item_Id);
27213 Matched := True;
27215 -- An abstract state with visible non-null refinement
27216 -- matches one of its constituents, or itself for an
27217 -- abstract state with partial visible refinement.
27219 elsif Has_Non_Null_Visible_Refinement (Dep_Item_Id) then
27220 if Is_Entity_Name (Ref_Item) then
27221 Ref_Item_Id := Entity_Of (Ref_Item);
27223 if Ekind (Ref_Item_Id) in
27224 E_Abstract_State | E_Constant | E_Variable
27225 and then Present (Encapsulating_State (Ref_Item_Id))
27226 and then Find_Encapsulating_State
27227 (Dep_States, Ref_Item_Id) = Dep_Item_Id
27228 then
27229 Record_Item (Dep_Item_Id);
27230 Matched := True;
27232 elsif not Has_Visible_Refinement (Dep_Item_Id)
27233 and then Ref_Item_Id = Dep_Item_Id
27234 then
27235 Record_Item (Dep_Item_Id);
27236 Matched := True;
27237 end if;
27238 end if;
27240 -- An abstract state without a visible refinement matches
27241 -- itself.
27243 elsif Is_Entity_Name (Ref_Item)
27244 and then Entity_Of (Ref_Item) = Dep_Item_Id
27245 then
27246 Record_Item (Dep_Item_Id);
27247 Matched := True;
27248 end if;
27250 -- A current instance of a concurrent type, discriminant,
27251 -- formal parameter or an object matches itself.
27253 elsif Is_Entity_Name (Ref_Item)
27254 and then Entity_Of (Ref_Item) = Dep_Item_Id
27255 then
27256 Record_Item (Dep_Item_Id);
27257 Matched := True;
27258 end if;
27259 end if;
27260 end Match_Items;
27262 -----------------
27263 -- Record_Item --
27264 -----------------
27266 procedure Record_Item (Item_Id : Entity_Id) is
27267 begin
27268 if No (Matched_Items) then
27269 Matched_Items := New_Elmt_List;
27270 end if;
27272 Append_Unique_Elmt (Item_Id, Matched_Items);
27273 end Record_Item;
27275 -- Local variables
27277 Clause_Matched : Boolean := False;
27278 Dummy : Boolean := False;
27279 Inputs_Match : Boolean;
27280 Next_Ref_Clause : Node_Id;
27281 Outputs_Match : Boolean;
27282 Ref_Clause : Node_Id;
27283 Ref_Input : Node_Id;
27284 Ref_Output : Node_Id;
27286 -- Start of processing for Check_Dependency_Clause
27288 begin
27289 -- Do not perform this check in an instance because it was already
27290 -- performed successfully in the generic template.
27292 if In_Instance then
27293 return;
27294 end if;
27296 -- Examine all refinement clauses and compare them against the
27297 -- dependence clause.
27299 Ref_Clause := First (Refinements);
27300 while Present (Ref_Clause) loop
27301 Next_Ref_Clause := Next (Ref_Clause);
27303 -- Obtain the attributes of the current refinement clause
27305 Ref_Input := Expression (Ref_Clause);
27306 Ref_Output := First (Choices (Ref_Clause));
27308 -- The current refinement clause matches the dependence clause
27309 -- when both outputs match and both inputs match. See routine
27310 -- Match_Items for all possible conformance scenarios.
27312 -- Depends Dep_Output => Dep_Input
27313 -- ^ ^
27314 -- match ? match ?
27315 -- v v
27316 -- Refined_Depends Ref_Output => Ref_Input
27318 Match_Items
27319 (Dep_Item => Dep_Input,
27320 Ref_Item => Ref_Input,
27321 Matched => Inputs_Match);
27323 Match_Items
27324 (Dep_Item => Dep_Output,
27325 Ref_Item => Ref_Output,
27326 Matched => Outputs_Match);
27328 -- An In_Out state clause may be matched against a refinement with
27329 -- a null input or null output as long as the non-null side of the
27330 -- relation contains a valid constituent of the In_Out_State.
27332 if Is_In_Out_State_Clause then
27334 -- Depends => (State => State)
27335 -- Refined_Depends => (null => Constit) -- OK
27337 if Inputs_Match
27338 and then not Outputs_Match
27339 and then Nkind (Ref_Output) = N_Null
27340 then
27341 Outputs_Match := True;
27342 end if;
27344 -- Depends => (State => State)
27345 -- Refined_Depends => (Constit => null) -- OK
27347 if not Inputs_Match
27348 and then Outputs_Match
27349 and then Nkind (Ref_Input) = N_Null
27350 then
27351 Inputs_Match := True;
27352 end if;
27353 end if;
27355 -- The current refinement clause is legally constructed following
27356 -- the rules in SPARK RM 7.2.5, therefore it can be removed from
27357 -- the pool of candidates. The search continues because a single
27358 -- dependence clause may have multiple matching refinements.
27360 if Inputs_Match and Outputs_Match then
27361 Clause_Matched := True;
27362 Remove (Ref_Clause);
27363 end if;
27365 Ref_Clause := Next_Ref_Clause;
27366 end loop;
27368 -- Depending on the order or composition of refinement clauses, an
27369 -- In_Out state clause may not be directly refinable.
27371 -- Refined_State => (State => (Constit_1, Constit_2))
27372 -- Depends => ((Output, State) => (Input, State))
27373 -- Refined_Depends => (Constit_1 => Input, Output => Constit_2)
27375 -- Matching normalized clause (State => State) fails because there is
27376 -- no direct refinement capable of satisfying this relation. Another
27377 -- similar case arises when clauses (Constit_1 => Input) and (Output
27378 -- => Constit_2) are matched first, leaving no candidates for clause
27379 -- (State => State). Both scenarios are legal as long as one of the
27380 -- previous clauses mentioned a valid constituent of State.
27382 if not Clause_Matched
27383 and then Is_In_Out_State_Clause
27384 and then Is_Already_Matched (Dep_Input)
27385 then
27386 Clause_Matched := True;
27387 end if;
27389 -- A clause where the input is an abstract state with visible null
27390 -- refinement or a 'Result attribute is implicitly matched when the
27391 -- output has already been matched in a previous clause.
27393 -- Refined_State => (State => null)
27394 -- Depends => (Output => State) -- implicitly OK
27395 -- Refined_Depends => (Output => ...)
27396 -- Depends => (...'Result => State) -- implicitly OK
27397 -- Refined_Depends => (...'Result => ...)
27399 if not Clause_Matched
27400 and then Is_Null_Refined_State (Dep_Input)
27401 and then Is_Already_Matched (Dep_Output)
27402 then
27403 Clause_Matched := True;
27404 end if;
27406 -- A clause where the output is an abstract state with visible null
27407 -- refinement is implicitly matched when the input has already been
27408 -- matched in a previous clause.
27410 -- Refined_State => (State => null)
27411 -- Depends => (State => Input) -- implicitly OK
27412 -- Refined_Depends => (... => Input)
27414 if not Clause_Matched
27415 and then Is_Null_Refined_State (Dep_Output)
27416 and then Is_Already_Matched (Dep_Input)
27417 then
27418 Clause_Matched := True;
27419 end if;
27421 -- At this point either all refinement clauses have been examined or
27422 -- pragma Refined_Depends contains a solitary null. Only an abstract
27423 -- state with null refinement can possibly match these cases.
27425 -- Refined_State => (State => null)
27426 -- Depends => (State => null)
27427 -- Refined_Depends => null -- OK
27429 if not Clause_Matched then
27430 Match_Items
27431 (Dep_Item => Dep_Input,
27432 Ref_Item => Empty,
27433 Matched => Inputs_Match);
27435 Match_Items
27436 (Dep_Item => Dep_Output,
27437 Ref_Item => Empty,
27438 Matched => Outputs_Match);
27440 Clause_Matched := Inputs_Match and Outputs_Match;
27441 end if;
27443 -- If the contents of Refined_Depends are legal, then the current
27444 -- dependence clause should be satisfied either by an explicit match
27445 -- or by one of the special cases.
27447 if not Clause_Matched then
27448 SPARK_Msg_NE
27449 (Fix_Msg (Spec_Id, "dependence clause of subprogram & has no "
27450 & "matching refinement in body"), Dep_Clause, Spec_Id);
27451 end if;
27452 end Check_Dependency_Clause;
27454 -------------------------
27455 -- Check_Output_States --
27456 -------------------------
27458 procedure Check_Output_States
27459 (Spec_Inputs : Elist_Id;
27460 Spec_Outputs : Elist_Id;
27461 Body_Inputs : Elist_Id;
27462 Body_Outputs : Elist_Id)
27464 procedure Check_Constituent_Usage (State_Id : Entity_Id);
27465 -- Determine whether all constituents of state State_Id with full
27466 -- visible refinement are used as outputs in pragma Refined_Depends.
27467 -- Emit an error if this is not the case (SPARK RM 7.2.4(5)).
27469 -----------------------------
27470 -- Check_Constituent_Usage --
27471 -----------------------------
27473 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
27474 Constits : constant Elist_Id :=
27475 Partial_Refinement_Constituents (State_Id);
27476 Constit_Elmt : Elmt_Id;
27477 Constit_Id : Entity_Id;
27478 Only_Partial : constant Boolean :=
27479 not Has_Visible_Refinement (State_Id);
27480 Posted : Boolean := False;
27482 begin
27483 if Present (Constits) then
27484 Constit_Elmt := First_Elmt (Constits);
27485 while Present (Constit_Elmt) loop
27486 Constit_Id := Node (Constit_Elmt);
27488 -- Issue an error when a constituent of State_Id is used,
27489 -- and State_Id has only partial visible refinement
27490 -- (SPARK RM 7.2.4(3d)).
27492 if Only_Partial then
27493 if (Present (Body_Inputs)
27494 and then Appears_In (Body_Inputs, Constit_Id))
27495 or else
27496 (Present (Body_Outputs)
27497 and then Appears_In (Body_Outputs, Constit_Id))
27498 then
27499 Error_Msg_Name_1 := Chars (State_Id);
27500 SPARK_Msg_NE
27501 ("constituent & of state % cannot be used in "
27502 & "dependence refinement", N, Constit_Id);
27503 Error_Msg_Name_1 := Chars (State_Id);
27504 SPARK_Msg_N ("\use state % instead", N);
27505 end if;
27507 -- The constituent acts as an input (SPARK RM 7.2.5(3))
27509 elsif Present (Body_Inputs)
27510 and then Appears_In (Body_Inputs, Constit_Id)
27511 then
27512 Error_Msg_Name_1 := Chars (State_Id);
27513 SPARK_Msg_NE
27514 ("constituent & of state % must act as output in "
27515 & "dependence refinement", N, Constit_Id);
27517 -- The constituent is altogether missing (SPARK RM 7.2.5(3))
27519 elsif No (Body_Outputs)
27520 or else not Appears_In (Body_Outputs, Constit_Id)
27521 then
27522 if not Posted then
27523 Posted := True;
27524 SPARK_Msg_NE
27525 ("output state & must be replaced by all its "
27526 & "constituents in dependence refinement",
27527 N, State_Id);
27528 end if;
27530 SPARK_Msg_NE
27531 ("\constituent & is missing in output list",
27532 N, Constit_Id);
27533 end if;
27535 Next_Elmt (Constit_Elmt);
27536 end loop;
27537 end if;
27538 end Check_Constituent_Usage;
27540 -- Local variables
27542 Item : Node_Id;
27543 Item_Elmt : Elmt_Id;
27544 Item_Id : Entity_Id;
27546 -- Start of processing for Check_Output_States
27548 begin
27549 -- Do not perform this check in an instance because it was already
27550 -- performed successfully in the generic template.
27552 if In_Instance then
27553 null;
27555 -- Inspect the outputs of pragma Depends looking for a state with a
27556 -- visible refinement.
27558 elsif Present (Spec_Outputs) then
27559 Item_Elmt := First_Elmt (Spec_Outputs);
27560 while Present (Item_Elmt) loop
27561 Item := Node (Item_Elmt);
27563 -- Deal with the mixed nature of the input and output lists
27565 if Nkind (Item) = N_Defining_Identifier then
27566 Item_Id := Item;
27567 else
27568 Item_Id := Available_View (Entity_Of (Item));
27569 end if;
27571 if Ekind (Item_Id) = E_Abstract_State then
27573 -- The state acts as an input-output, skip it
27575 if Present (Spec_Inputs)
27576 and then Appears_In (Spec_Inputs, Item_Id)
27577 then
27578 null;
27580 -- Ensure that all of the constituents are utilized as
27581 -- outputs in pragma Refined_Depends.
27583 elsif Has_Non_Null_Visible_Refinement (Item_Id) then
27584 Check_Constituent_Usage (Item_Id);
27585 end if;
27586 end if;
27588 Next_Elmt (Item_Elmt);
27589 end loop;
27590 end if;
27591 end Check_Output_States;
27593 --------------------
27594 -- Collect_States --
27595 --------------------
27597 function Collect_States (Clauses : List_Id) return Elist_Id is
27598 procedure Collect_State
27599 (Item : Node_Id;
27600 States : in out Elist_Id);
27601 -- Add the entity of Item to list States when it denotes to a state
27603 -------------------
27604 -- Collect_State --
27605 -------------------
27607 procedure Collect_State
27608 (Item : Node_Id;
27609 States : in out Elist_Id)
27611 Id : Entity_Id;
27613 begin
27614 if Is_Entity_Name (Item) then
27615 Id := Entity_Of (Item);
27617 if Ekind (Id) = E_Abstract_State then
27618 if No (States) then
27619 States := New_Elmt_List;
27620 end if;
27622 Append_Unique_Elmt (Id, States);
27623 end if;
27624 end if;
27625 end Collect_State;
27627 -- Local variables
27629 Clause : Node_Id;
27630 Input : Node_Id;
27631 Output : Node_Id;
27632 States : Elist_Id := No_Elist;
27634 -- Start of processing for Collect_States
27636 begin
27637 Clause := First (Clauses);
27638 while Present (Clause) loop
27639 Input := Expression (Clause);
27640 Output := First (Choices (Clause));
27642 Collect_State (Input, States);
27643 Collect_State (Output, States);
27645 Next (Clause);
27646 end loop;
27648 return States;
27649 end Collect_States;
27651 -----------------------
27652 -- Normalize_Clauses --
27653 -----------------------
27655 procedure Normalize_Clauses (Clauses : List_Id) is
27656 procedure Normalize_Inputs (Clause : Node_Id);
27657 -- Normalize clause Clause by creating multiple clauses for each
27658 -- input item of Clause. It is assumed that Clause has exactly one
27659 -- output. The transformation is as follows:
27661 -- Output => (Input_1, Input_2) -- original
27663 -- Output => Input_1 -- normalizations
27664 -- Output => Input_2
27666 procedure Normalize_Outputs (Clause : Node_Id);
27667 -- Normalize clause Clause by creating multiple clause for each
27668 -- output item of Clause. The transformation is as follows:
27670 -- (Output_1, Output_2) => Input -- original
27672 -- Output_1 => Input -- normalization
27673 -- Output_2 => Input
27675 ----------------------
27676 -- Normalize_Inputs --
27677 ----------------------
27679 procedure Normalize_Inputs (Clause : Node_Id) is
27680 Inputs : constant Node_Id := Expression (Clause);
27681 Loc : constant Source_Ptr := Sloc (Clause);
27682 Output : constant List_Id := Choices (Clause);
27683 Last_Input : Node_Id;
27684 Input : Node_Id;
27685 New_Clause : Node_Id;
27686 Next_Input : Node_Id;
27688 begin
27689 -- Normalization is performed only when the original clause has
27690 -- more than one input. Multiple inputs appear as an aggregate.
27692 if Nkind (Inputs) = N_Aggregate then
27693 Last_Input := Last (Expressions (Inputs));
27695 -- Create a new clause for each input
27697 Input := First (Expressions (Inputs));
27698 while Present (Input) loop
27699 Next_Input := Next (Input);
27701 -- Unhook the current input from the original input list
27702 -- because it will be relocated to a new clause.
27704 Remove (Input);
27706 -- Special processing for the last input. At this point the
27707 -- original aggregate has been stripped down to one element.
27708 -- Replace the aggregate by the element itself.
27710 if Input = Last_Input then
27711 Rewrite (Inputs, Input);
27713 -- Generate a clause of the form:
27714 -- Output => Input
27716 else
27717 New_Clause :=
27718 Make_Component_Association (Loc,
27719 Choices => New_Copy_List_Tree (Output),
27720 Expression => Input);
27722 -- The new clause contains replicated content that has
27723 -- already been analyzed, mark the clause as analyzed.
27725 Set_Analyzed (New_Clause);
27726 Insert_After (Clause, New_Clause);
27727 end if;
27729 Input := Next_Input;
27730 end loop;
27731 end if;
27732 end Normalize_Inputs;
27734 -----------------------
27735 -- Normalize_Outputs --
27736 -----------------------
27738 procedure Normalize_Outputs (Clause : Node_Id) is
27739 Inputs : constant Node_Id := Expression (Clause);
27740 Loc : constant Source_Ptr := Sloc (Clause);
27741 Outputs : constant Node_Id := First (Choices (Clause));
27742 Last_Output : Node_Id;
27743 New_Clause : Node_Id;
27744 Next_Output : Node_Id;
27745 Output : Node_Id;
27747 begin
27748 -- Multiple outputs appear as an aggregate. Nothing to do when
27749 -- the clause has exactly one output.
27751 if Nkind (Outputs) = N_Aggregate then
27752 Last_Output := Last (Expressions (Outputs));
27754 -- Create a clause for each output. Note that each time a new
27755 -- clause is created, the original output list slowly shrinks
27756 -- until there is one item left.
27758 Output := First (Expressions (Outputs));
27759 while Present (Output) loop
27760 Next_Output := Next (Output);
27762 -- Unhook the output from the original output list as it
27763 -- will be relocated to a new clause.
27765 Remove (Output);
27767 -- Special processing for the last output. At this point
27768 -- the original aggregate has been stripped down to one
27769 -- element. Replace the aggregate by the element itself.
27771 if Output = Last_Output then
27772 Rewrite (Outputs, Output);
27774 else
27775 -- Generate a clause of the form:
27776 -- (Output => Inputs)
27778 New_Clause :=
27779 Make_Component_Association (Loc,
27780 Choices => New_List (Output),
27781 Expression => New_Copy_Tree (Inputs));
27783 -- The new clause contains replicated content that has
27784 -- already been analyzed. There is not need to reanalyze
27785 -- them.
27787 Set_Analyzed (New_Clause);
27788 Insert_After (Clause, New_Clause);
27789 end if;
27791 Output := Next_Output;
27792 end loop;
27793 end if;
27794 end Normalize_Outputs;
27796 -- Local variables
27798 Clause : Node_Id;
27800 -- Start of processing for Normalize_Clauses
27802 begin
27803 Clause := First (Clauses);
27804 while Present (Clause) loop
27805 Normalize_Outputs (Clause);
27806 Next (Clause);
27807 end loop;
27809 Clause := First (Clauses);
27810 while Present (Clause) loop
27811 Normalize_Inputs (Clause);
27812 Next (Clause);
27813 end loop;
27814 end Normalize_Clauses;
27816 --------------------------
27817 -- Remove_Extra_Clauses --
27818 --------------------------
27820 procedure Remove_Extra_Clauses
27821 (Clauses : List_Id;
27822 Matched_Items : Elist_Id)
27824 Clause : Node_Id;
27825 Input : Node_Id;
27826 Input_Id : Entity_Id;
27827 Next_Clause : Node_Id;
27828 Output : Node_Id;
27829 State_Id : Entity_Id;
27831 begin
27832 Clause := First (Clauses);
27833 while Present (Clause) loop
27834 Next_Clause := Next (Clause);
27836 Input := Expression (Clause);
27837 Output := First (Choices (Clause));
27839 -- Recognize a clause of the form
27841 -- null => Input
27843 -- where Input is a constituent of a state which was already
27844 -- successfully matched. This clause must be removed because it
27845 -- simply indicates that some of the constituents of the state
27846 -- are not used.
27848 -- Refined_State => (State => (Constit_1, Constit_2))
27849 -- Depends => (Output => State)
27850 -- Refined_Depends => ((Output => Constit_1), -- State matched
27851 -- (null => Constit_2)) -- OK
27853 if Nkind (Output) = N_Null and then Is_Entity_Name (Input) then
27855 -- Handle abstract views generated for limited with clauses
27857 Input_Id := Available_View (Entity_Of (Input));
27859 -- The input must be a constituent of a state
27861 if Ekind (Input_Id) in
27862 E_Abstract_State | E_Constant | E_Variable
27863 and then Present (Encapsulating_State (Input_Id))
27864 then
27865 State_Id := Encapsulating_State (Input_Id);
27867 -- The state must have a non-null visible refinement and be
27868 -- matched in a previous clause.
27870 if Has_Non_Null_Visible_Refinement (State_Id)
27871 and then Contains (Matched_Items, State_Id)
27872 then
27873 Remove (Clause);
27874 end if;
27875 end if;
27877 -- Recognize a clause of the form
27879 -- Output => null
27881 -- where Output is an arbitrary item. This clause must be removed
27882 -- because a null input legitimately matches anything.
27884 elsif Nkind (Input) = N_Null then
27885 Remove (Clause);
27886 end if;
27888 Clause := Next_Clause;
27889 end loop;
27890 end Remove_Extra_Clauses;
27892 --------------------------
27893 -- Report_Extra_Clauses --
27894 --------------------------
27896 procedure Report_Extra_Clauses (Clauses : List_Id) is
27897 Clause : Node_Id;
27899 begin
27900 -- Do not perform this check in an instance because it was already
27901 -- performed successfully in the generic template.
27903 if In_Instance then
27904 null;
27906 elsif Present (Clauses) then
27907 Clause := First (Clauses);
27908 while Present (Clause) loop
27909 SPARK_Msg_N
27910 ("unmatched or extra clause in dependence refinement",
27911 Clause);
27913 Next (Clause);
27914 end loop;
27915 end if;
27916 end Report_Extra_Clauses;
27918 -- Local variables
27920 Body_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
27921 Body_Id : constant Entity_Id := Defining_Entity (Body_Decl);
27922 Errors : constant Nat := Serious_Errors_Detected;
27924 Clause : Node_Id;
27925 Deps : Node_Id;
27926 Dummy : Boolean;
27927 Refs : Node_Id;
27929 Body_Inputs : Elist_Id := No_Elist;
27930 Body_Outputs : Elist_Id := No_Elist;
27931 -- The inputs and outputs of the subprogram body synthesized from pragma
27932 -- Refined_Depends.
27934 Dependencies : List_Id := No_List;
27935 Depends : Node_Id;
27936 -- The corresponding Depends pragma along with its clauses
27938 Matched_Items : Elist_Id := No_Elist;
27939 -- A list containing the entities of all successfully matched items
27940 -- found in pragma Depends.
27942 Refinements : List_Id := No_List;
27943 -- The clauses of pragma Refined_Depends
27945 Spec_Id : Entity_Id;
27946 -- The entity of the subprogram subject to pragma Refined_Depends
27948 Spec_Inputs : Elist_Id := No_Elist;
27949 Spec_Outputs : Elist_Id := No_Elist;
27950 -- The inputs and outputs of the subprogram spec synthesized from pragma
27951 -- Depends.
27953 States : Elist_Id := No_Elist;
27954 -- A list containing the entities of all states whose constituents
27955 -- appear in pragma Depends.
27957 -- Start of processing for Analyze_Refined_Depends_In_Decl_Part
27959 begin
27960 -- Do not analyze the pragma multiple times
27962 if Is_Analyzed_Pragma (N) then
27963 return;
27964 end if;
27966 Spec_Id := Unique_Defining_Entity (Body_Decl);
27968 -- Use the anonymous object as the proper spec when Refined_Depends
27969 -- applies to the body of a single task type. The object carries the
27970 -- proper Chars as well as all non-refined versions of pragmas.
27972 if Is_Single_Concurrent_Type (Spec_Id) then
27973 Spec_Id := Anonymous_Object (Spec_Id);
27974 end if;
27976 Depends := Get_Pragma (Spec_Id, Pragma_Depends);
27978 -- Subprogram declarations lacks pragma Depends. Refined_Depends is
27979 -- rendered useless as there is nothing to refine (SPARK RM 7.2.5(2)).
27981 if No (Depends) then
27982 SPARK_Msg_NE
27983 (Fix_Msg (Spec_Id, "useless refinement, declaration of subprogram "
27984 & "& lacks aspect or pragma Depends"), N, Spec_Id);
27985 goto Leave;
27986 end if;
27988 Deps := Expression (Get_Argument (Depends, Spec_Id));
27990 -- A null dependency relation renders the refinement useless because it
27991 -- cannot possibly mention abstract states with visible refinement. Note
27992 -- that the inverse is not true as states may be refined to null
27993 -- (SPARK RM 7.2.5(2)).
27995 if Nkind (Deps) = N_Null then
27996 SPARK_Msg_NE
27997 (Fix_Msg (Spec_Id, "useless refinement, subprogram & does not "
27998 & "depend on abstract state with visible refinement"), N, Spec_Id);
27999 goto Leave;
28000 end if;
28002 -- Analyze Refined_Depends as if it behaved as a regular pragma Depends.
28003 -- This ensures that the categorization of all refined dependency items
28004 -- is consistent with their role.
28006 Analyze_Depends_In_Decl_Part (N);
28008 -- Do not match dependencies against refinements if Refined_Depends is
28009 -- illegal to avoid emitting misleading error.
28011 if Serious_Errors_Detected = Errors then
28013 -- The related subprogram lacks pragma [Refined_]Global. Synthesize
28014 -- the inputs and outputs of the subprogram spec and body to verify
28015 -- the use of states with visible refinement and their constituents.
28017 if No (Get_Pragma (Spec_Id, Pragma_Global))
28018 or else No (Get_Pragma (Body_Id, Pragma_Refined_Global))
28019 then
28020 Collect_Subprogram_Inputs_Outputs
28021 (Subp_Id => Spec_Id,
28022 Synthesize => True,
28023 Subp_Inputs => Spec_Inputs,
28024 Subp_Outputs => Spec_Outputs,
28025 Global_Seen => Dummy);
28027 Collect_Subprogram_Inputs_Outputs
28028 (Subp_Id => Body_Id,
28029 Synthesize => True,
28030 Subp_Inputs => Body_Inputs,
28031 Subp_Outputs => Body_Outputs,
28032 Global_Seen => Dummy);
28034 -- For an output state with a visible refinement, ensure that all
28035 -- constituents appear as outputs in the dependency refinement.
28037 Check_Output_States
28038 (Spec_Inputs => Spec_Inputs,
28039 Spec_Outputs => Spec_Outputs,
28040 Body_Inputs => Body_Inputs,
28041 Body_Outputs => Body_Outputs);
28042 end if;
28044 -- Multiple dependency clauses appear as component associations of an
28045 -- aggregate. Note that the clauses are copied because the algorithm
28046 -- modifies them and this should not be visible in Depends.
28048 pragma Assert (Nkind (Deps) = N_Aggregate);
28049 Dependencies := New_Copy_List_Tree (Component_Associations (Deps));
28050 Normalize_Clauses (Dependencies);
28052 -- Gather all states which appear in Depends
28054 States := Collect_States (Dependencies);
28056 Refs := Expression (Get_Argument (N, Spec_Id));
28058 if Nkind (Refs) = N_Null then
28059 Refinements := No_List;
28061 -- Multiple dependency clauses appear as component associations of an
28062 -- aggregate. Note that the clauses are copied because the algorithm
28063 -- modifies them and this should not be visible in Refined_Depends.
28065 else pragma Assert (Nkind (Refs) = N_Aggregate);
28066 Refinements := New_Copy_List_Tree (Component_Associations (Refs));
28067 Normalize_Clauses (Refinements);
28068 end if;
28070 -- At this point the clauses of pragmas Depends and Refined_Depends
28071 -- have been normalized into simple dependencies between one output
28072 -- and one input. Examine all clauses of pragma Depends looking for
28073 -- matching clauses in pragma Refined_Depends.
28075 Clause := First (Dependencies);
28076 while Present (Clause) loop
28077 Check_Dependency_Clause
28078 (Spec_Id => Spec_Id,
28079 Dep_Clause => Clause,
28080 Dep_States => States,
28081 Refinements => Refinements,
28082 Matched_Items => Matched_Items);
28084 Next (Clause);
28085 end loop;
28087 -- Pragma Refined_Depends may contain multiple clarification clauses
28088 -- which indicate that certain constituents do not influence the data
28089 -- flow in any way. Such clauses must be removed as long as the state
28090 -- has been matched, otherwise they will be incorrectly flagged as
28091 -- unmatched.
28093 -- Refined_State => (State => (Constit_1, Constit_2))
28094 -- Depends => (Output => State)
28095 -- Refined_Depends => ((Output => Constit_1), -- State matched
28096 -- (null => Constit_2)) -- must be removed
28098 Remove_Extra_Clauses (Refinements, Matched_Items);
28100 if Serious_Errors_Detected = Errors then
28101 Report_Extra_Clauses (Refinements);
28102 end if;
28103 end if;
28105 <<Leave>>
28106 Set_Is_Analyzed_Pragma (N);
28107 end Analyze_Refined_Depends_In_Decl_Part;
28109 -----------------------------------------
28110 -- Analyze_Refined_Global_In_Decl_Part --
28111 -----------------------------------------
28113 procedure Analyze_Refined_Global_In_Decl_Part (N : Node_Id) is
28114 Global : Node_Id;
28115 -- The corresponding Global pragma
28117 Has_In_State : Boolean := False;
28118 Has_In_Out_State : Boolean := False;
28119 Has_Out_State : Boolean := False;
28120 Has_Proof_In_State : Boolean := False;
28121 -- These flags are set when the corresponding Global pragma has a state
28122 -- of mode Input, In_Out, Output or Proof_In respectively with a visible
28123 -- refinement.
28125 Has_Null_State : Boolean := False;
28126 -- This flag is set when the corresponding Global pragma has at least
28127 -- one state with a null refinement.
28129 In_Constits : Elist_Id := No_Elist;
28130 In_Out_Constits : Elist_Id := No_Elist;
28131 Out_Constits : Elist_Id := No_Elist;
28132 Proof_In_Constits : Elist_Id := No_Elist;
28133 -- These lists contain the entities of all Input, In_Out, Output and
28134 -- Proof_In constituents that appear in Refined_Global and participate
28135 -- in state refinement.
28137 In_Items : Elist_Id := No_Elist;
28138 In_Out_Items : Elist_Id := No_Elist;
28139 Out_Items : Elist_Id := No_Elist;
28140 Proof_In_Items : Elist_Id := No_Elist;
28141 -- These lists contain the entities of all Input, In_Out, Output and
28142 -- Proof_In items defined in the corresponding Global pragma.
28144 Repeat_Items : Elist_Id := No_Elist;
28145 -- A list of all global items without full visible refinement found
28146 -- in pragma Global. These states should be repeated in the global
28147 -- refinement (SPARK RM 7.2.4(3c)) unless they have a partial visible
28148 -- refinement, in which case they may be repeated (SPARK RM 7.2.4(3d)).
28150 Spec_Id : Entity_Id;
28151 -- The entity of the subprogram subject to pragma Refined_Global
28153 States : Elist_Id := No_Elist;
28154 -- A list of all states with full or partial visible refinement found in
28155 -- pragma Global.
28157 procedure Check_In_Out_States;
28158 -- Determine whether the corresponding Global pragma mentions In_Out
28159 -- states with visible refinement and if so, ensure that one of the
28160 -- following completions apply to the constituents of the state:
28161 -- 1) there is at least one constituent of mode In_Out
28162 -- 2) there is at least one Input and one Output constituent
28163 -- 3) not all constituents are present and one of them is of mode
28164 -- Output.
28165 -- This routine may remove elements from In_Constits, In_Out_Constits,
28166 -- Out_Constits and Proof_In_Constits.
28168 procedure Check_Input_States;
28169 -- Determine whether the corresponding Global pragma mentions Input
28170 -- states with visible refinement and if so, ensure that at least one of
28171 -- its constituents appears as an Input item in Refined_Global.
28172 -- This routine may remove elements from In_Constits, In_Out_Constits,
28173 -- Out_Constits and Proof_In_Constits.
28175 procedure Check_Output_States;
28176 -- Determine whether the corresponding Global pragma mentions Output
28177 -- states with visible refinement and if so, ensure that all of its
28178 -- constituents appear as Output items in Refined_Global.
28179 -- This routine may remove elements from In_Constits, In_Out_Constits,
28180 -- Out_Constits and Proof_In_Constits.
28182 procedure Check_Proof_In_States;
28183 -- Determine whether the corresponding Global pragma mentions Proof_In
28184 -- states with visible refinement and if so, ensure that at least one of
28185 -- its constituents appears as a Proof_In item in Refined_Global.
28186 -- This routine may remove elements from In_Constits, In_Out_Constits,
28187 -- Out_Constits and Proof_In_Constits.
28189 procedure Check_Refined_Global_List
28190 (List : Node_Id;
28191 Global_Mode : Name_Id := Name_Input);
28192 -- Verify the legality of a single global list declaration. Global_Mode
28193 -- denotes the current mode in effect.
28195 procedure Collect_Global_Items
28196 (List : Node_Id;
28197 Mode : Name_Id := Name_Input);
28198 -- Gather all Input, In_Out, Output and Proof_In items from node List
28199 -- and separate them in lists In_Items, In_Out_Items, Out_Items and
28200 -- Proof_In_Items. Flags Has_In_State, Has_In_Out_State, Has_Out_State
28201 -- and Has_Proof_In_State are set when there is at least one abstract
28202 -- state with full or partial visible refinement available in the
28203 -- corresponding mode. Flag Has_Null_State is set when at least state
28204 -- has a null refinement. Mode denotes the current global mode in
28205 -- effect.
28207 function Present_Then_Remove
28208 (List : Elist_Id;
28209 Item : Entity_Id) return Boolean;
28210 -- Search List for a particular entity Item. If Item has been found,
28211 -- remove it from List. This routine is used to strip lists In_Constits,
28212 -- In_Out_Constits and Out_Constits of valid constituents.
28214 procedure Present_Then_Remove (List : Elist_Id; Item : Entity_Id);
28215 -- Same as function Present_Then_Remove, but do not report the presence
28216 -- of Item in List.
28218 procedure Report_Extra_Constituents;
28219 -- Emit an error for each constituent found in lists In_Constits,
28220 -- In_Out_Constits and Out_Constits.
28222 procedure Report_Missing_Items;
28223 -- Emit an error for each global item not repeated found in list
28224 -- Repeat_Items.
28226 -------------------------
28227 -- Check_In_Out_States --
28228 -------------------------
28230 procedure Check_In_Out_States is
28231 procedure Check_Constituent_Usage (State_Id : Entity_Id);
28232 -- Determine whether one of the following coverage scenarios is in
28233 -- effect:
28234 -- 1) there is at least one constituent of mode In_Out or Output
28235 -- 2) there is at least one pair of constituents with modes Input
28236 -- and Output, or Proof_In and Output.
28237 -- 3) there is at least one constituent of mode Output and not all
28238 -- constituents are present.
28239 -- If this is not the case, emit an error (SPARK RM 7.2.4(5)).
28241 -----------------------------
28242 -- Check_Constituent_Usage --
28243 -----------------------------
28245 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
28246 Constits : constant Elist_Id :=
28247 Partial_Refinement_Constituents (State_Id);
28248 Constit_Elmt : Elmt_Id;
28249 Constit_Id : Entity_Id;
28250 Has_Missing : Boolean := False;
28251 In_Out_Seen : Boolean := False;
28252 Input_Seen : Boolean := False;
28253 Output_Seen : Boolean := False;
28254 Proof_In_Seen : Boolean := False;
28256 begin
28257 -- Process all the constituents of the state and note their modes
28258 -- within the global refinement.
28260 if Present (Constits) then
28261 Constit_Elmt := First_Elmt (Constits);
28262 while Present (Constit_Elmt) loop
28263 Constit_Id := Node (Constit_Elmt);
28265 if Present_Then_Remove (In_Constits, Constit_Id) then
28266 Input_Seen := True;
28268 elsif Present_Then_Remove (In_Out_Constits, Constit_Id) then
28269 In_Out_Seen := True;
28271 elsif Present_Then_Remove (Out_Constits, Constit_Id) then
28272 Output_Seen := True;
28274 elsif Present_Then_Remove (Proof_In_Constits, Constit_Id)
28275 then
28276 Proof_In_Seen := True;
28278 else
28279 Has_Missing := True;
28280 end if;
28282 Next_Elmt (Constit_Elmt);
28283 end loop;
28284 end if;
28286 -- An In_Out constituent is a valid completion
28288 if In_Out_Seen then
28289 null;
28291 -- A pair of one Input/Proof_In and one Output constituent is a
28292 -- valid completion.
28294 elsif (Input_Seen or Proof_In_Seen) and Output_Seen then
28295 null;
28297 elsif Output_Seen then
28299 -- A single Output constituent is a valid completion only when
28300 -- some of the other constituents are missing.
28302 if Has_Missing then
28303 null;
28305 -- Otherwise all constituents are of mode Output
28307 else
28308 SPARK_Msg_NE
28309 ("global refinement of state & must include at least one "
28310 & "constituent of mode `In_Out`, `Input`, or `Proof_In`",
28311 N, State_Id);
28312 end if;
28314 -- The state lacks a completion. When full refinement is visible,
28315 -- always emit an error (SPARK RM 7.2.4(3a)). When only partial
28316 -- refinement is visible, emit an error if the abstract state
28317 -- itself is not utilized (SPARK RM 7.2.4(3d)). In the case where
28318 -- both are utilized, Check_State_And_Constituent_Use. will issue
28319 -- the error.
28321 elsif not Input_Seen
28322 and then not In_Out_Seen
28323 and then not Output_Seen
28324 and then not Proof_In_Seen
28325 then
28326 if Has_Visible_Refinement (State_Id)
28327 or else Contains (Repeat_Items, State_Id)
28328 then
28329 SPARK_Msg_NE
28330 ("missing global refinement of state &", N, State_Id);
28331 end if;
28333 -- Otherwise the state has a malformed completion where at least
28334 -- one of the constituents has a different mode.
28336 else
28337 SPARK_Msg_NE
28338 ("global refinement of state & redefines the mode of its "
28339 & "constituents", N, State_Id);
28340 end if;
28341 end Check_Constituent_Usage;
28343 -- Local variables
28345 Item_Elmt : Elmt_Id;
28346 Item_Id : Entity_Id;
28348 -- Start of processing for Check_In_Out_States
28350 begin
28351 -- Do not perform this check in an instance because it was already
28352 -- performed successfully in the generic template.
28354 if In_Instance then
28355 null;
28357 -- Inspect the In_Out items of the corresponding Global pragma
28358 -- looking for a state with a visible refinement.
28360 elsif Has_In_Out_State and then Present (In_Out_Items) then
28361 Item_Elmt := First_Elmt (In_Out_Items);
28362 while Present (Item_Elmt) loop
28363 Item_Id := Node (Item_Elmt);
28365 -- Ensure that one of the three coverage variants is satisfied
28367 if Ekind (Item_Id) = E_Abstract_State
28368 and then Has_Non_Null_Visible_Refinement (Item_Id)
28369 then
28370 Check_Constituent_Usage (Item_Id);
28371 end if;
28373 Next_Elmt (Item_Elmt);
28374 end loop;
28375 end if;
28376 end Check_In_Out_States;
28378 ------------------------
28379 -- Check_Input_States --
28380 ------------------------
28382 procedure Check_Input_States is
28383 procedure Check_Constituent_Usage (State_Id : Entity_Id);
28384 -- Determine whether at least one constituent of state State_Id with
28385 -- full or partial visible refinement is used and has mode Input.
28386 -- Ensure that the remaining constituents do not have In_Out or
28387 -- Output modes. Emit an error if this is not the case
28388 -- (SPARK RM 7.2.4(5)).
28390 -----------------------------
28391 -- Check_Constituent_Usage --
28392 -----------------------------
28394 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
28395 Constits : constant Elist_Id :=
28396 Partial_Refinement_Constituents (State_Id);
28397 Constit_Elmt : Elmt_Id;
28398 Constit_Id : Entity_Id;
28399 In_Seen : Boolean := False;
28401 begin
28402 if Present (Constits) then
28403 Constit_Elmt := First_Elmt (Constits);
28404 while Present (Constit_Elmt) loop
28405 Constit_Id := Node (Constit_Elmt);
28407 -- At least one of the constituents appears as an Input
28409 if Present_Then_Remove (In_Constits, Constit_Id) then
28410 In_Seen := True;
28412 -- A Proof_In constituent can refine an Input state as long
28413 -- as there is at least one Input constituent present.
28415 elsif Present_Then_Remove (Proof_In_Constits, Constit_Id)
28416 then
28417 null;
28419 -- The constituent appears in the global refinement, but has
28420 -- mode In_Out or Output (SPARK RM 7.2.4(5)).
28422 elsif Present_Then_Remove (In_Out_Constits, Constit_Id)
28423 or else Present_Then_Remove (Out_Constits, Constit_Id)
28424 then
28425 Error_Msg_Name_1 := Chars (State_Id);
28426 SPARK_Msg_NE
28427 ("constituent & of state % must have mode `Input` in "
28428 & "global refinement", N, Constit_Id);
28429 end if;
28431 Next_Elmt (Constit_Elmt);
28432 end loop;
28433 end if;
28435 -- Not one of the constituents appeared as Input. Always emit an
28436 -- error when the full refinement is visible (SPARK RM 7.2.4(3a)).
28437 -- When only partial refinement is visible, emit an error if the
28438 -- abstract state itself is not utilized (SPARK RM 7.2.4(3d)). In
28439 -- the case where both are utilized, an error will be issued in
28440 -- Check_State_And_Constituent_Use.
28442 if not In_Seen
28443 and then (Has_Visible_Refinement (State_Id)
28444 or else Contains (Repeat_Items, State_Id))
28445 then
28446 SPARK_Msg_NE
28447 ("global refinement of state & must include at least one "
28448 & "constituent of mode `Input`", N, State_Id);
28449 end if;
28450 end Check_Constituent_Usage;
28452 -- Local variables
28454 Item_Elmt : Elmt_Id;
28455 Item_Id : Entity_Id;
28457 -- Start of processing for Check_Input_States
28459 begin
28460 -- Do not perform this check in an instance because it was already
28461 -- performed successfully in the generic template.
28463 if In_Instance then
28464 null;
28466 -- Inspect the Input items of the corresponding Global pragma looking
28467 -- for a state with a visible refinement.
28469 elsif Has_In_State and then Present (In_Items) then
28470 Item_Elmt := First_Elmt (In_Items);
28471 while Present (Item_Elmt) loop
28472 Item_Id := Node (Item_Elmt);
28474 -- When full refinement is visible, ensure that at least one of
28475 -- the constituents is utilized and is of mode Input. When only
28476 -- partial refinement is visible, ensure that either one of
28477 -- the constituents is utilized and is of mode Input, or the
28478 -- abstract state is repeated and no constituent is utilized.
28480 if Ekind (Item_Id) = E_Abstract_State
28481 and then Has_Non_Null_Visible_Refinement (Item_Id)
28482 then
28483 Check_Constituent_Usage (Item_Id);
28484 end if;
28486 Next_Elmt (Item_Elmt);
28487 end loop;
28488 end if;
28489 end Check_Input_States;
28491 -------------------------
28492 -- Check_Output_States --
28493 -------------------------
28495 procedure Check_Output_States is
28496 procedure Check_Constituent_Usage (State_Id : Entity_Id);
28497 -- Determine whether all constituents of state State_Id with full
28498 -- visible refinement are used and have mode Output. Emit an error
28499 -- if this is not the case (SPARK RM 7.2.4(5)).
28501 -----------------------------
28502 -- Check_Constituent_Usage --
28503 -----------------------------
28505 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
28506 Constits : constant Elist_Id :=
28507 Partial_Refinement_Constituents (State_Id);
28508 Only_Partial : constant Boolean :=
28509 not Has_Visible_Refinement (State_Id);
28510 Constit_Elmt : Elmt_Id;
28511 Constit_Id : Entity_Id;
28512 Posted : Boolean := False;
28514 begin
28515 if Present (Constits) then
28516 Constit_Elmt := First_Elmt (Constits);
28517 while Present (Constit_Elmt) loop
28518 Constit_Id := Node (Constit_Elmt);
28520 -- Issue an error when a constituent of State_Id is utilized
28521 -- and State_Id has only partial visible refinement
28522 -- (SPARK RM 7.2.4(3d)).
28524 if Only_Partial then
28525 if Present_Then_Remove (Out_Constits, Constit_Id)
28526 or else Present_Then_Remove (In_Constits, Constit_Id)
28527 or else
28528 Present_Then_Remove (In_Out_Constits, Constit_Id)
28529 or else
28530 Present_Then_Remove (Proof_In_Constits, Constit_Id)
28531 then
28532 Error_Msg_Name_1 := Chars (State_Id);
28533 SPARK_Msg_NE
28534 ("constituent & of state % cannot be used in global "
28535 & "refinement", N, Constit_Id);
28536 Error_Msg_Name_1 := Chars (State_Id);
28537 SPARK_Msg_N ("\use state % instead", N);
28538 end if;
28540 elsif Present_Then_Remove (Out_Constits, Constit_Id) then
28541 null;
28543 -- The constituent appears in the global refinement, but has
28544 -- mode Input, In_Out or Proof_In (SPARK RM 7.2.4(5)).
28546 elsif Present_Then_Remove (In_Constits, Constit_Id)
28547 or else Present_Then_Remove (In_Out_Constits, Constit_Id)
28548 or else Present_Then_Remove (Proof_In_Constits, Constit_Id)
28549 then
28550 Error_Msg_Name_1 := Chars (State_Id);
28551 SPARK_Msg_NE
28552 ("constituent & of state % must have mode `Output` in "
28553 & "global refinement", N, Constit_Id);
28555 -- The constituent is altogether missing (SPARK RM 7.2.5(3))
28557 else
28558 if not Posted then
28559 Posted := True;
28560 SPARK_Msg_NE
28561 ("`Output` state & must be replaced by all its "
28562 & "constituents in global refinement", N, State_Id);
28563 end if;
28565 SPARK_Msg_NE
28566 ("\constituent & is missing in output list",
28567 N, Constit_Id);
28568 end if;
28570 Next_Elmt (Constit_Elmt);
28571 end loop;
28572 end if;
28573 end Check_Constituent_Usage;
28575 -- Local variables
28577 Item_Elmt : Elmt_Id;
28578 Item_Id : Entity_Id;
28580 -- Start of processing for Check_Output_States
28582 begin
28583 -- Do not perform this check in an instance because it was already
28584 -- performed successfully in the generic template.
28586 if In_Instance then
28587 null;
28589 -- Inspect the Output items of the corresponding Global pragma
28590 -- looking for a state with a visible refinement.
28592 elsif Has_Out_State and then Present (Out_Items) then
28593 Item_Elmt := First_Elmt (Out_Items);
28594 while Present (Item_Elmt) loop
28595 Item_Id := Node (Item_Elmt);
28597 -- When full refinement is visible, ensure that all of the
28598 -- constituents are utilized and they have mode Output. When
28599 -- only partial refinement is visible, ensure that no
28600 -- constituent is utilized.
28602 if Ekind (Item_Id) = E_Abstract_State
28603 and then Has_Non_Null_Visible_Refinement (Item_Id)
28604 then
28605 Check_Constituent_Usage (Item_Id);
28606 end if;
28608 Next_Elmt (Item_Elmt);
28609 end loop;
28610 end if;
28611 end Check_Output_States;
28613 ---------------------------
28614 -- Check_Proof_In_States --
28615 ---------------------------
28617 procedure Check_Proof_In_States is
28618 procedure Check_Constituent_Usage (State_Id : Entity_Id);
28619 -- Determine whether at least one constituent of state State_Id with
28620 -- full or partial visible refinement is used and has mode Proof_In.
28621 -- Ensure that the remaining constituents do not have Input, In_Out,
28622 -- or Output modes. Emit an error if this is not the case
28623 -- (SPARK RM 7.2.4(5)).
28625 -----------------------------
28626 -- Check_Constituent_Usage --
28627 -----------------------------
28629 procedure Check_Constituent_Usage (State_Id : Entity_Id) is
28630 Constits : constant Elist_Id :=
28631 Partial_Refinement_Constituents (State_Id);
28632 Constit_Elmt : Elmt_Id;
28633 Constit_Id : Entity_Id;
28634 Proof_In_Seen : Boolean := False;
28636 begin
28637 if Present (Constits) then
28638 Constit_Elmt := First_Elmt (Constits);
28639 while Present (Constit_Elmt) loop
28640 Constit_Id := Node (Constit_Elmt);
28642 -- At least one of the constituents appears as Proof_In
28644 if Present_Then_Remove (Proof_In_Constits, Constit_Id) then
28645 Proof_In_Seen := True;
28647 -- The constituent appears in the global refinement, but has
28648 -- mode Input, In_Out or Output (SPARK RM 7.2.4(5)).
28650 elsif Present_Then_Remove (In_Constits, Constit_Id)
28651 or else Present_Then_Remove (In_Out_Constits, Constit_Id)
28652 or else Present_Then_Remove (Out_Constits, Constit_Id)
28653 then
28654 Error_Msg_Name_1 := Chars (State_Id);
28655 SPARK_Msg_NE
28656 ("constituent & of state % must have mode `Proof_In` "
28657 & "in global refinement", N, Constit_Id);
28658 end if;
28660 Next_Elmt (Constit_Elmt);
28661 end loop;
28662 end if;
28664 -- Not one of the constituents appeared as Proof_In. Always emit
28665 -- an error when full refinement is visible (SPARK RM 7.2.4(3a)).
28666 -- When only partial refinement is visible, emit an error if the
28667 -- abstract state itself is not utilized (SPARK RM 7.2.4(3d)). In
28668 -- the case where both are utilized, an error will be issued by
28669 -- Check_State_And_Constituent_Use.
28671 if not Proof_In_Seen
28672 and then (Has_Visible_Refinement (State_Id)
28673 or else Contains (Repeat_Items, State_Id))
28674 then
28675 SPARK_Msg_NE
28676 ("global refinement of state & must include at least one "
28677 & "constituent of mode `Proof_In`", N, State_Id);
28678 end if;
28679 end Check_Constituent_Usage;
28681 -- Local variables
28683 Item_Elmt : Elmt_Id;
28684 Item_Id : Entity_Id;
28686 -- Start of processing for Check_Proof_In_States
28688 begin
28689 -- Do not perform this check in an instance because it was already
28690 -- performed successfully in the generic template.
28692 if In_Instance then
28693 null;
28695 -- Inspect the Proof_In items of the corresponding Global pragma
28696 -- looking for a state with a visible refinement.
28698 elsif Has_Proof_In_State and then Present (Proof_In_Items) then
28699 Item_Elmt := First_Elmt (Proof_In_Items);
28700 while Present (Item_Elmt) loop
28701 Item_Id := Node (Item_Elmt);
28703 -- Ensure that at least one of the constituents is utilized
28704 -- and is of mode Proof_In. When only partial refinement is
28705 -- visible, ensure that either one of the constituents is
28706 -- utilized and is of mode Proof_In, or the abstract state
28707 -- is repeated and no constituent is utilized.
28709 if Ekind (Item_Id) = E_Abstract_State
28710 and then Has_Non_Null_Visible_Refinement (Item_Id)
28711 then
28712 Check_Constituent_Usage (Item_Id);
28713 end if;
28715 Next_Elmt (Item_Elmt);
28716 end loop;
28717 end if;
28718 end Check_Proof_In_States;
28720 -------------------------------
28721 -- Check_Refined_Global_List --
28722 -------------------------------
28724 procedure Check_Refined_Global_List
28725 (List : Node_Id;
28726 Global_Mode : Name_Id := Name_Input)
28728 procedure Check_Refined_Global_Item
28729 (Item : Node_Id;
28730 Global_Mode : Name_Id);
28731 -- Verify the legality of a single global item declaration. Parameter
28732 -- Global_Mode denotes the current mode in effect.
28734 -------------------------------
28735 -- Check_Refined_Global_Item --
28736 -------------------------------
28738 procedure Check_Refined_Global_Item
28739 (Item : Node_Id;
28740 Global_Mode : Name_Id)
28742 Item_Id : constant Entity_Id := Entity_Of (Item);
28744 procedure Inconsistent_Mode_Error (Expect : Name_Id);
28745 -- Issue a common error message for all mode mismatches. Expect
28746 -- denotes the expected mode.
28748 -----------------------------
28749 -- Inconsistent_Mode_Error --
28750 -----------------------------
28752 procedure Inconsistent_Mode_Error (Expect : Name_Id) is
28753 begin
28754 SPARK_Msg_NE
28755 ("global item & has inconsistent modes", Item, Item_Id);
28757 Error_Msg_Name_1 := Global_Mode;
28758 Error_Msg_Name_2 := Expect;
28759 SPARK_Msg_N ("\expected mode %, found mode %", Item);
28760 end Inconsistent_Mode_Error;
28762 -- Local variables
28764 Enc_State : Entity_Id := Empty;
28765 -- Encapsulating state for constituent, Empty otherwise
28767 -- Start of processing for Check_Refined_Global_Item
28769 begin
28770 if Ekind (Item_Id) in E_Abstract_State | E_Constant | E_Variable
28771 then
28772 Enc_State := Find_Encapsulating_State (States, Item_Id);
28773 end if;
28775 -- When the state or object acts as a constituent of another
28776 -- state with a visible refinement, collect it for the state
28777 -- completeness checks performed later on. Note that the item
28778 -- acts as a constituent only when the encapsulating state is
28779 -- present in pragma Global.
28781 if Present (Enc_State)
28782 and then (Has_Visible_Refinement (Enc_State)
28783 or else Has_Partial_Visible_Refinement (Enc_State))
28784 and then Contains (States, Enc_State)
28785 then
28786 -- If the state has only partial visible refinement, remove it
28787 -- from the list of items that should be repeated from pragma
28788 -- Global.
28790 if not Has_Visible_Refinement (Enc_State) then
28791 Present_Then_Remove (Repeat_Items, Enc_State);
28792 end if;
28794 if Global_Mode = Name_Input then
28795 Append_New_Elmt (Item_Id, In_Constits);
28797 elsif Global_Mode = Name_In_Out then
28798 Append_New_Elmt (Item_Id, In_Out_Constits);
28800 elsif Global_Mode = Name_Output then
28801 Append_New_Elmt (Item_Id, Out_Constits);
28803 elsif Global_Mode = Name_Proof_In then
28804 Append_New_Elmt (Item_Id, Proof_In_Constits);
28805 end if;
28807 -- When not a constituent, ensure that both occurrences of the
28808 -- item in pragmas Global and Refined_Global match. Also remove
28809 -- it when present from the list of items that should be repeated
28810 -- from pragma Global.
28812 else
28813 Present_Then_Remove (Repeat_Items, Item_Id);
28815 if Contains (In_Items, Item_Id) then
28816 if Global_Mode /= Name_Input then
28817 Inconsistent_Mode_Error (Name_Input);
28818 end if;
28820 elsif Contains (In_Out_Items, Item_Id) then
28821 if Global_Mode /= Name_In_Out then
28822 Inconsistent_Mode_Error (Name_In_Out);
28823 end if;
28825 elsif Contains (Out_Items, Item_Id) then
28826 if Global_Mode /= Name_Output then
28827 Inconsistent_Mode_Error (Name_Output);
28828 end if;
28830 elsif Contains (Proof_In_Items, Item_Id) then
28831 null;
28833 -- The item does not appear in the corresponding Global pragma,
28834 -- it must be an extra (SPARK RM 7.2.4(3)).
28836 else
28837 pragma Assert (Present (Global));
28838 Error_Msg_Sloc := Sloc (Global);
28839 SPARK_Msg_NE
28840 ("extra global item & does not refine or repeat any "
28841 & "global item #", Item, Item_Id);
28842 end if;
28843 end if;
28844 end Check_Refined_Global_Item;
28846 -- Local variables
28848 Item : Node_Id;
28850 -- Start of processing for Check_Refined_Global_List
28852 begin
28853 -- Do not perform this check in an instance because it was already
28854 -- performed successfully in the generic template.
28856 if In_Instance then
28857 null;
28859 elsif Nkind (List) = N_Null then
28860 null;
28862 -- Single global item declaration
28864 elsif Nkind (List) in N_Expanded_Name
28865 | N_Identifier
28866 | N_Selected_Component
28867 then
28868 Check_Refined_Global_Item (List, Global_Mode);
28870 -- Simple global list or moded global list declaration
28872 elsif Nkind (List) = N_Aggregate then
28874 -- The declaration of a simple global list appear as a collection
28875 -- of expressions.
28877 if Present (Expressions (List)) then
28878 Item := First (Expressions (List));
28879 while Present (Item) loop
28880 Check_Refined_Global_Item (Item, Global_Mode);
28881 Next (Item);
28882 end loop;
28884 -- The declaration of a moded global list appears as a collection
28885 -- of component associations where individual choices denote
28886 -- modes.
28888 elsif Present (Component_Associations (List)) then
28889 Item := First (Component_Associations (List));
28890 while Present (Item) loop
28891 Check_Refined_Global_List
28892 (List => Expression (Item),
28893 Global_Mode => Chars (First (Choices (Item))));
28895 Next (Item);
28896 end loop;
28898 -- Invalid tree
28900 else
28901 raise Program_Error;
28902 end if;
28904 -- Invalid list
28906 else
28907 raise Program_Error;
28908 end if;
28909 end Check_Refined_Global_List;
28911 --------------------------
28912 -- Collect_Global_Items --
28913 --------------------------
28915 procedure Collect_Global_Items
28916 (List : Node_Id;
28917 Mode : Name_Id := Name_Input)
28919 procedure Collect_Global_Item
28920 (Item : Node_Id;
28921 Item_Mode : Name_Id);
28922 -- Add a single item to the appropriate list. Item_Mode denotes the
28923 -- current mode in effect.
28925 -------------------------
28926 -- Collect_Global_Item --
28927 -------------------------
28929 procedure Collect_Global_Item
28930 (Item : Node_Id;
28931 Item_Mode : Name_Id)
28933 Item_Id : constant Entity_Id := Available_View (Entity_Of (Item));
28934 -- The above handles abstract views of variables and states built
28935 -- for limited with clauses.
28937 begin
28938 -- Signal that the global list contains at least one abstract
28939 -- state with a visible refinement. Note that the refinement may
28940 -- be null in which case there are no constituents.
28942 if Ekind (Item_Id) = E_Abstract_State then
28943 if Has_Null_Visible_Refinement (Item_Id) then
28944 Has_Null_State := True;
28946 elsif Has_Non_Null_Visible_Refinement (Item_Id) then
28947 Append_New_Elmt (Item_Id, States);
28949 if Item_Mode = Name_Input then
28950 Has_In_State := True;
28951 elsif Item_Mode = Name_In_Out then
28952 Has_In_Out_State := True;
28953 elsif Item_Mode = Name_Output then
28954 Has_Out_State := True;
28955 elsif Item_Mode = Name_Proof_In then
28956 Has_Proof_In_State := True;
28957 end if;
28958 end if;
28959 end if;
28961 -- Record global items without full visible refinement found in
28962 -- pragma Global which should be repeated in the global refinement
28963 -- (SPARK RM 7.2.4(3c), SPARK RM 7.2.4(3d)).
28965 if Ekind (Item_Id) /= E_Abstract_State
28966 or else not Has_Visible_Refinement (Item_Id)
28967 then
28968 Append_New_Elmt (Item_Id, Repeat_Items);
28969 end if;
28971 -- Add the item to the proper list
28973 if Item_Mode = Name_Input then
28974 Append_New_Elmt (Item_Id, In_Items);
28975 elsif Item_Mode = Name_In_Out then
28976 Append_New_Elmt (Item_Id, In_Out_Items);
28977 elsif Item_Mode = Name_Output then
28978 Append_New_Elmt (Item_Id, Out_Items);
28979 elsif Item_Mode = Name_Proof_In then
28980 Append_New_Elmt (Item_Id, Proof_In_Items);
28981 end if;
28982 end Collect_Global_Item;
28984 -- Local variables
28986 Item : Node_Id;
28988 -- Start of processing for Collect_Global_Items
28990 begin
28991 if Nkind (List) = N_Null then
28992 null;
28994 -- Single global item declaration
28996 elsif Nkind (List) in N_Expanded_Name
28997 | N_Identifier
28998 | N_Selected_Component
28999 then
29000 Collect_Global_Item (List, Mode);
29002 -- Single global list or moded global list declaration
29004 elsif Nkind (List) = N_Aggregate then
29006 -- The declaration of a simple global list appear as a collection
29007 -- of expressions.
29009 if Present (Expressions (List)) then
29010 Item := First (Expressions (List));
29011 while Present (Item) loop
29012 Collect_Global_Item (Item, Mode);
29013 Next (Item);
29014 end loop;
29016 -- The declaration of a moded global list appears as a collection
29017 -- of component associations where individual choices denote mode.
29019 elsif Present (Component_Associations (List)) then
29020 Item := First (Component_Associations (List));
29021 while Present (Item) loop
29022 Collect_Global_Items
29023 (List => Expression (Item),
29024 Mode => Chars (First (Choices (Item))));
29026 Next (Item);
29027 end loop;
29029 -- Invalid tree
29031 else
29032 raise Program_Error;
29033 end if;
29035 -- To accommodate partial decoration of disabled SPARK features, this
29036 -- routine may be called with illegal input. If this is the case, do
29037 -- not raise Program_Error.
29039 else
29040 null;
29041 end if;
29042 end Collect_Global_Items;
29044 -------------------------
29045 -- Present_Then_Remove --
29046 -------------------------
29048 function Present_Then_Remove
29049 (List : Elist_Id;
29050 Item : Entity_Id) return Boolean
29052 Elmt : Elmt_Id;
29054 begin
29055 if Present (List) then
29056 Elmt := First_Elmt (List);
29057 while Present (Elmt) loop
29058 if Node (Elmt) = Item then
29059 Remove_Elmt (List, Elmt);
29060 return True;
29061 end if;
29063 Next_Elmt (Elmt);
29064 end loop;
29065 end if;
29067 return False;
29068 end Present_Then_Remove;
29070 procedure Present_Then_Remove (List : Elist_Id; Item : Entity_Id) is
29071 Ignore : Boolean;
29072 begin
29073 Ignore := Present_Then_Remove (List, Item);
29074 end Present_Then_Remove;
29076 -------------------------------
29077 -- Report_Extra_Constituents --
29078 -------------------------------
29080 procedure Report_Extra_Constituents is
29081 procedure Report_Extra_Constituents_In_List (List : Elist_Id);
29082 -- Emit an error for every element of List
29084 ---------------------------------------
29085 -- Report_Extra_Constituents_In_List --
29086 ---------------------------------------
29088 procedure Report_Extra_Constituents_In_List (List : Elist_Id) is
29089 Constit_Elmt : Elmt_Id;
29091 begin
29092 if Present (List) then
29093 Constit_Elmt := First_Elmt (List);
29094 while Present (Constit_Elmt) loop
29095 SPARK_Msg_NE ("extra constituent &", N, Node (Constit_Elmt));
29096 Next_Elmt (Constit_Elmt);
29097 end loop;
29098 end if;
29099 end Report_Extra_Constituents_In_List;
29101 -- Start of processing for Report_Extra_Constituents
29103 begin
29104 -- Do not perform this check in an instance because it was already
29105 -- performed successfully in the generic template.
29107 if In_Instance then
29108 null;
29110 else
29111 Report_Extra_Constituents_In_List (In_Constits);
29112 Report_Extra_Constituents_In_List (In_Out_Constits);
29113 Report_Extra_Constituents_In_List (Out_Constits);
29114 Report_Extra_Constituents_In_List (Proof_In_Constits);
29115 end if;
29116 end Report_Extra_Constituents;
29118 --------------------------
29119 -- Report_Missing_Items --
29120 --------------------------
29122 procedure Report_Missing_Items is
29123 Item_Elmt : Elmt_Id;
29124 Item_Id : Entity_Id;
29126 begin
29127 -- Do not perform this check in an instance because it was already
29128 -- performed successfully in the generic template.
29130 if In_Instance then
29131 null;
29133 else
29134 if Present (Repeat_Items) then
29135 Item_Elmt := First_Elmt (Repeat_Items);
29136 while Present (Item_Elmt) loop
29137 Item_Id := Node (Item_Elmt);
29138 SPARK_Msg_NE ("missing global item &", N, Item_Id);
29139 Next_Elmt (Item_Elmt);
29140 end loop;
29141 end if;
29142 end if;
29143 end Report_Missing_Items;
29145 -- Local variables
29147 Body_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
29148 Errors : constant Nat := Serious_Errors_Detected;
29149 Items : Node_Id;
29150 No_Constit : Boolean;
29152 -- Start of processing for Analyze_Refined_Global_In_Decl_Part
29154 begin
29155 -- Do not analyze the pragma multiple times
29157 if Is_Analyzed_Pragma (N) then
29158 return;
29159 end if;
29161 Spec_Id := Unique_Defining_Entity (Body_Decl);
29163 -- Use the anonymous object as the proper spec when Refined_Global
29164 -- applies to the body of a single task type. The object carries the
29165 -- proper Chars as well as all non-refined versions of pragmas.
29167 if Is_Single_Concurrent_Type (Spec_Id) then
29168 Spec_Id := Anonymous_Object (Spec_Id);
29169 end if;
29171 Global := Get_Pragma (Spec_Id, Pragma_Global);
29172 Items := Expression (Get_Argument (N, Spec_Id));
29174 -- The subprogram declaration lacks pragma Global. This renders
29175 -- Refined_Global useless as there is nothing to refine.
29177 if No (Global) then
29178 SPARK_Msg_NE
29179 (Fix_Msg (Spec_Id, "useless refinement, declaration of subprogram "
29180 & "& lacks aspect or pragma Global"), N, Spec_Id);
29181 goto Leave;
29182 end if;
29184 -- Extract all relevant items from the corresponding Global pragma
29186 Collect_Global_Items (Expression (Get_Argument (Global, Spec_Id)));
29188 -- Package and subprogram bodies are instantiated individually in
29189 -- a separate compiler pass. Due to this mode of instantiation, the
29190 -- refinement of a state may no longer be visible when a subprogram
29191 -- body contract is instantiated. Since the generic template is legal,
29192 -- do not perform this check in the instance to circumvent this oddity.
29194 if In_Instance then
29195 null;
29197 -- Non-instance case
29199 else
29200 -- The corresponding Global pragma must mention at least one
29201 -- state with a visible refinement at the point Refined_Global
29202 -- is processed. States with null refinements need Refined_Global
29203 -- pragma (SPARK RM 7.2.4(2)).
29205 if not Has_In_State
29206 and then not Has_In_Out_State
29207 and then not Has_Out_State
29208 and then not Has_Proof_In_State
29209 and then not Has_Null_State
29210 then
29211 SPARK_Msg_NE
29212 (Fix_Msg (Spec_Id, "useless refinement, subprogram & does not "
29213 & "depend on abstract state with visible refinement"),
29214 N, Spec_Id);
29215 goto Leave;
29217 -- The global refinement of inputs and outputs cannot be null when
29218 -- the corresponding Global pragma contains at least one item except
29219 -- in the case where we have states with null refinements.
29221 elsif Nkind (Items) = N_Null
29222 and then
29223 (Present (In_Items)
29224 or else Present (In_Out_Items)
29225 or else Present (Out_Items)
29226 or else Present (Proof_In_Items))
29227 and then not Has_Null_State
29228 then
29229 SPARK_Msg_NE
29230 (Fix_Msg (Spec_Id, "refinement cannot be null, subprogram & has "
29231 & "global items"), N, Spec_Id);
29232 goto Leave;
29233 end if;
29234 end if;
29236 -- Analyze Refined_Global as if it behaved as a regular pragma Global.
29237 -- This ensures that the categorization of all refined global items is
29238 -- consistent with their role.
29240 Analyze_Global_In_Decl_Part (N);
29242 -- Perform all refinement checks with respect to completeness and mode
29243 -- matching.
29245 if Serious_Errors_Detected = Errors then
29246 Check_Refined_Global_List (Items);
29247 end if;
29249 -- Store the information that no constituent is used in the global
29250 -- refinement, prior to calling checking procedures which remove items
29251 -- from the list of constituents.
29253 No_Constit :=
29254 No (In_Constits)
29255 and then No (In_Out_Constits)
29256 and then No (Out_Constits)
29257 and then No (Proof_In_Constits);
29259 -- For Input states with visible refinement, at least one constituent
29260 -- must be used as an Input in the global refinement.
29262 if Serious_Errors_Detected = Errors then
29263 Check_Input_States;
29264 end if;
29266 -- Verify all possible completion variants for In_Out states with
29267 -- visible refinement.
29269 if Serious_Errors_Detected = Errors then
29270 Check_In_Out_States;
29271 end if;
29273 -- For Output states with visible refinement, all constituents must be
29274 -- used as Outputs in the global refinement.
29276 if Serious_Errors_Detected = Errors then
29277 Check_Output_States;
29278 end if;
29280 -- For Proof_In states with visible refinement, at least one constituent
29281 -- must be used as Proof_In in the global refinement.
29283 if Serious_Errors_Detected = Errors then
29284 Check_Proof_In_States;
29285 end if;
29287 -- Emit errors for all constituents that belong to other states with
29288 -- visible refinement that do not appear in Global.
29290 if Serious_Errors_Detected = Errors then
29291 Report_Extra_Constituents;
29292 end if;
29294 -- Emit errors for all items in Global that are not repeated in the
29295 -- global refinement and for which there is no full visible refinement
29296 -- and, in the case of states with partial visible refinement, no
29297 -- constituent is mentioned in the global refinement.
29299 if Serious_Errors_Detected = Errors then
29300 Report_Missing_Items;
29301 end if;
29303 -- Emit an error if no constituent is used in the global refinement
29304 -- (SPARK RM 7.2.4(3f)). Emit this error last, in case a more precise
29305 -- one may be issued by the checking procedures. Do not perform this
29306 -- check in an instance because it was already performed successfully
29307 -- in the generic template.
29309 if Serious_Errors_Detected = Errors
29310 and then not In_Instance
29311 and then not Has_Null_State
29312 and then No_Constit
29313 then
29314 SPARK_Msg_N ("missing refinement", N);
29315 end if;
29317 <<Leave>>
29318 Set_Is_Analyzed_Pragma (N);
29319 end Analyze_Refined_Global_In_Decl_Part;
29321 ----------------------------------------
29322 -- Analyze_Refined_State_In_Decl_Part --
29323 ----------------------------------------
29325 procedure Analyze_Refined_State_In_Decl_Part
29326 (N : Node_Id;
29327 Freeze_Id : Entity_Id := Empty)
29329 Body_Decl : constant Node_Id := Find_Related_Package_Or_Body (N);
29330 Body_Id : constant Entity_Id := Defining_Entity (Body_Decl);
29331 Spec_Id : constant Entity_Id := Corresponding_Spec (Body_Decl);
29333 Available_States : Elist_Id := No_Elist;
29334 -- A list of all abstract states defined in the package declaration that
29335 -- are available for refinement. The list is used to report unrefined
29336 -- states.
29338 Body_States : Elist_Id := No_Elist;
29339 -- A list of all hidden states that appear in the body of the related
29340 -- package. The list is used to report unused hidden states.
29342 Constituents_Seen : Elist_Id := No_Elist;
29343 -- A list that contains all constituents processed so far. The list is
29344 -- used to detect multiple uses of the same constituent.
29346 Freeze_Posted : Boolean := False;
29347 -- A flag that controls the output of a freezing-related error (see use
29348 -- below).
29350 Refined_States_Seen : Elist_Id := No_Elist;
29351 -- A list that contains all refined states processed so far. The list is
29352 -- used to detect duplicate refinements.
29354 procedure Analyze_Refinement_Clause (Clause : Node_Id);
29355 -- Perform full analysis of a single refinement clause
29357 procedure Report_Unrefined_States (States : Elist_Id);
29358 -- Emit errors for all unrefined abstract states found in list States
29360 -------------------------------
29361 -- Analyze_Refinement_Clause --
29362 -------------------------------
29364 procedure Analyze_Refinement_Clause (Clause : Node_Id) is
29365 AR_Constit : Entity_Id := Empty;
29366 AW_Constit : Entity_Id := Empty;
29367 ER_Constit : Entity_Id := Empty;
29368 EW_Constit : Entity_Id := Empty;
29369 -- The entities of external constituents that contain one of the
29370 -- following enabled properties: Async_Readers, Async_Writers,
29371 -- Effective_Reads and Effective_Writes.
29373 External_Constit_Seen : Boolean := False;
29374 -- Flag used to mark when at least one external constituent is part
29375 -- of the state refinement.
29377 Non_Null_Seen : Boolean := False;
29378 Null_Seen : Boolean := False;
29379 -- Flags used to detect multiple uses of null in a single clause or a
29380 -- mixture of null and non-null constituents.
29382 Part_Of_Constits : Elist_Id := No_Elist;
29383 -- A list of all candidate constituents subject to indicator Part_Of
29384 -- where the encapsulating state is the current state.
29386 State : Node_Id;
29387 State_Id : Entity_Id;
29388 -- The current state being refined
29390 procedure Analyze_Constituent (Constit : Node_Id);
29391 -- Perform full analysis of a single constituent
29393 procedure Check_External_Property
29394 (Prop_Nam : Name_Id;
29395 Enabled : Boolean;
29396 Constit : Entity_Id);
29397 -- Determine whether a property denoted by name Prop_Nam is present
29398 -- in the refined state. Emit an error if this is not the case. Flag
29399 -- Enabled should be set when the property applies to the refined
29400 -- state. Constit denotes the constituent (if any) which introduces
29401 -- the property in the refinement.
29403 procedure Match_State;
29404 -- Determine whether the state being refined appears in list
29405 -- Available_States. Emit an error when attempting to re-refine the
29406 -- state or when the state is not defined in the package declaration,
29407 -- otherwise remove the state from Available_States.
29409 procedure Report_Unused_Constituents (Constits : Elist_Id);
29410 -- Emit errors for all unused Part_Of constituents in list Constits
29412 -------------------------
29413 -- Analyze_Constituent --
29414 -------------------------
29416 procedure Analyze_Constituent (Constit : Node_Id) is
29417 procedure Match_Constituent (Constit_Id : Entity_Id);
29418 -- Determine whether constituent Constit denoted by its entity
29419 -- Constit_Id appears in Body_States. Emit an error when the
29420 -- constituent is not a valid hidden state of the related package
29421 -- or when it is used more than once. Otherwise remove the
29422 -- constituent from Body_States.
29424 -----------------------
29425 -- Match_Constituent --
29426 -----------------------
29428 procedure Match_Constituent (Constit_Id : Entity_Id) is
29429 procedure Collect_Constituent;
29430 -- Verify the legality of constituent Constit_Id and add it to
29431 -- the refinements of State_Id.
29433 -------------------------
29434 -- Collect_Constituent --
29435 -------------------------
29437 procedure Collect_Constituent is
29438 Constits : Elist_Id;
29440 begin
29441 -- The Ghost policy in effect at the point of abstract state
29442 -- declaration and constituent must match (SPARK RM 6.9(15))
29444 Check_Ghost_Refinement
29445 (State, State_Id, Constit, Constit_Id);
29447 -- A synchronized state must be refined by a synchronized
29448 -- object or another synchronized state (SPARK RM 9.6).
29450 if Is_Synchronized_State (State_Id)
29451 and then not Is_Synchronized_Object (Constit_Id)
29452 and then not Is_Synchronized_State (Constit_Id)
29453 then
29454 SPARK_Msg_NE
29455 ("constituent of synchronized state & must be "
29456 & "synchronized", Constit, State_Id);
29457 end if;
29459 -- Add the constituent to the list of processed items to aid
29460 -- with the detection of duplicates.
29462 Append_New_Elmt (Constit_Id, Constituents_Seen);
29464 -- Collect the constituent in the list of refinement items
29465 -- and establish a relation between the refined state and
29466 -- the item.
29468 Constits := Refinement_Constituents (State_Id);
29470 if No (Constits) then
29471 Constits := New_Elmt_List;
29472 Set_Refinement_Constituents (State_Id, Constits);
29473 end if;
29475 Append_Elmt (Constit_Id, Constits);
29476 Set_Encapsulating_State (Constit_Id, State_Id);
29478 -- The state has at least one legal constituent, mark the
29479 -- start of the refinement region. The region ends when the
29480 -- body declarations end (see routine Analyze_Declarations).
29482 Set_Has_Visible_Refinement (State_Id);
29484 -- When the constituent is external, save its relevant
29485 -- property for further checks.
29487 if Async_Readers_Enabled (Constit_Id) then
29488 AR_Constit := Constit_Id;
29489 External_Constit_Seen := True;
29490 end if;
29492 if Async_Writers_Enabled (Constit_Id) then
29493 AW_Constit := Constit_Id;
29494 External_Constit_Seen := True;
29495 end if;
29497 if Effective_Reads_Enabled (Constit_Id) then
29498 ER_Constit := Constit_Id;
29499 External_Constit_Seen := True;
29500 end if;
29502 if Effective_Writes_Enabled (Constit_Id) then
29503 EW_Constit := Constit_Id;
29504 External_Constit_Seen := True;
29505 end if;
29506 end Collect_Constituent;
29508 -- Local variables
29510 State_Elmt : Elmt_Id;
29512 -- Start of processing for Match_Constituent
29514 begin
29515 -- Detect a duplicate use of a constituent
29517 if Contains (Constituents_Seen, Constit_Id) then
29518 SPARK_Msg_NE
29519 ("duplicate use of constituent &", Constit, Constit_Id);
29520 return;
29521 end if;
29523 -- The constituent is subject to a Part_Of indicator
29525 if Present (Encapsulating_State (Constit_Id)) then
29526 if Encapsulating_State (Constit_Id) = State_Id then
29527 Remove (Part_Of_Constits, Constit_Id);
29528 Collect_Constituent;
29530 -- The constituent is part of another state and is used
29531 -- incorrectly in the refinement of the current state.
29533 else
29534 Error_Msg_Name_1 := Chars (State_Id);
29535 SPARK_Msg_NE
29536 ("& cannot act as constituent of state %",
29537 Constit, Constit_Id);
29538 SPARK_Msg_NE
29539 ("\Part_Of indicator specifies encapsulator &",
29540 Constit, Encapsulating_State (Constit_Id));
29541 end if;
29543 else
29544 declare
29545 Pack_Id : Entity_Id;
29546 Placement : State_Space_Kind;
29547 begin
29548 -- Find where the constituent lives with respect to the
29549 -- state space.
29551 Find_Placement_In_State_Space
29552 (Item_Id => Constit_Id,
29553 Placement => Placement,
29554 Pack_Id => Pack_Id);
29556 -- The constituent is either part of the hidden state of
29557 -- the package or part of the visible state of a private
29558 -- child package, but lacks a Part_Of indicator.
29560 if (Placement = Private_State_Space
29561 and then Pack_Id = Spec_Id)
29562 or else
29563 (Placement = Visible_State_Space
29564 and then Is_Child_Unit (Pack_Id)
29565 and then not Is_Generic_Unit (Pack_Id)
29566 and then Is_Private_Descendant (Pack_Id))
29567 then
29568 Error_Msg_Name_1 := Chars (State_Id);
29569 SPARK_Msg_NE
29570 ("& cannot act as constituent of state %",
29571 Constit, Constit_Id);
29572 Error_Msg_Sloc :=
29573 Sloc (Enclosing_Declaration (Constit_Id));
29574 SPARK_Msg_NE
29575 ("\missing Part_Of indicator # should specify "
29576 & "encapsulator &",
29577 Constit, State_Id);
29579 -- The only other source of legal constituents is the
29580 -- body state space of the related package.
29582 else
29583 if Present (Body_States) then
29584 State_Elmt := First_Elmt (Body_States);
29585 while Present (State_Elmt) loop
29587 -- Consume a valid constituent to signal that it
29588 -- has been encountered.
29590 if Node (State_Elmt) = Constit_Id then
29591 Remove_Elmt (Body_States, State_Elmt);
29592 Collect_Constituent;
29593 return;
29594 end if;
29596 Next_Elmt (State_Elmt);
29597 end loop;
29598 end if;
29600 -- At this point it is known that the constituent is
29601 -- not part of the package hidden state and cannot be
29602 -- used in a refinement (SPARK RM 7.2.2(9)).
29604 Error_Msg_Name_1 := Chars (Spec_Id);
29605 SPARK_Msg_NE
29606 ("cannot use & in refinement, constituent is not a "
29607 & "hidden state of package %", Constit, Constit_Id);
29608 end if;
29609 end;
29610 end if;
29611 end Match_Constituent;
29613 -- Local variables
29615 Constit_Id : Entity_Id;
29616 Constits : Elist_Id;
29618 -- Start of processing for Analyze_Constituent
29620 begin
29621 -- Detect multiple uses of null in a single refinement clause or a
29622 -- mixture of null and non-null constituents.
29624 if Nkind (Constit) = N_Null then
29625 if Null_Seen then
29626 SPARK_Msg_N
29627 ("multiple null constituents not allowed", Constit);
29629 elsif Non_Null_Seen then
29630 SPARK_Msg_N
29631 ("cannot mix null and non-null constituents", Constit);
29633 else
29634 Null_Seen := True;
29636 -- Collect the constituent in the list of refinement items
29638 Constits := Refinement_Constituents (State_Id);
29640 if No (Constits) then
29641 Constits := New_Elmt_List;
29642 Set_Refinement_Constituents (State_Id, Constits);
29643 end if;
29645 Append_Elmt (Constit, Constits);
29647 -- The state has at least one legal constituent, mark the
29648 -- start of the refinement region. The region ends when the
29649 -- body declarations end (see Analyze_Declarations).
29651 Set_Has_Visible_Refinement (State_Id);
29652 end if;
29654 -- Non-null constituents
29656 else
29657 Non_Null_Seen := True;
29659 if Null_Seen then
29660 SPARK_Msg_N
29661 ("cannot mix null and non-null constituents", Constit);
29662 end if;
29664 Analyze (Constit);
29665 Resolve_State (Constit);
29667 -- Ensure that the constituent denotes a valid state or a
29668 -- whole object (SPARK RM 7.2.2(5)).
29670 if Is_Entity_Name (Constit) then
29671 Constit_Id := Entity_Of (Constit);
29673 -- When a constituent is declared after a subprogram body
29674 -- that caused freezing of the related contract where
29675 -- pragma Refined_State resides, the constituent appears
29676 -- undefined and carries Any_Id as its entity.
29678 -- package body Pack
29679 -- with Refined_State => (State => Constit)
29680 -- is
29681 -- procedure Proc
29682 -- with Refined_Global => (Input => Constit)
29683 -- is
29684 -- ...
29685 -- end Proc;
29687 -- Constit : ...;
29688 -- end Pack;
29690 if Constit_Id = Any_Id then
29691 SPARK_Msg_NE ("& is undefined", Constit, Constit_Id);
29693 -- Emit a specialized info message when the contract of
29694 -- the related package body was "frozen" by another body.
29695 -- Note that it is not possible to precisely identify why
29696 -- the constituent is undefined because it is not visible
29697 -- when pragma Refined_State is analyzed. This message is
29698 -- a reasonable approximation.
29700 if Present (Freeze_Id) and then not Freeze_Posted then
29701 Freeze_Posted := True;
29703 Error_Msg_Name_1 := Chars (Body_Id);
29704 Error_Msg_Sloc := Sloc (Freeze_Id);
29705 SPARK_Msg_NE
29706 ("body & declared # freezes the contract of %",
29707 N, Freeze_Id);
29708 SPARK_Msg_N
29709 ("\all constituents must be declared before body #",
29712 -- A misplaced constituent is a critical error because
29713 -- pragma Refined_Depends or Refined_Global depends on
29714 -- the proper link between a state and a constituent.
29715 -- Stop the compilation, as this leads to a multitude
29716 -- of misleading cascaded errors.
29718 raise Unrecoverable_Error;
29719 end if;
29721 -- The constituent is a valid state or object
29723 elsif Ekind (Constit_Id) in
29724 E_Abstract_State | E_Constant | E_Variable
29725 then
29726 Match_Constituent (Constit_Id);
29728 -- The variable may eventually become a constituent of a
29729 -- single protected/task type. Record the reference now
29730 -- and verify its legality when analyzing the contract of
29731 -- the variable (SPARK RM 9.3).
29733 if Ekind (Constit_Id) = E_Variable then
29734 Record_Possible_Part_Of_Reference
29735 (Var_Id => Constit_Id,
29736 Ref => Constit);
29737 end if;
29739 -- Otherwise the constituent is illegal
29741 else
29742 SPARK_Msg_NE
29743 ("constituent & must denote object or state",
29744 Constit, Constit_Id);
29745 end if;
29747 -- The constituent is illegal
29749 else
29750 SPARK_Msg_N ("malformed constituent", Constit);
29751 end if;
29752 end if;
29753 end Analyze_Constituent;
29755 -----------------------------
29756 -- Check_External_Property --
29757 -----------------------------
29759 procedure Check_External_Property
29760 (Prop_Nam : Name_Id;
29761 Enabled : Boolean;
29762 Constit : Entity_Id)
29764 begin
29765 -- The property is missing in the declaration of the state, but
29766 -- a constituent is introducing it in the state refinement
29767 -- (SPARK RM 7.2.8(2)).
29769 if not Enabled and then Present (Constit) then
29770 Error_Msg_Name_1 := Prop_Nam;
29771 Error_Msg_Name_2 := Chars (State_Id);
29772 SPARK_Msg_NE
29773 ("constituent & introduces external property % in refinement "
29774 & "of state %", State, Constit);
29776 Error_Msg_Sloc := Sloc (State_Id);
29777 SPARK_Msg_N
29778 ("\property is missing in abstract state declaration #",
29779 State);
29780 end if;
29781 end Check_External_Property;
29783 -----------------
29784 -- Match_State --
29785 -----------------
29787 procedure Match_State is
29788 State_Elmt : Elmt_Id;
29790 begin
29791 -- Detect a duplicate refinement of a state (SPARK RM 7.2.2(8))
29793 if Contains (Refined_States_Seen, State_Id) then
29794 SPARK_Msg_NE
29795 ("duplicate refinement of state &", State, State_Id);
29796 return;
29797 end if;
29799 -- Inspect the abstract states defined in the package declaration
29800 -- looking for a match.
29802 State_Elmt := First_Elmt (Available_States);
29803 while Present (State_Elmt) loop
29805 -- A valid abstract state is being refined in the body. Add
29806 -- the state to the list of processed refined states to aid
29807 -- with the detection of duplicate refinements. Remove the
29808 -- state from Available_States to signal that it has already
29809 -- been refined.
29811 if Node (State_Elmt) = State_Id then
29812 Append_New_Elmt (State_Id, Refined_States_Seen);
29813 Remove_Elmt (Available_States, State_Elmt);
29814 return;
29815 end if;
29817 Next_Elmt (State_Elmt);
29818 end loop;
29820 -- If we get here, we are refining a state that is not defined in
29821 -- the package declaration.
29823 Error_Msg_Name_1 := Chars (Spec_Id);
29824 SPARK_Msg_NE
29825 ("cannot refine state, & is not defined in package %",
29826 State, State_Id);
29827 end Match_State;
29829 --------------------------------
29830 -- Report_Unused_Constituents --
29831 --------------------------------
29833 procedure Report_Unused_Constituents (Constits : Elist_Id) is
29834 Constit_Elmt : Elmt_Id;
29835 Constit_Id : Entity_Id;
29836 Posted : Boolean := False;
29838 begin
29839 if Present (Constits) then
29840 Constit_Elmt := First_Elmt (Constits);
29841 while Present (Constit_Elmt) loop
29842 Constit_Id := Node (Constit_Elmt);
29844 -- Generate an error message of the form:
29846 -- state ... has unused Part_Of constituents
29847 -- abstract state ... defined at ...
29848 -- constant ... defined at ...
29849 -- variable ... defined at ...
29851 if not Posted then
29852 Posted := True;
29853 SPARK_Msg_NE
29854 ("state & has unused Part_Of constituents",
29855 State, State_Id);
29856 end if;
29858 Error_Msg_Sloc := Sloc (Constit_Id);
29860 if Ekind (Constit_Id) = E_Abstract_State then
29861 SPARK_Msg_NE
29862 ("\abstract state & defined #", State, Constit_Id);
29864 elsif Ekind (Constit_Id) = E_Constant then
29865 SPARK_Msg_NE
29866 ("\constant & defined #", State, Constit_Id);
29868 else
29869 pragma Assert (Ekind (Constit_Id) = E_Variable);
29870 SPARK_Msg_NE ("\variable & defined #", State, Constit_Id);
29871 end if;
29873 Next_Elmt (Constit_Elmt);
29874 end loop;
29875 end if;
29876 end Report_Unused_Constituents;
29878 -- Local declarations
29880 Body_Ref : Node_Id;
29881 Body_Ref_Elmt : Elmt_Id;
29882 Constit : Node_Id;
29883 Extra_State : Node_Id;
29885 -- Start of processing for Analyze_Refinement_Clause
29887 begin
29888 -- A refinement clause appears as a component association where the
29889 -- sole choice is the state and the expressions are the constituents.
29890 -- This is a syntax error, always report.
29892 if Nkind (Clause) /= N_Component_Association then
29893 Error_Msg_N ("malformed state refinement clause", Clause);
29894 return;
29895 end if;
29897 -- Analyze the state name of a refinement clause
29899 State := First (Choices (Clause));
29901 Analyze (State);
29902 Resolve_State (State);
29904 -- Ensure that the state name denotes a valid abstract state that is
29905 -- defined in the spec of the related package.
29907 if Is_Entity_Name (State) then
29908 State_Id := Entity_Of (State);
29910 -- When the abstract state is undefined, it appears as Any_Id. Do
29911 -- not continue with the analysis of the clause.
29913 if State_Id = Any_Id then
29914 return;
29916 -- Catch any attempts to re-refine a state or refine a state that
29917 -- is not defined in the package declaration.
29919 elsif Ekind (State_Id) = E_Abstract_State then
29920 Match_State;
29922 else
29923 SPARK_Msg_NE ("& must denote abstract state", State, State_Id);
29924 return;
29925 end if;
29927 -- References to a state with visible refinement are illegal.
29928 -- When nested packages are involved, detecting such references is
29929 -- tricky because pragma Refined_State is analyzed later than the
29930 -- offending pragma Depends or Global. References that occur in
29931 -- such nested context are stored in a list. Emit errors for all
29932 -- references found in Body_References (SPARK RM 6.1.4(8)).
29934 if Present (Body_References (State_Id)) then
29935 Body_Ref_Elmt := First_Elmt (Body_References (State_Id));
29936 while Present (Body_Ref_Elmt) loop
29937 Body_Ref := Node (Body_Ref_Elmt);
29939 SPARK_Msg_N ("reference to & not allowed", Body_Ref);
29940 Error_Msg_Sloc := Sloc (State);
29941 SPARK_Msg_N ("\refinement of & is visible#", Body_Ref);
29943 Next_Elmt (Body_Ref_Elmt);
29944 end loop;
29945 end if;
29947 -- The state name is illegal. This is a syntax error, always report.
29949 else
29950 Error_Msg_N ("malformed state name in refinement clause", State);
29951 return;
29952 end if;
29954 -- A refinement clause may only refine one state at a time
29956 Extra_State := Next (State);
29958 if Present (Extra_State) then
29959 SPARK_Msg_N
29960 ("refinement clause cannot cover multiple states", Extra_State);
29961 end if;
29963 -- Replicate the Part_Of constituents of the refined state because
29964 -- the algorithm will consume items.
29966 Part_Of_Constits := New_Copy_Elist (Part_Of_Constituents (State_Id));
29968 -- Analyze all constituents of the refinement. Multiple constituents
29969 -- appear as an aggregate.
29971 Constit := Expression (Clause);
29973 if Nkind (Constit) = N_Aggregate then
29974 if Present (Component_Associations (Constit)) then
29975 SPARK_Msg_N
29976 ("constituents of refinement clause must appear in "
29977 & "positional form", Constit);
29979 else pragma Assert (Present (Expressions (Constit)));
29980 Constit := First (Expressions (Constit));
29981 while Present (Constit) loop
29982 Analyze_Constituent (Constit);
29983 Next (Constit);
29984 end loop;
29985 end if;
29987 -- Various forms of a single constituent. Note that these may include
29988 -- malformed constituents.
29990 else
29991 Analyze_Constituent (Constit);
29992 end if;
29994 -- Verify that external constituents do not introduce new external
29995 -- property in the state refinement (SPARK RM 7.2.8(2)).
29997 if Is_External_State (State_Id) then
29998 Check_External_Property
29999 (Prop_Nam => Name_Async_Readers,
30000 Enabled => Async_Readers_Enabled (State_Id),
30001 Constit => AR_Constit);
30003 Check_External_Property
30004 (Prop_Nam => Name_Async_Writers,
30005 Enabled => Async_Writers_Enabled (State_Id),
30006 Constit => AW_Constit);
30008 Check_External_Property
30009 (Prop_Nam => Name_Effective_Reads,
30010 Enabled => Effective_Reads_Enabled (State_Id),
30011 Constit => ER_Constit);
30013 Check_External_Property
30014 (Prop_Nam => Name_Effective_Writes,
30015 Enabled => Effective_Writes_Enabled (State_Id),
30016 Constit => EW_Constit);
30018 -- When a refined state is not external, it should not have external
30019 -- constituents (SPARK RM 7.2.8(1)).
30021 elsif External_Constit_Seen then
30022 SPARK_Msg_NE
30023 ("non-external state & cannot contain external constituents in "
30024 & "refinement", State, State_Id);
30025 end if;
30027 -- Ensure that all Part_Of candidate constituents have been mentioned
30028 -- in the refinement clause.
30030 Report_Unused_Constituents (Part_Of_Constits);
30032 -- Avoid a cascading error reporting a missing refinement by adding a
30033 -- dummy constituent.
30035 if No (Refinement_Constituents (State_Id)) then
30036 Set_Refinement_Constituents (State_Id, New_Elmt_List (Any_Id));
30037 end if;
30039 -- At this point the refinement might be dummy, but must be
30040 -- well-formed, to prevent cascaded errors.
30042 pragma Assert (Has_Null_Refinement (State_Id)
30044 Has_Non_Null_Refinement (State_Id));
30045 end Analyze_Refinement_Clause;
30047 -----------------------------
30048 -- Report_Unrefined_States --
30049 -----------------------------
30051 procedure Report_Unrefined_States (States : Elist_Id) is
30052 State_Elmt : Elmt_Id;
30054 begin
30055 if Present (States) then
30056 State_Elmt := First_Elmt (States);
30057 while Present (State_Elmt) loop
30058 SPARK_Msg_N
30059 ("abstract state & must be refined", Node (State_Elmt));
30061 Next_Elmt (State_Elmt);
30062 end loop;
30063 end if;
30064 end Report_Unrefined_States;
30066 -- Local declarations
30068 Clauses : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
30069 Clause : Node_Id;
30071 -- Start of processing for Analyze_Refined_State_In_Decl_Part
30073 begin
30074 -- Do not analyze the pragma multiple times
30076 if Is_Analyzed_Pragma (N) then
30077 return;
30078 end if;
30080 -- Save the scenario for examination by the ABE Processing phase
30082 Record_Elaboration_Scenario (N);
30084 -- Replicate the abstract states declared by the package because the
30085 -- matching algorithm will consume states.
30087 Available_States := New_Copy_Elist (Abstract_States (Spec_Id));
30089 -- Gather all abstract states and objects declared in the visible
30090 -- state space of the package body. These items must be utilized as
30091 -- constituents in a state refinement.
30093 Body_States := Collect_Body_States (Body_Id);
30095 -- Multiple non-null state refinements appear as an aggregate
30097 if Nkind (Clauses) = N_Aggregate then
30098 if Present (Expressions (Clauses)) then
30099 SPARK_Msg_N
30100 ("state refinements must appear as component associations",
30101 Clauses);
30103 else pragma Assert (Present (Component_Associations (Clauses)));
30104 Clause := First (Component_Associations (Clauses));
30105 while Present (Clause) loop
30106 Analyze_Refinement_Clause (Clause);
30107 Next (Clause);
30108 end loop;
30109 end if;
30111 -- Various forms of a single state refinement. Note that these may
30112 -- include malformed refinements.
30114 else
30115 Analyze_Refinement_Clause (Clauses);
30116 end if;
30118 -- List all abstract states that were left unrefined
30120 Report_Unrefined_States (Available_States);
30122 Set_Is_Analyzed_Pragma (N);
30123 end Analyze_Refined_State_In_Decl_Part;
30125 ---------------------------------------------
30126 -- Analyze_Subprogram_Variant_In_Decl_Part --
30127 ---------------------------------------------
30129 -- WARNING: This routine manages Ghost regions. Return statements must be
30130 -- replaced by gotos which jump to the end of the routine and restore the
30131 -- Ghost mode.
30133 procedure Analyze_Subprogram_Variant_In_Decl_Part
30134 (N : Node_Id;
30135 Freeze_Id : Entity_Id := Empty)
30137 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
30138 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
30140 procedure Analyze_Variant (Variant : Node_Id);
30141 -- Verify the legality of a single contract case
30143 ---------------------
30144 -- Analyze_Variant --
30145 ---------------------
30147 procedure Analyze_Variant (Variant : Node_Id) is
30148 Direction : Node_Id;
30149 Expr : Node_Id;
30150 Errors : Nat;
30151 Extra_Direction : Node_Id;
30153 begin
30154 if Nkind (Variant) /= N_Component_Association then
30155 Error_Msg_N ("wrong syntax in subprogram variant", Variant);
30156 return;
30157 end if;
30159 Direction := First (Choices (Variant));
30160 Expr := Expression (Variant);
30162 -- Each variant must have exactly one direction
30164 Extra_Direction := Next (Direction);
30166 if Present (Extra_Direction) then
30167 Error_Msg_N
30168 ("subprogram variant case must have exactly one direction",
30169 Extra_Direction);
30170 end if;
30172 -- Check placement of OTHERS if available (SPARK RM 6.1.3(1))
30174 if Nkind (Direction) = N_Identifier then
30175 if Chars (Direction) not in Name_Decreases
30176 | Name_Increases
30177 | Name_Structural
30178 then
30179 Error_Msg_N ("wrong direction", Direction);
30180 end if;
30181 else
30182 Error_Msg_N ("wrong syntax", Direction);
30183 end if;
30185 Errors := Serious_Errors_Detected;
30187 -- Preanalyze_Assert_Expression, but without enforcing any of the two
30188 -- acceptable types.
30190 Preanalyze_Assert_Expression (Expr);
30192 -- Expression of a discrete type is allowed. Nothing more to check
30193 -- for structural variants.
30195 if Is_Discrete_Type (Etype (Expr))
30196 or else Chars (Direction) = Name_Structural
30197 then
30198 null;
30200 -- Expression of a Big_Integer type (or its ghost variant) is only
30201 -- allowed in Decreases clause.
30203 elsif
30204 Is_RTE (Base_Type (Etype (Expr)), RE_Big_Integer)
30205 or else
30206 Is_RTE (Base_Type (Etype (Expr)), RO_GH_Big_Integer)
30207 then
30208 if Chars (Direction) = Name_Increases then
30209 Error_Msg_N
30210 ("Subprogram_Variant with Big_Integer can only decrease",
30211 Expr);
30212 end if;
30214 -- Expression of other types is not allowed
30216 else
30217 Error_Msg_N ("expected a discrete or Big_Integer type", Expr);
30218 end if;
30220 -- Emit a clarification message when the variant expression
30221 -- contains at least one undefined reference, possibly due
30222 -- to contract freezing.
30224 if Errors /= Serious_Errors_Detected
30225 and then Present (Freeze_Id)
30226 and then Has_Undefined_Reference (Expr)
30227 then
30228 Contract_Freeze_Error (Spec_Id, Freeze_Id);
30229 end if;
30230 end Analyze_Variant;
30232 -- Local variables
30234 Variants : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
30236 Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
30237 Saved_IGR : constant Node_Id := Ignored_Ghost_Region;
30238 -- Save the Ghost-related attributes to restore on exit
30240 Variant : Node_Id;
30241 Restore_Scope : Boolean := False;
30243 -- Start of processing for Analyze_Subprogram_Variant_In_Decl_Part
30245 begin
30246 -- Do not analyze the pragma multiple times
30248 if Is_Analyzed_Pragma (N) then
30249 return;
30250 end if;
30252 -- Set the Ghost mode in effect from the pragma. Due to the delayed
30253 -- analysis of the pragma, the Ghost mode at point of declaration and
30254 -- point of analysis may not necessarily be the same. Use the mode in
30255 -- effect at the point of declaration.
30257 Set_Ghost_Mode (N);
30259 -- Single and multiple contract cases must appear in aggregate form. If
30260 -- this is not the case, then either the parser of the analysis of the
30261 -- pragma failed to produce an aggregate, e.g. when the contract is
30262 -- "null" or a "(null record)".
30264 pragma Assert
30265 (if Nkind (Variants) = N_Aggregate
30266 then Null_Record_Present (Variants)
30267 xor (Present (Component_Associations (Variants))
30269 Present (Expressions (Variants)))
30270 else Nkind (Variants) = N_Null);
30272 -- Only "change_direction => discrete_expression" clauses are allowed
30274 if Nkind (Variants) = N_Aggregate
30275 and then Present (Component_Associations (Variants))
30276 and then No (Expressions (Variants))
30277 then
30279 -- Check that the expression is a proper aggregate (no parentheses)
30281 if Paren_Count (Variants) /= 0 then
30282 Error_Msg_F -- CODEFIX
30283 ("redundant parentheses", Variants);
30284 end if;
30286 -- Ensure that the formal parameters are visible when analyzing all
30287 -- clauses. This falls out of the general rule of aspects pertaining
30288 -- to subprogram declarations.
30290 if not In_Open_Scopes (Spec_Id) then
30291 Restore_Scope := True;
30292 Push_Scope (Spec_Id);
30294 if Is_Generic_Subprogram (Spec_Id) then
30295 Install_Generic_Formals (Spec_Id);
30296 else
30297 Install_Formals (Spec_Id);
30298 end if;
30299 end if;
30301 Variant := First (Component_Associations (Variants));
30302 while Present (Variant) loop
30303 Analyze_Variant (Variant);
30305 if Chars (First (Choices (Variant))) = Name_Structural
30306 and then List_Length (Component_Associations (Variants)) > 1
30307 then
30308 Error_Msg_N
30309 ("Structural variant shall be the only variant", Variant);
30310 end if;
30312 Next (Variant);
30313 end loop;
30315 if Restore_Scope then
30316 End_Scope;
30317 end if;
30319 -- Currently it is not possible to inline Subprogram_Variant on a
30320 -- subprogram subject to pragma Inline_Always.
30322 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
30324 -- Otherwise the pragma is illegal
30326 else
30327 Error_Msg_N ("wrong syntax for subprogram variant", N);
30328 end if;
30330 Set_Is_Analyzed_Pragma (N);
30332 Restore_Ghost_Region (Saved_GM, Saved_IGR);
30333 end Analyze_Subprogram_Variant_In_Decl_Part;
30335 ------------------------------------
30336 -- Analyze_Test_Case_In_Decl_Part --
30337 ------------------------------------
30339 procedure Analyze_Test_Case_In_Decl_Part (N : Node_Id) is
30340 Subp_Decl : constant Node_Id := Find_Related_Declaration_Or_Body (N);
30341 Spec_Id : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
30343 procedure Preanalyze_Test_Case_Arg (Arg_Nam : Name_Id);
30344 -- Preanalyze one of the optional arguments "Requires" or "Ensures"
30345 -- denoted by Arg_Nam.
30347 ------------------------------
30348 -- Preanalyze_Test_Case_Arg --
30349 ------------------------------
30351 procedure Preanalyze_Test_Case_Arg (Arg_Nam : Name_Id) is
30352 Arg : Node_Id;
30354 begin
30355 -- Preanalyze the original aspect argument for a generic subprogram
30356 -- to properly capture global references.
30358 if Is_Generic_Subprogram (Spec_Id) then
30359 Arg :=
30360 Test_Case_Arg
30361 (Prag => N,
30362 Arg_Nam => Arg_Nam,
30363 From_Aspect => True);
30365 if Present (Arg) then
30366 Preanalyze_Assert_Expression
30367 (Expression (Arg), Standard_Boolean);
30368 end if;
30369 end if;
30371 Arg := Test_Case_Arg (N, Arg_Nam);
30373 if Present (Arg) then
30374 Preanalyze_Assert_Expression (Expression (Arg), Standard_Boolean);
30375 end if;
30376 end Preanalyze_Test_Case_Arg;
30378 -- Local variables
30380 Restore_Scope : Boolean := False;
30382 -- Start of processing for Analyze_Test_Case_In_Decl_Part
30384 begin
30385 -- Do not analyze the pragma multiple times
30387 if Is_Analyzed_Pragma (N) then
30388 return;
30389 end if;
30391 -- Ensure that the formal parameters are visible when analyzing all
30392 -- clauses. This falls out of the general rule of aspects pertaining
30393 -- to subprogram declarations.
30395 if not In_Open_Scopes (Spec_Id) then
30396 Restore_Scope := True;
30397 Push_Scope (Spec_Id);
30399 if Is_Generic_Subprogram (Spec_Id) then
30400 Install_Generic_Formals (Spec_Id);
30401 else
30402 Install_Formals (Spec_Id);
30403 end if;
30404 end if;
30406 Preanalyze_Test_Case_Arg (Name_Requires);
30407 Preanalyze_Test_Case_Arg (Name_Ensures);
30409 if Restore_Scope then
30410 End_Scope;
30411 end if;
30413 -- Currently it is not possible to inline pre/postconditions on a
30414 -- subprogram subject to pragma Inline_Always.
30416 Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
30418 Set_Is_Analyzed_Pragma (N);
30419 end Analyze_Test_Case_In_Decl_Part;
30421 ----------------
30422 -- Appears_In --
30423 ----------------
30425 function Appears_In (List : Elist_Id; Item_Id : Entity_Id) return Boolean is
30426 Elmt : Elmt_Id;
30427 Id : Entity_Id;
30429 begin
30430 if Present (List) then
30431 Elmt := First_Elmt (List);
30432 while Present (Elmt) loop
30433 if Nkind (Node (Elmt)) = N_Defining_Identifier then
30434 Id := Node (Elmt);
30435 else
30436 Id := Entity_Of (Node (Elmt));
30437 end if;
30439 if Id = Item_Id then
30440 return True;
30441 end if;
30443 Next_Elmt (Elmt);
30444 end loop;
30445 end if;
30447 return False;
30448 end Appears_In;
30450 -----------------------------------
30451 -- Build_Pragma_Check_Equivalent --
30452 -----------------------------------
30454 function Build_Pragma_Check_Equivalent
30455 (Prag : Node_Id;
30456 Subp_Id : Entity_Id := Empty;
30457 Inher_Id : Entity_Id := Empty;
30458 Keep_Pragma_Id : Boolean := False) return Node_Id
30460 function Suppress_Reference (N : Node_Id) return Traverse_Result;
30461 -- Detect whether node N references a formal parameter subject to
30462 -- pragma Unreferenced. If this is the case, set Comes_From_Source
30463 -- to False to suppress the generation of a reference when analyzing
30464 -- N later on.
30466 ------------------------
30467 -- Suppress_Reference --
30468 ------------------------
30470 function Suppress_Reference (N : Node_Id) return Traverse_Result is
30471 Formal : Entity_Id;
30473 begin
30474 if Is_Entity_Name (N) and then Present (Entity (N)) then
30475 Formal := Entity (N);
30477 -- The formal parameter is subject to pragma Unreferenced. Prevent
30478 -- the generation of references by resetting the Comes_From_Source
30479 -- flag.
30481 if Is_Formal (Formal)
30482 and then Has_Pragma_Unreferenced (Formal)
30483 then
30484 Set_Comes_From_Source (N, False);
30485 end if;
30486 end if;
30488 return OK;
30489 end Suppress_Reference;
30491 procedure Suppress_References is
30492 new Traverse_Proc (Suppress_Reference);
30494 -- Local variables
30496 Loc : constant Source_Ptr := Sloc (Prag);
30497 Prag_Nam : constant Name_Id := Pragma_Name (Prag);
30498 Check_Prag : Node_Id;
30499 Msg_Arg : Node_Id;
30500 Nam : Name_Id;
30502 -- Start of processing for Build_Pragma_Check_Equivalent
30504 begin
30505 -- When the pre- or postcondition is inherited, map the formals of the
30506 -- inherited subprogram to those of the current subprogram. In addition,
30507 -- map primitive operations of the parent type into the corresponding
30508 -- primitive operations of the descendant.
30510 if Present (Inher_Id) then
30511 pragma Assert (Present (Subp_Id));
30513 Update_Primitives_Mapping (Inher_Id, Subp_Id);
30515 -- Use generic machinery to copy inherited pragma, as if it were an
30516 -- instantiation, resetting source locations appropriately, so that
30517 -- expressions inside the inherited pragma use chained locations.
30518 -- This is used in particular in GNATprove to locate precisely
30519 -- messages on a given inherited pragma.
30521 Set_Copied_Sloc_For_Inherited_Pragma
30522 (Unit_Declaration_Node (Subp_Id), Inher_Id);
30523 Check_Prag := New_Copy_Tree (Source => Prag);
30525 -- Build the inherited class-wide condition
30527 Build_Class_Wide_Expression
30528 (Pragma_Or_Expr => Check_Prag,
30529 Subp => Subp_Id,
30530 Par_Subp => Inher_Id,
30531 Adjust_Sloc => True);
30533 -- If not an inherited condition simply copy the original pragma
30535 else
30536 Check_Prag := New_Copy_Tree (Source => Prag);
30537 end if;
30539 -- Mark the pragma as being internally generated and reset the Analyzed
30540 -- flag.
30542 Set_Analyzed (Check_Prag, False);
30543 Set_Comes_From_Source (Check_Prag, False);
30545 -- The tree of the original pragma may contain references to the
30546 -- formal parameters of the related subprogram. At the same time
30547 -- the corresponding body may mark the formals as unreferenced:
30549 -- procedure Proc (Formal : ...)
30550 -- with Pre => Formal ...;
30552 -- procedure Proc (Formal : ...) is
30553 -- pragma Unreferenced (Formal);
30554 -- ...
30556 -- This creates problems because all pragma Check equivalents are
30557 -- analyzed at the end of the body declarations. Since all source
30558 -- references have already been accounted for, reset any references
30559 -- to such formals in the generated pragma Check equivalent.
30561 Suppress_References (Check_Prag);
30563 if Present (Corresponding_Aspect (Prag)) then
30564 Nam := Chars (Identifier (Corresponding_Aspect (Prag)));
30565 else
30566 Nam := Prag_Nam;
30567 end if;
30569 -- Unless Keep_Pragma_Id is True in order to keep the identifier of
30570 -- the copied pragma in the newly created pragma, convert the copy into
30571 -- pragma Check by correcting the name and adding a check_kind argument.
30573 if not Keep_Pragma_Id then
30574 Set_Class_Present (Check_Prag, False);
30576 Set_Pragma_Identifier
30577 (Check_Prag, Make_Identifier (Loc, Name_Check));
30579 Prepend_To (Pragma_Argument_Associations (Check_Prag),
30580 Make_Pragma_Argument_Association (Loc,
30581 Expression => Make_Identifier (Loc, Nam)));
30582 end if;
30584 -- Update the error message when the pragma is inherited
30586 if Present (Inher_Id) then
30587 Msg_Arg := Last (Pragma_Argument_Associations (Check_Prag));
30589 if Chars (Msg_Arg) = Name_Message then
30590 String_To_Name_Buffer (Strval (Expression (Msg_Arg)));
30592 -- Insert "inherited" to improve the error message
30594 if Name_Buffer (1 .. 8) = "failed p" then
30595 Insert_Str_In_Name_Buffer ("inherited ", 8);
30596 Set_Strval (Expression (Msg_Arg), String_From_Name_Buffer);
30597 end if;
30598 end if;
30599 end if;
30601 return Check_Prag;
30602 end Build_Pragma_Check_Equivalent;
30604 -----------------------------
30605 -- Check_Applicable_Policy --
30606 -----------------------------
30608 procedure Check_Applicable_Policy (N : Node_Id) is
30609 PP : Node_Id;
30610 Policy : Name_Id;
30612 Ename : constant Name_Id := Original_Aspect_Pragma_Name (N);
30614 begin
30615 -- No effect if not valid assertion kind name
30617 if not Is_Valid_Assertion_Kind (Ename) then
30618 return;
30619 end if;
30621 -- Loop through entries in check policy list
30623 PP := Opt.Check_Policy_List;
30624 while Present (PP) loop
30625 declare
30626 PPA : constant List_Id := Pragma_Argument_Associations (PP);
30627 Pnm : constant Name_Id := Chars (Get_Pragma_Arg (First (PPA)));
30629 begin
30630 if Ename = Pnm
30631 or else Pnm = Name_Assertion
30632 or else (Pnm = Name_Statement_Assertions
30633 and then Ename in Name_Assert
30634 | Name_Assert_And_Cut
30635 | Name_Assume
30636 | Name_Loop_Invariant
30637 | Name_Loop_Variant)
30638 then
30639 Policy := Chars (Get_Pragma_Arg (Last (PPA)));
30641 case Policy is
30642 when Name_Ignore
30643 | Name_Off
30645 -- In CodePeer mode and GNATprove mode, we need to
30646 -- consider all assertions, unless they are disabled.
30647 -- Force Is_Checked on ignored assertions, in particular
30648 -- because transformations of the AST may depend on
30649 -- assertions being checked (e.g. the translation of
30650 -- attribute 'Loop_Entry).
30652 if CodePeer_Mode or GNATprove_Mode then
30653 Set_Is_Checked (N, True);
30654 Set_Is_Ignored (N, False);
30655 else
30656 Set_Is_Checked (N, False);
30657 Set_Is_Ignored (N, True);
30658 end if;
30660 when Name_Check
30661 | Name_On
30663 Set_Is_Checked (N, True);
30664 Set_Is_Ignored (N, False);
30666 when Name_Disable =>
30667 Set_Is_Ignored (N, True);
30668 Set_Is_Checked (N, False);
30669 Set_Is_Disabled (N, True);
30671 -- That should be exhaustive, the null here is a defence
30672 -- against a malformed tree from previous errors.
30674 when others =>
30675 null;
30676 end case;
30678 return;
30679 end if;
30681 PP := Next_Pragma (PP);
30682 end;
30683 end loop;
30685 -- If there are no specific entries that matched, then we let the
30686 -- setting of assertions govern. Note that this provides the needed
30687 -- compatibility with the RM for the cases of assertion, invariant,
30688 -- precondition, predicate, and postcondition. Note also that
30689 -- Assertions_Enabled is forced in CodePeer mode and GNATprove mode.
30691 if Assertions_Enabled then
30692 Set_Is_Checked (N, True);
30693 Set_Is_Ignored (N, False);
30694 else
30695 Set_Is_Checked (N, False);
30696 Set_Is_Ignored (N, True);
30697 end if;
30698 end Check_Applicable_Policy;
30700 -------------------------------
30701 -- Check_External_Properties --
30702 -------------------------------
30704 procedure Check_External_Properties
30705 (Item : Node_Id;
30706 AR : Boolean;
30707 AW : Boolean;
30708 ER : Boolean;
30709 EW : Boolean)
30711 type Properties is array (Positive range 1 .. 4) of Boolean;
30712 type Combinations is array (Positive range <>) of Properties;
30713 -- Arrays of Async_Readers, Async_Writers, Effective_Writes and
30714 -- Effective_Reads properties and their combinations, respectively.
30716 Specified : constant Properties := (AR, AW, EW, ER);
30717 -- External properties, as given by the Item pragma
30719 Allowed : constant Combinations :=
30720 (1 => (True, False, True, False),
30721 2 => (False, True, False, True),
30722 3 => (True, False, False, False),
30723 4 => (False, True, False, False),
30724 5 => (True, True, True, False),
30725 6 => (True, True, False, True),
30726 7 => (True, True, False, False),
30727 8 => (True, True, True, True));
30728 -- Allowed combinations, as listed in the SPARK RM 7.1.2(6) table
30730 begin
30731 -- Check if the specified properties match any of the allowed
30732 -- combination; if not, then emit an error.
30734 for J in Allowed'Range loop
30735 if Specified = Allowed (J) then
30736 return;
30737 end if;
30738 end loop;
30740 SPARK_Msg_N
30741 ("illegal combination of external properties (SPARK RM 7.1.2(6))",
30742 Item);
30743 end Check_External_Properties;
30745 ----------------
30746 -- Check_Kind --
30747 ----------------
30749 function Check_Kind (Nam : Name_Id) return Name_Id is
30750 PP : Node_Id;
30752 begin
30753 -- Loop through entries in check policy list
30755 PP := Opt.Check_Policy_List;
30756 while Present (PP) loop
30757 declare
30758 PPA : constant List_Id := Pragma_Argument_Associations (PP);
30759 Pnm : constant Name_Id := Chars (Get_Pragma_Arg (First (PPA)));
30761 begin
30762 if Nam = Pnm
30763 or else (Pnm = Name_Assertion
30764 and then Is_Valid_Assertion_Kind (Nam))
30765 or else (Pnm = Name_Statement_Assertions
30766 and then Nam in Name_Assert
30767 | Name_Assert_And_Cut
30768 | Name_Assume
30769 | Name_Loop_Invariant
30770 | Name_Loop_Variant)
30771 then
30772 case Chars (Get_Pragma_Arg (Last (PPA))) is
30773 when Name_Check
30774 | Name_On
30776 return Name_Check;
30778 when Name_Ignore
30779 | Name_Off
30781 return Name_Ignore;
30783 when Name_Disable =>
30784 return Name_Disable;
30786 when others =>
30787 raise Program_Error;
30788 end case;
30790 else
30791 PP := Next_Pragma (PP);
30792 end if;
30793 end;
30794 end loop;
30796 -- If there are no specific entries that matched, then we let the
30797 -- setting of assertions govern. Note that this provides the needed
30798 -- compatibility with the RM for the cases of assertion, invariant,
30799 -- precondition, predicate, and postcondition.
30801 if Assertions_Enabled then
30802 return Name_Check;
30803 else
30804 return Name_Ignore;
30805 end if;
30806 end Check_Kind;
30808 ---------------------------
30809 -- Check_Missing_Part_Of --
30810 ---------------------------
30812 procedure Check_Missing_Part_Of (Item_Id : Entity_Id) is
30813 function Has_Visible_State (Pack_Id : Entity_Id) return Boolean;
30814 -- Determine whether a package denoted by Pack_Id declares at least one
30815 -- visible state.
30817 -----------------------
30818 -- Has_Visible_State --
30819 -----------------------
30821 function Has_Visible_State (Pack_Id : Entity_Id) return Boolean is
30822 Item_Id : Entity_Id;
30824 begin
30825 -- Traverse the entity chain of the package trying to find at least
30826 -- one visible abstract state, variable or a package [instantiation]
30827 -- that declares a visible state.
30829 Item_Id := First_Entity (Pack_Id);
30830 while Present (Item_Id)
30831 and then not In_Private_Part (Item_Id)
30832 loop
30833 -- Do not consider internally generated items
30835 if not Comes_From_Source (Item_Id) then
30836 null;
30838 -- Do not consider generic formals or their corresponding actuals
30839 -- because they are not part of a visible state. Note that both
30840 -- entities are marked as hidden.
30842 elsif Is_Hidden (Item_Id) then
30843 null;
30845 -- A visible state has been found. Note that constants are not
30846 -- considered here because it is not possible to determine whether
30847 -- they depend on variable input. This check is left to the SPARK
30848 -- prover.
30850 elsif Ekind (Item_Id) in E_Abstract_State | E_Variable then
30851 return True;
30853 -- Recursively peek into nested packages and instantiations
30855 elsif Ekind (Item_Id) = E_Package
30856 and then Has_Visible_State (Item_Id)
30857 then
30858 return True;
30859 end if;
30861 Next_Entity (Item_Id);
30862 end loop;
30864 return False;
30865 end Has_Visible_State;
30867 -- Local variables
30869 Pack_Id : Entity_Id;
30870 Placement : State_Space_Kind;
30872 -- Start of processing for Check_Missing_Part_Of
30874 begin
30875 -- Do not consider abstract states, variables or package instantiations
30876 -- coming from an instance as those always inherit the Part_Of indicator
30877 -- of the instance itself.
30879 if In_Instance then
30880 return;
30882 -- Do not consider internally generated entities as these can never
30883 -- have a Part_Of indicator.
30885 elsif not Comes_From_Source (Item_Id) then
30886 return;
30888 -- Perform these checks only when SPARK_Mode is enabled as they will
30889 -- interfere with standard Ada rules and produce false positives.
30891 elsif SPARK_Mode /= On then
30892 return;
30894 -- Do not consider constants, because the compiler cannot accurately
30895 -- determine whether they have variable input (SPARK RM 7.1.1(2)) and
30896 -- act as a hidden state of a package.
30898 elsif Ekind (Item_Id) = E_Constant then
30899 return;
30900 end if;
30902 -- Find where the abstract state, variable or package instantiation
30903 -- lives with respect to the state space.
30905 Find_Placement_In_State_Space
30906 (Item_Id => Item_Id,
30907 Placement => Placement,
30908 Pack_Id => Pack_Id);
30910 -- Items that appear in a non-package construct (subprogram, block, etc)
30911 -- do not require a Part_Of indicator because they can never act as a
30912 -- hidden state.
30914 if Placement = Not_In_Package then
30915 null;
30917 -- An item declared in the body state space of a package always act as a
30918 -- constituent and does not need explicit Part_Of indicator.
30920 elsif Placement = Body_State_Space then
30921 null;
30923 -- In general an item declared in the visible state space of a package
30924 -- does not require a Part_Of indicator. The only exception is when the
30925 -- related package is a nongeneric private child unit, in which case
30926 -- Part_Of must denote a state in the parent unit or in one of its
30927 -- descendants.
30929 elsif Placement = Visible_State_Space then
30930 if Is_Child_Unit (Pack_Id)
30931 and then not Is_Generic_Unit (Pack_Id)
30932 and then Is_Private_Descendant (Pack_Id)
30933 then
30934 -- A package instantiation does not need a Part_Of indicator when
30935 -- the related generic template has no visible state.
30937 if Ekind (Item_Id) = E_Package
30938 and then Is_Generic_Instance (Item_Id)
30939 and then not Has_Visible_State (Item_Id)
30940 then
30941 null;
30943 -- All other cases require Part_Of
30945 else
30946 Error_Msg_N
30947 ("indicator Part_Of is required in this context "
30948 & "(SPARK RM 7.2.6(3))", Item_Id);
30949 Error_Msg_Name_1 := Chars (Pack_Id);
30950 Error_Msg_N
30951 ("\& is declared in the visible part of private child "
30952 & "unit %", Item_Id);
30953 end if;
30954 end if;
30956 -- When the item appears in the private state space of a package, it
30957 -- must be a part of some state declared by the said package.
30959 else pragma Assert (Placement = Private_State_Space);
30961 -- The related package does not declare a state, the item cannot act
30962 -- as a Part_Of constituent.
30964 if No (Get_Pragma (Pack_Id, Pragma_Abstract_State)) then
30965 null;
30967 -- A package instantiation does not need a Part_Of indicator when the
30968 -- related generic template has no visible state.
30970 elsif Ekind (Item_Id) = E_Package
30971 and then Is_Generic_Instance (Item_Id)
30972 and then not Has_Visible_State (Item_Id)
30973 then
30974 null;
30976 -- All other cases require Part_Of
30978 else
30979 Error_Msg_Code := GEC_Required_Part_Of;
30980 Error_Msg_N
30981 ("indicator Part_Of is required in this context '[[]']",
30982 Item_Id);
30983 Error_Msg_Name_1 := Chars (Pack_Id);
30984 Error_Msg_N
30985 ("\& is declared in the private part of package %", Item_Id);
30986 end if;
30987 end if;
30988 end Check_Missing_Part_Of;
30990 ---------------------------------------------------
30991 -- Check_Postcondition_Use_In_Inlined_Subprogram --
30992 ---------------------------------------------------
30994 procedure Check_Postcondition_Use_In_Inlined_Subprogram
30995 (Prag : Node_Id;
30996 Spec_Id : Entity_Id)
30998 begin
30999 if Warn_On_Redundant_Constructs
31000 and then Has_Pragma_Inline_Always (Spec_Id)
31001 and then Assertions_Enabled
31002 and then not Back_End_Inlining
31003 then
31004 Error_Msg_Name_1 := Original_Aspect_Pragma_Name (Prag);
31006 if From_Aspect_Specification (Prag) then
31007 Error_Msg_NE
31008 ("aspect % not enforced on inlined subprogram &?r?",
31009 Corresponding_Aspect (Prag), Spec_Id);
31010 else
31011 Error_Msg_NE
31012 ("pragma % not enforced on inlined subprogram &?r?",
31013 Prag, Spec_Id);
31014 end if;
31015 end if;
31016 end Check_Postcondition_Use_In_Inlined_Subprogram;
31018 -------------------------------------
31019 -- Check_State_And_Constituent_Use --
31020 -------------------------------------
31022 procedure Check_State_And_Constituent_Use
31023 (States : Elist_Id;
31024 Constits : Elist_Id;
31025 Context : Node_Id)
31027 Constit_Elmt : Elmt_Id;
31028 Constit_Id : Entity_Id;
31029 State_Id : Entity_Id;
31031 begin
31032 -- Nothing to do if there are no states or constituents
31034 if No (States) or else No (Constits) then
31035 return;
31036 end if;
31038 -- Inspect the list of constituents and try to determine whether its
31039 -- encapsulating state is in list States.
31041 Constit_Elmt := First_Elmt (Constits);
31042 while Present (Constit_Elmt) loop
31043 Constit_Id := Node (Constit_Elmt);
31045 -- Determine whether the constituent is part of an encapsulating
31046 -- state that appears in the same context and if this is the case,
31047 -- emit an error (SPARK RM 7.2.6(7)).
31049 State_Id := Find_Encapsulating_State (States, Constit_Id);
31051 if Present (State_Id) then
31052 Error_Msg_Name_1 := Chars (Constit_Id);
31053 SPARK_Msg_NE
31054 ("cannot mention state & and its constituent % in the same "
31055 & "context", Context, State_Id);
31056 exit;
31057 end if;
31059 Next_Elmt (Constit_Elmt);
31060 end loop;
31061 end Check_State_And_Constituent_Use;
31063 ---------------------------------------------
31064 -- Collect_Inherited_Class_Wide_Conditions --
31065 ---------------------------------------------
31067 procedure Collect_Inherited_Class_Wide_Conditions (Subp : Entity_Id) is
31068 Parent_Subp : constant Entity_Id :=
31069 Ultimate_Alias (Overridden_Operation (Subp));
31070 -- The Overridden_Operation may itself be inherited and as such have no
31071 -- explicit contract.
31073 Prags : constant Node_Id := Contract (Parent_Subp);
31074 In_Spec_Expr : Boolean := In_Spec_Expression;
31075 Installed : Boolean;
31076 Prag : Node_Id;
31077 New_Prag : Node_Id;
31079 begin
31080 Installed := False;
31082 -- Iterate over the contract of the overridden subprogram to find all
31083 -- inherited class-wide pre- and postconditions.
31085 if Present (Prags) then
31086 Prag := Pre_Post_Conditions (Prags);
31088 while Present (Prag) loop
31089 if Pragma_Name_Unmapped (Prag)
31090 in Name_Precondition | Name_Postcondition
31091 and then Class_Present (Prag)
31092 then
31093 -- The generated pragma must be analyzed in the context of
31094 -- the subprogram, to make its formals visible. In addition,
31095 -- we must inhibit freezing and full analysis because the
31096 -- controlling type of the subprogram is not frozen yet, and
31097 -- may have further primitives.
31099 if not Installed then
31100 Installed := True;
31101 Push_Scope (Subp);
31102 Install_Formals (Subp);
31103 In_Spec_Expr := In_Spec_Expression;
31104 In_Spec_Expression := True;
31105 end if;
31107 New_Prag :=
31108 Build_Pragma_Check_Equivalent
31109 (Prag, Subp, Parent_Subp, Keep_Pragma_Id => True);
31111 Insert_After (Unit_Declaration_Node (Subp), New_Prag);
31112 Preanalyze (New_Prag);
31114 -- Prevent further analysis in subsequent processing of the
31115 -- current list of declarations
31117 Set_Analyzed (New_Prag);
31118 end if;
31120 Prag := Next_Pragma (Prag);
31121 end loop;
31123 if Installed then
31124 In_Spec_Expression := In_Spec_Expr;
31125 End_Scope;
31126 end if;
31127 end if;
31128 end Collect_Inherited_Class_Wide_Conditions;
31130 ---------------------------------------
31131 -- Collect_Subprogram_Inputs_Outputs --
31132 ---------------------------------------
31134 procedure Collect_Subprogram_Inputs_Outputs
31135 (Subp_Id : Entity_Id;
31136 Synthesize : Boolean := False;
31137 Subp_Inputs : in out Elist_Id;
31138 Subp_Outputs : in out Elist_Id;
31139 Global_Seen : out Boolean)
31141 procedure Collect_Dependency_Clause (Clause : Node_Id);
31142 -- Collect all relevant items from a dependency clause
31144 procedure Collect_Global_List
31145 (List : Node_Id;
31146 Mode : Name_Id := Name_Input);
31147 -- Collect all relevant items from a global list
31149 -------------------------------
31150 -- Collect_Dependency_Clause --
31151 -------------------------------
31153 procedure Collect_Dependency_Clause (Clause : Node_Id) is
31154 procedure Collect_Dependency_Item
31155 (Item : Node_Id;
31156 Is_Input : Boolean);
31157 -- Add an item to the proper subprogram input or output collection
31159 -----------------------------
31160 -- Collect_Dependency_Item --
31161 -----------------------------
31163 procedure Collect_Dependency_Item
31164 (Item : Node_Id;
31165 Is_Input : Boolean)
31167 Extra : Node_Id;
31169 begin
31170 -- Nothing to collect when the item is null
31172 if Nkind (Item) = N_Null then
31173 null;
31175 -- Ditto for attribute 'Result
31177 elsif Is_Attribute_Result (Item) then
31178 null;
31180 -- Multiple items appear as an aggregate
31182 elsif Nkind (Item) = N_Aggregate then
31183 Extra := First (Expressions (Item));
31184 while Present (Extra) loop
31185 Collect_Dependency_Item (Extra, Is_Input);
31186 Next (Extra);
31187 end loop;
31189 -- Otherwise this is a solitary item
31191 else
31192 if Is_Input then
31193 Append_New_Elmt (Item, Subp_Inputs);
31194 else
31195 Append_New_Elmt (Item, Subp_Outputs);
31196 end if;
31197 end if;
31198 end Collect_Dependency_Item;
31200 -- Start of processing for Collect_Dependency_Clause
31202 begin
31203 if Nkind (Clause) = N_Null then
31204 null;
31206 -- A dependency clause appears as component association
31208 elsif Nkind (Clause) = N_Component_Association then
31209 Collect_Dependency_Item
31210 (Item => Expression (Clause),
31211 Is_Input => True);
31213 Collect_Dependency_Item
31214 (Item => First (Choices (Clause)),
31215 Is_Input => False);
31217 -- To accommodate partial decoration of disabled SPARK features, this
31218 -- routine may be called with illegal input. If this is the case, do
31219 -- not raise Program_Error.
31221 else
31222 null;
31223 end if;
31224 end Collect_Dependency_Clause;
31226 -------------------------
31227 -- Collect_Global_List --
31228 -------------------------
31230 procedure Collect_Global_List
31231 (List : Node_Id;
31232 Mode : Name_Id := Name_Input)
31234 procedure Collect_Global_Item (Item : Node_Id; Mode : Name_Id);
31235 -- Add an item to the proper subprogram input or output collection
31237 -------------------------
31238 -- Collect_Global_Item --
31239 -------------------------
31241 procedure Collect_Global_Item (Item : Node_Id; Mode : Name_Id) is
31242 begin
31243 if Mode in Name_In_Out | Name_Input then
31244 Append_New_Elmt (Item, Subp_Inputs);
31245 end if;
31247 if Mode in Name_In_Out | Name_Output then
31248 Append_New_Elmt (Item, Subp_Outputs);
31249 end if;
31250 end Collect_Global_Item;
31252 -- Local variables
31254 Assoc : Node_Id;
31255 Item : Node_Id;
31257 -- Start of processing for Collect_Global_List
31259 begin
31260 if Nkind (List) = N_Null then
31261 null;
31263 -- Single global item declaration
31265 elsif Nkind (List) in N_Expanded_Name
31266 | N_Identifier
31267 | N_Selected_Component
31268 then
31269 Collect_Global_Item (List, Mode);
31271 -- Simple global list or moded global list declaration
31273 elsif Nkind (List) = N_Aggregate then
31274 if Present (Expressions (List)) then
31275 Item := First (Expressions (List));
31276 while Present (Item) loop
31277 Collect_Global_Item (Item, Mode);
31278 Next (Item);
31279 end loop;
31281 else
31282 Assoc := First (Component_Associations (List));
31283 while Present (Assoc) loop
31284 Collect_Global_List
31285 (List => Expression (Assoc),
31286 Mode => Chars (First (Choices (Assoc))));
31287 Next (Assoc);
31288 end loop;
31289 end if;
31291 -- To accommodate partial decoration of disabled SPARK features, this
31292 -- routine may be called with illegal input. If this is the case, do
31293 -- not raise Program_Error.
31295 else
31296 null;
31297 end if;
31298 end Collect_Global_List;
31300 -- Local variables
31302 Clause : Node_Id;
31303 Clauses : Node_Id;
31304 Depends : Node_Id;
31305 Formal : Entity_Id;
31306 Global : Node_Id;
31307 Spec_Id : Entity_Id := Empty;
31308 Subp_Decl : Node_Id;
31309 Typ : Entity_Id;
31311 -- Start of processing for Collect_Subprogram_Inputs_Outputs
31313 begin
31314 Global_Seen := False;
31316 -- Process all formal parameters of entries, [generic] subprograms, and
31317 -- their bodies.
31319 if Ekind (Subp_Id) in E_Entry
31320 | E_Entry_Family
31321 | E_Function
31322 | E_Generic_Function
31323 | E_Generic_Procedure
31324 | E_Procedure
31325 | E_Subprogram_Body
31326 then
31327 Subp_Decl := Unit_Declaration_Node (Subp_Id);
31328 Spec_Id := Unique_Defining_Entity (Subp_Decl);
31330 -- Process all formal parameters
31332 Formal := First_Formal (Spec_Id);
31333 while Present (Formal) loop
31334 if Ekind (Formal) in E_In_Out_Parameter | E_In_Parameter then
31335 Append_New_Elmt (Formal, Subp_Inputs);
31336 end if;
31338 if Ekind (Formal) in E_In_Out_Parameter | E_Out_Parameter then
31339 Append_New_Elmt (Formal, Subp_Outputs);
31341 -- OUT parameters can act as inputs when the related type is
31342 -- tagged, unconstrained array, unconstrained record, or record
31343 -- with unconstrained components.
31345 if Ekind (Formal) = E_Out_Parameter
31346 and then Is_Unconstrained_Or_Tagged_Item (Formal)
31347 then
31348 Append_New_Elmt (Formal, Subp_Inputs);
31349 end if;
31350 end if;
31352 -- IN parameters of procedures and protected entries can act as
31353 -- outputs when the related type is access-to-variable.
31355 if Ekind (Formal) = E_In_Parameter
31356 and then Ekind (Spec_Id) not in E_Function
31357 | E_Generic_Function
31358 and then Is_Access_Variable (Etype (Formal))
31359 then
31360 Append_New_Elmt (Formal, Subp_Outputs);
31361 end if;
31363 Next_Formal (Formal);
31364 end loop;
31366 -- Otherwise the input denotes a task type, a task body, or the
31367 -- anonymous object created for a single task type.
31369 elsif Ekind (Subp_Id) in E_Task_Type | E_Task_Body
31370 or else Is_Single_Task_Object (Subp_Id)
31371 then
31372 Subp_Decl := Declaration_Node (Subp_Id);
31373 Spec_Id := Unique_Defining_Entity (Subp_Decl);
31374 end if;
31376 -- When processing an entry, subprogram or task body, look for pragmas
31377 -- Refined_Depends and Refined_Global as they specify the inputs and
31378 -- outputs.
31380 if Is_Entry_Body (Subp_Id)
31381 or else Ekind (Subp_Id) in E_Subprogram_Body | E_Task_Body
31382 then
31383 Depends := Get_Pragma (Subp_Id, Pragma_Refined_Depends);
31384 Global := Get_Pragma (Subp_Id, Pragma_Refined_Global);
31386 -- Subprogram declaration or stand-alone body case, look for pragmas
31387 -- Depends and Global.
31389 else
31390 Depends := Get_Pragma (Spec_Id, Pragma_Depends);
31391 Global := Get_Pragma (Spec_Id, Pragma_Global);
31392 end if;
31394 -- Pragma [Refined_]Global takes precedence over [Refined_]Depends
31395 -- because it provides finer granularity of inputs and outputs.
31397 if Present (Global) then
31398 Global_Seen := True;
31399 Collect_Global_List (Expression (Get_Argument (Global, Spec_Id)));
31401 -- When the related subprogram lacks pragma [Refined_]Global, fall back
31402 -- to [Refined_]Depends if the caller requests this behavior. Synthesize
31403 -- the inputs and outputs from [Refined_]Depends.
31405 elsif Synthesize and then Present (Depends) then
31406 Clauses := Expression (Get_Argument (Depends, Spec_Id));
31408 -- Multiple dependency clauses appear as an aggregate
31410 if Nkind (Clauses) = N_Aggregate then
31411 Clause := First (Component_Associations (Clauses));
31412 while Present (Clause) loop
31413 Collect_Dependency_Clause (Clause);
31414 Next (Clause);
31415 end loop;
31417 -- Otherwise this is a single dependency clause
31419 else
31420 Collect_Dependency_Clause (Clauses);
31421 end if;
31422 end if;
31424 -- The current instance of a protected type acts as a formal parameter
31425 -- of mode IN for functions and IN OUT for entries and procedures
31426 -- (SPARK RM 6.1.4).
31428 if Ekind (Scope (Spec_Id)) = E_Protected_Type then
31429 Typ := Scope (Spec_Id);
31431 -- Use the anonymous object when the type is single protected
31433 if Is_Single_Concurrent_Type_Declaration (Declaration_Node (Typ)) then
31434 Typ := Anonymous_Object (Typ);
31435 end if;
31437 Append_New_Elmt (Typ, Subp_Inputs);
31439 if Ekind (Spec_Id) in E_Entry | E_Entry_Family | E_Procedure then
31440 Append_New_Elmt (Typ, Subp_Outputs);
31441 end if;
31443 -- The current instance of a task type acts as a formal parameter of
31444 -- mode IN OUT (SPARK RM 6.1.4).
31446 elsif Ekind (Spec_Id) = E_Task_Type then
31447 Typ := Spec_Id;
31449 -- Use the anonymous object when the type is single task
31451 if Is_Single_Concurrent_Type_Declaration (Declaration_Node (Typ)) then
31452 Typ := Anonymous_Object (Typ);
31453 end if;
31455 Append_New_Elmt (Typ, Subp_Inputs);
31456 Append_New_Elmt (Typ, Subp_Outputs);
31458 elsif Is_Single_Task_Object (Spec_Id) then
31459 Append_New_Elmt (Spec_Id, Subp_Inputs);
31460 Append_New_Elmt (Spec_Id, Subp_Outputs);
31461 end if;
31462 end Collect_Subprogram_Inputs_Outputs;
31464 ---------------------------
31465 -- Contract_Freeze_Error --
31466 ---------------------------
31468 procedure Contract_Freeze_Error
31469 (Contract_Id : Entity_Id;
31470 Freeze_Id : Entity_Id)
31472 begin
31473 Error_Msg_Name_1 := Chars (Contract_Id);
31474 Error_Msg_Sloc := Sloc (Freeze_Id);
31476 SPARK_Msg_NE
31477 ("body & declared # freezes the contract of%", Contract_Id, Freeze_Id);
31478 SPARK_Msg_N
31479 ("\all contractual items must be declared before body #", Contract_Id);
31480 end Contract_Freeze_Error;
31482 ---------------------------------
31483 -- Delay_Config_Pragma_Analyze --
31484 ---------------------------------
31486 function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
31487 begin
31488 return Pragma_Name_Unmapped (N)
31489 in Name_Interrupt_State | Name_Priority_Specific_Dispatching;
31490 end Delay_Config_Pragma_Analyze;
31492 -----------------------
31493 -- Duplication_Error --
31494 -----------------------
31496 procedure Duplication_Error (Prag : Node_Id; Prev : Node_Id) is
31497 Prag_From_Asp : constant Boolean := From_Aspect_Specification (Prag);
31498 Prev_From_Asp : constant Boolean := From_Aspect_Specification (Prev);
31500 begin
31501 Error_Msg_Sloc := Sloc (Prev);
31502 Error_Msg_Name_1 := Original_Aspect_Pragma_Name (Prag);
31504 -- Emit a precise message to distinguish between source pragmas and
31505 -- pragmas generated from aspects. The ordering of the two pragmas is
31506 -- the following:
31508 -- Prev -- ok
31509 -- Prag -- duplicate
31511 -- No error is emitted when both pragmas come from aspects because this
31512 -- is already detected by the general aspect analysis mechanism.
31514 if Prag_From_Asp and Prev_From_Asp then
31515 null;
31516 elsif Prag_From_Asp then
31517 Error_Msg_N ("aspect % duplicates pragma declared #", Prag);
31518 elsif Prev_From_Asp then
31519 Error_Msg_N ("pragma % duplicates aspect declared #", Prag);
31520 else
31521 Error_Msg_N ("pragma % duplicates pragma declared #", Prag);
31522 end if;
31523 end Duplication_Error;
31525 ------------------------------
31526 -- Find_Encapsulating_State --
31527 ------------------------------
31529 function Find_Encapsulating_State
31530 (States : Elist_Id;
31531 Constit_Id : Entity_Id) return Entity_Id
31533 State_Id : Entity_Id;
31535 begin
31536 -- Since a constituent may be part of a larger constituent set, climb
31537 -- the encapsulating state chain looking for a state that appears in
31538 -- States.
31540 State_Id := Encapsulating_State (Constit_Id);
31541 while Present (State_Id) loop
31542 if Contains (States, State_Id) then
31543 return State_Id;
31544 end if;
31546 State_Id := Encapsulating_State (State_Id);
31547 end loop;
31549 return Empty;
31550 end Find_Encapsulating_State;
31552 --------------------------
31553 -- Find_Related_Context --
31554 --------------------------
31556 function Find_Related_Context
31557 (Prag : Node_Id;
31558 Do_Checks : Boolean := False) return Node_Id
31560 Stmt : Node_Id;
31562 begin
31563 -- If the pragma comes from an aspect on a compilation unit that is a
31564 -- package instance, then return the original package instantiation
31565 -- node.
31567 if Nkind (Parent (Prag)) = N_Compilation_Unit_Aux then
31568 return
31569 Get_Unit_Instantiation_Node
31570 (Defining_Entity (Unit (Enclosing_Comp_Unit_Node (Prag))));
31571 end if;
31573 Stmt := Prev (Prag);
31574 while Present (Stmt) loop
31576 -- Skip prior pragmas, but check for duplicates
31578 if Nkind (Stmt) = N_Pragma then
31579 if Do_Checks
31580 and then Pragma_Name (Stmt) = Pragma_Name (Prag)
31581 then
31582 Duplication_Error
31583 (Prag => Prag,
31584 Prev => Stmt);
31585 end if;
31587 -- Skip internally generated code
31589 elsif not Comes_From_Source (Stmt)
31590 and then not Comes_From_Source (Original_Node (Stmt))
31591 then
31593 -- The anonymous object created for a single concurrent type is a
31594 -- suitable context.
31596 if Nkind (Stmt) = N_Object_Declaration
31597 and then Is_Single_Concurrent_Object (Defining_Entity (Stmt))
31598 then
31599 return Stmt;
31600 end if;
31602 -- Return the current source construct
31604 else
31605 return Stmt;
31606 end if;
31608 Prev (Stmt);
31609 end loop;
31611 return Empty;
31612 end Find_Related_Context;
31614 --------------------------------------
31615 -- Find_Related_Declaration_Or_Body --
31616 --------------------------------------
31618 function Find_Related_Declaration_Or_Body
31619 (Prag : Node_Id;
31620 Do_Checks : Boolean := False) return Node_Id
31622 Prag_Nam : constant Name_Id := Original_Aspect_Pragma_Name (Prag);
31624 procedure Expression_Function_Error;
31625 -- Emit an error concerning pragma Prag that illegaly applies to an
31626 -- expression function.
31628 -------------------------------
31629 -- Expression_Function_Error --
31630 -------------------------------
31632 procedure Expression_Function_Error is
31633 begin
31634 Error_Msg_Name_1 := Prag_Nam;
31636 -- Emit a precise message to distinguish between source pragmas and
31637 -- pragmas generated from aspects.
31639 if From_Aspect_Specification (Prag) then
31640 Error_Msg_N
31641 ("aspect % cannot apply to a standalone expression function",
31642 Prag);
31643 else
31644 Error_Msg_N
31645 ("pragma % cannot apply to a standalone expression function",
31646 Prag);
31647 end if;
31648 end Expression_Function_Error;
31650 -- Local variables
31652 Context : constant Node_Id := Parent (Prag);
31653 Stmt : Node_Id;
31655 Look_For_Body : constant Boolean :=
31656 Prag_Nam in Name_Refined_Depends
31657 | Name_Refined_Global
31658 | Name_Refined_Post
31659 | Name_Refined_State;
31660 -- Refinement pragmas must be associated with a subprogram body [stub]
31662 -- Start of processing for Find_Related_Declaration_Or_Body
31664 begin
31665 Stmt := Prev (Prag);
31666 while Present (Stmt) loop
31668 -- Skip prior pragmas, but check for duplicates. Pragmas produced
31669 -- by splitting a complex pre/postcondition are not considered to
31670 -- be duplicates.
31672 if Nkind (Stmt) = N_Pragma then
31673 if Do_Checks
31674 and then not Split_PPC (Stmt)
31675 and then Original_Aspect_Pragma_Name (Stmt) = Prag_Nam
31676 then
31677 Duplication_Error
31678 (Prag => Prag,
31679 Prev => Stmt);
31680 end if;
31682 -- Emit an error when a refinement pragma appears on an expression
31683 -- function without a completion.
31685 elsif Do_Checks
31686 and then Look_For_Body
31687 and then Nkind (Stmt) = N_Subprogram_Declaration
31688 and then Nkind (Original_Node (Stmt)) = N_Expression_Function
31689 and then not Has_Completion (Defining_Entity (Stmt))
31690 then
31691 Expression_Function_Error;
31692 return Empty;
31694 -- The refinement pragma applies to a subprogram body stub
31696 elsif Look_For_Body
31697 and then Nkind (Stmt) = N_Subprogram_Body_Stub
31698 then
31699 return Stmt;
31701 -- Skip internally generated code
31703 elsif not Comes_From_Source (Stmt) then
31705 -- The anonymous object created for a single concurrent type is a
31706 -- suitable context.
31708 if Nkind (Stmt) = N_Object_Declaration
31709 and then Is_Single_Concurrent_Object (Defining_Entity (Stmt))
31710 then
31711 return Stmt;
31713 elsif Nkind (Stmt) = N_Subprogram_Declaration then
31715 -- The subprogram declaration is an internally generated spec
31716 -- for an expression function.
31718 if Nkind (Original_Node (Stmt)) = N_Expression_Function then
31719 return Stmt;
31721 -- The subprogram declaration is an internally generated spec
31722 -- for a stand-alone subprogram body declared inside a
31723 -- protected body.
31725 elsif Present (Corresponding_Body (Stmt))
31726 and then Comes_From_Source (Corresponding_Body (Stmt))
31727 and then Is_Protected_Type (Current_Scope)
31728 then
31729 return Stmt;
31731 -- The subprogram is actually an instance housed within an
31732 -- anonymous wrapper package.
31734 elsif Present (Generic_Parent (Specification (Stmt))) then
31735 return Stmt;
31737 -- Ada 2022: contract on formal subprogram or on generated
31738 -- Access_Subprogram_Wrapper, which appears after the related
31739 -- Access_Subprogram declaration.
31741 elsif Is_Generic_Actual_Subprogram (Defining_Entity (Stmt))
31742 and then Ada_Version >= Ada_2022
31743 then
31744 return Stmt;
31746 elsif Is_Access_Subprogram_Wrapper (Defining_Entity (Stmt))
31747 and then Ada_Version >= Ada_2022
31748 then
31749 return Stmt;
31750 end if;
31751 end if;
31753 -- Return the current construct which is either a subprogram body,
31754 -- a subprogram declaration or is illegal.
31756 else
31757 return Stmt;
31758 end if;
31760 Prev (Stmt);
31761 end loop;
31763 -- If we fall through, then the pragma was either the first declaration
31764 -- or it was preceded by other pragmas and no source constructs.
31766 -- The pragma is associated with a library-level subprogram
31768 if Nkind (Context) = N_Compilation_Unit_Aux then
31769 return Unit (Parent (Context));
31771 -- The pragma appears inside the declarations of an entry body
31773 elsif Nkind (Context) = N_Entry_Body then
31774 return Context;
31776 -- The pragma appears inside the statements of a subprogram body at
31777 -- some nested level.
31779 elsif Is_Statement (Context)
31780 and then Present (Enclosing_HSS (Context))
31781 then
31782 return Parent (Enclosing_HSS (Context));
31784 -- The pragma appears directly in the statements of a subprogram body
31786 elsif Nkind (Context) = N_Handled_Sequence_Of_Statements then
31787 return Parent (Context);
31789 -- The pragma appears inside the declarative part of a package body
31791 elsif Nkind (Context) = N_Package_Body then
31792 return Context;
31794 -- The pragma appears inside the declarative part of a subprogram body
31796 elsif Nkind (Context) = N_Subprogram_Body then
31797 return Context;
31799 -- The pragma appears inside the declarative part of a task body
31801 elsif Nkind (Context) = N_Task_Body then
31802 return Context;
31804 -- The pragma appears inside the visible part of a package specification
31806 elsif Nkind (Context) = N_Package_Specification then
31807 return Parent (Context);
31809 -- The pragma is a byproduct of aspect expansion, return the related
31810 -- context of the original aspect. This case has a lower priority as
31811 -- the above circuitry pinpoints precisely the related context.
31813 elsif Present (Corresponding_Aspect (Prag)) then
31814 return Parent (Corresponding_Aspect (Prag));
31816 -- No candidate subprogram [body] found
31818 else
31819 return Empty;
31820 end if;
31821 end Find_Related_Declaration_Or_Body;
31823 ----------------------------------
31824 -- Find_Related_Package_Or_Body --
31825 ----------------------------------
31827 function Find_Related_Package_Or_Body
31828 (Prag : Node_Id;
31829 Do_Checks : Boolean := False) return Node_Id
31831 Context : constant Node_Id := Parent (Prag);
31832 Prag_Nam : constant Name_Id := Pragma_Name (Prag);
31833 Stmt : Node_Id;
31835 begin
31836 Stmt := Prev (Prag);
31837 while Present (Stmt) loop
31839 -- Skip prior pragmas, but check for duplicates
31841 if Nkind (Stmt) = N_Pragma then
31842 if Do_Checks and then Pragma_Name (Stmt) = Prag_Nam then
31843 Duplication_Error
31844 (Prag => Prag,
31845 Prev => Stmt);
31846 end if;
31848 -- Skip internally generated code
31850 elsif not Comes_From_Source (Stmt) then
31851 if Nkind (Stmt) = N_Subprogram_Declaration then
31853 -- The subprogram declaration is an internally generated spec
31854 -- for an expression function.
31856 if Nkind (Original_Node (Stmt)) = N_Expression_Function then
31857 return Stmt;
31859 -- The subprogram is actually an instance housed within an
31860 -- anonymous wrapper package.
31862 elsif Present (Generic_Parent (Specification (Stmt))) then
31863 return Stmt;
31864 end if;
31865 end if;
31867 -- Return the current source construct which is illegal
31869 else
31870 return Stmt;
31871 end if;
31873 Prev (Stmt);
31874 end loop;
31876 -- If we fall through, then the pragma was either the first declaration
31877 -- or it was preceded by other pragmas and no source constructs.
31879 -- The pragma is associated with a package. The immediate context in
31880 -- this case is the specification of the package.
31882 if Nkind (Context) = N_Package_Specification then
31883 return Parent (Context);
31885 -- The pragma appears in the declarations of a package body
31887 elsif Nkind (Context) = N_Package_Body then
31888 return Context;
31890 -- The pragma appears in the statements of a package body
31892 elsif Nkind (Context) = N_Handled_Sequence_Of_Statements
31893 and then Nkind (Parent (Context)) = N_Package_Body
31894 then
31895 return Parent (Context);
31897 -- The pragma is a byproduct of aspect expansion, return the related
31898 -- context of the original aspect. This case has a lower priority as
31899 -- the above circuitry pinpoints precisely the related context.
31901 elsif Present (Corresponding_Aspect (Prag)) then
31902 return Parent (Corresponding_Aspect (Prag));
31904 -- No candidate package [body] found
31906 else
31907 return Empty;
31908 end if;
31909 end Find_Related_Package_Or_Body;
31911 ------------------
31912 -- Get_Argument --
31913 ------------------
31915 function Get_Argument
31916 (Prag : Node_Id;
31917 Context_Id : Entity_Id := Empty) return Node_Id
31919 Args : constant List_Id := Pragma_Argument_Associations (Prag);
31921 begin
31922 -- Use the expression of the original aspect when analyzing the template
31923 -- of a generic unit. In both cases the aspect's tree must be decorated
31924 -- to save the global references in the generic context.
31926 if From_Aspect_Specification (Prag)
31927 and then Present (Context_Id)
31928 and then
31929 Is_Generic_Declaration_Or_Body (Unit_Declaration_Node (Context_Id))
31930 then
31931 return Corresponding_Aspect (Prag);
31933 -- Otherwise use the expression of the pragma
31935 elsif Present (Args) then
31936 return First (Args);
31938 else
31939 return Empty;
31940 end if;
31941 end Get_Argument;
31943 -------------------------
31944 -- Get_Base_Subprogram --
31945 -------------------------
31947 function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
31948 begin
31949 -- Follow subprogram renaming chain
31951 if Is_Subprogram (Def_Id)
31952 and then Parent_Kind (Declaration_Node (Def_Id)) =
31953 N_Subprogram_Renaming_Declaration
31954 and then Present (Alias (Def_Id))
31955 then
31956 return Alias (Def_Id);
31957 else
31958 return Def_Id;
31959 end if;
31960 end Get_Base_Subprogram;
31962 -------------------------
31963 -- Get_SPARK_Mode_Type --
31964 -------------------------
31966 function Get_SPARK_Mode_Type (N : Name_Id) return SPARK_Mode_Type is
31967 begin
31968 case N is
31969 when Name_Auto =>
31970 return None;
31971 when Name_On =>
31972 return On;
31973 when Name_Off =>
31974 return Off;
31976 -- Any other argument is illegal. Assume that no SPARK mode applies
31977 -- to avoid potential cascaded errors.
31979 when others =>
31980 return None;
31981 end case;
31982 end Get_SPARK_Mode_Type;
31984 ------------------------------------
31985 -- Get_SPARK_Mode_From_Annotation --
31986 ------------------------------------
31988 function Get_SPARK_Mode_From_Annotation
31989 (N : Node_Id) return SPARK_Mode_Type
31991 Mode : Node_Id;
31993 begin
31994 if Nkind (N) = N_Aspect_Specification then
31995 Mode := Expression (N);
31997 else pragma Assert (Nkind (N) = N_Pragma);
31998 Mode := First (Pragma_Argument_Associations (N));
32000 if Present (Mode) then
32001 Mode := Get_Pragma_Arg (Mode);
32002 end if;
32003 end if;
32005 -- Aspect or pragma SPARK_Mode specifies an explicit mode
32007 if Present (Mode) then
32008 if Nkind (Mode) = N_Identifier then
32009 return Get_SPARK_Mode_Type (Chars (Mode));
32011 -- In case of a malformed aspect or pragma, return the default None
32013 else
32014 return None;
32015 end if;
32017 -- Otherwise the lack of an expression defaults SPARK_Mode to On
32019 else
32020 return On;
32021 end if;
32022 end Get_SPARK_Mode_From_Annotation;
32024 ---------------------------
32025 -- Has_Extra_Parentheses --
32026 ---------------------------
32028 function Has_Extra_Parentheses (Clause : Node_Id) return Boolean is
32029 Expr : Node_Id;
32031 begin
32032 -- The aggregate should not have an expression list because a clause
32033 -- is always interpreted as a component association. The only way an
32034 -- expression list can sneak in is by adding extra parentheses around
32035 -- the individual clauses:
32037 -- Depends (Output => Input) -- proper form
32038 -- Depends ((Output => Input)) -- extra parentheses
32040 -- Since the extra parentheses are not allowed by the syntax of the
32041 -- pragma, flag them now to avoid emitting misleading errors down the
32042 -- line.
32044 if Nkind (Clause) = N_Aggregate
32045 and then Present (Expressions (Clause))
32046 then
32047 Expr := First (Expressions (Clause));
32048 while Present (Expr) loop
32050 -- A dependency clause surrounded by extra parentheses appears
32051 -- as an aggregate of component associations with an optional
32052 -- Paren_Count set.
32054 if Nkind (Expr) = N_Aggregate
32055 and then Present (Component_Associations (Expr))
32056 then
32057 SPARK_Msg_N
32058 ("dependency clause contains extra parentheses", Expr);
32060 -- Otherwise the expression is a malformed construct
32062 else
32063 SPARK_Msg_N ("malformed dependency clause", Expr);
32064 end if;
32066 Next (Expr);
32067 end loop;
32069 return True;
32070 end if;
32072 return False;
32073 end Has_Extra_Parentheses;
32075 ----------------
32076 -- Initialize --
32077 ----------------
32079 procedure Initialize is
32080 begin
32081 Externals.Init;
32082 Compile_Time_Warnings_Errors.Init;
32083 end Initialize;
32085 --------
32086 -- ip --
32087 --------
32089 procedure ip is
32090 begin
32091 Dummy := Dummy + 1;
32092 end ip;
32094 -----------------------------
32095 -- Is_Config_Static_String --
32096 -----------------------------
32098 function Is_Config_Static_String (Arg : Node_Id) return Boolean is
32100 function Add_Config_Static_String (Arg : Node_Id) return Boolean;
32101 -- This is an internal recursive function that is just like the outer
32102 -- function except that it adds the string to the name buffer rather
32103 -- than placing the string in the name buffer.
32105 ------------------------------
32106 -- Add_Config_Static_String --
32107 ------------------------------
32109 function Add_Config_Static_String (Arg : Node_Id) return Boolean is
32110 N : Node_Id;
32111 C : Char_Code;
32113 begin
32114 N := Arg;
32116 if Nkind (N) = N_Op_Concat then
32117 if Add_Config_Static_String (Left_Opnd (N)) then
32118 N := Right_Opnd (N);
32119 else
32120 return False;
32121 end if;
32122 end if;
32124 if Nkind (N) /= N_String_Literal then
32125 Error_Msg_N ("string literal expected for pragma argument", N);
32126 return False;
32128 else
32129 for J in 1 .. String_Length (Strval (N)) loop
32130 C := Get_String_Char (Strval (N), J);
32132 if not In_Character_Range (C) then
32133 Error_Msg
32134 ("string literal contains invalid wide character",
32135 Sloc (N) + 1 + Source_Ptr (J));
32136 return False;
32137 end if;
32139 Add_Char_To_Name_Buffer (Get_Character (C));
32140 end loop;
32141 end if;
32143 return True;
32144 end Add_Config_Static_String;
32146 -- Start of processing for Is_Config_Static_String
32148 begin
32149 Name_Len := 0;
32151 return Add_Config_Static_String (Arg);
32152 end Is_Config_Static_String;
32154 -------------------------------
32155 -- Is_Elaboration_SPARK_Mode --
32156 -------------------------------
32158 function Is_Elaboration_SPARK_Mode (N : Node_Id) return Boolean is
32159 begin
32160 pragma Assert
32161 (Nkind (N) = N_Pragma
32162 and then Pragma_Name (N) = Name_SPARK_Mode
32163 and then Is_List_Member (N));
32165 -- Pragma SPARK_Mode affects the elaboration of a package body when it
32166 -- appears in the statement part of the body.
32168 return
32169 Present (Parent (N))
32170 and then Nkind (Parent (N)) = N_Handled_Sequence_Of_Statements
32171 and then List_Containing (N) = Statements (Parent (N))
32172 and then Present (Parent (Parent (N)))
32173 and then Nkind (Parent (Parent (N))) = N_Package_Body;
32174 end Is_Elaboration_SPARK_Mode;
32176 -----------------------
32177 -- Is_Enabled_Pragma --
32178 -----------------------
32180 function Is_Enabled_Pragma (Prag : Node_Id) return Boolean is
32181 Arg : Node_Id;
32183 begin
32184 if Present (Prag) then
32185 Arg := First (Pragma_Argument_Associations (Prag));
32187 if Present (Arg) then
32188 return Is_True (Expr_Value (Get_Pragma_Arg (Arg)));
32190 -- The lack of a Boolean argument automatically enables the pragma
32192 else
32193 return True;
32194 end if;
32196 -- The pragma is missing, therefore it is not enabled
32198 else
32199 return False;
32200 end if;
32201 end Is_Enabled_Pragma;
32203 -----------------------------------------
32204 -- Is_Non_Significant_Pragma_Reference --
32205 -----------------------------------------
32207 -- This function makes use of the following static table which indicates
32208 -- whether appearance of some name in a given pragma is to be considered
32209 -- as a reference for the purposes of warnings about unreferenced objects.
32211 -- -1 indicates that appearance in any argument is significant
32212 -- 0 indicates that appearance in any argument is not significant
32213 -- +n indicates that appearance as argument n is significant, but all
32214 -- other arguments are not significant
32215 -- 9n arguments from n on are significant, before n insignificant
32217 Sig_Flags : constant array (Pragma_Id) of Int :=
32218 (Pragma_Abort_Defer => -1,
32219 Pragma_Abstract_State => -1,
32220 Pragma_Ada_83 => -1,
32221 Pragma_Ada_95 => -1,
32222 Pragma_Ada_05 => -1,
32223 Pragma_Ada_2005 => -1,
32224 Pragma_Ada_12 => -1,
32225 Pragma_Ada_2012 => -1,
32226 Pragma_Ada_2022 => -1,
32227 Pragma_Aggregate_Individually_Assign => 0,
32228 Pragma_All_Calls_Remote => -1,
32229 Pragma_Allow_Integer_Address => -1,
32230 Pragma_Always_Terminates => -1,
32231 Pragma_Annotate => 93,
32232 Pragma_Assert => -1,
32233 Pragma_Assert_And_Cut => -1,
32234 Pragma_Assertion_Policy => 0,
32235 Pragma_Assume => -1,
32236 Pragma_Assume_No_Invalid_Values => 0,
32237 Pragma_Async_Readers => 0,
32238 Pragma_Async_Writers => 0,
32239 Pragma_Asynchronous => 0,
32240 Pragma_Atomic => 0,
32241 Pragma_Atomic_Components => 0,
32242 Pragma_Attach_Handler => -1,
32243 Pragma_Attribute_Definition => 92,
32244 Pragma_Check => -1,
32245 Pragma_Check_Float_Overflow => 0,
32246 Pragma_Check_Name => 0,
32247 Pragma_Check_Policy => 0,
32248 Pragma_CPP_Class => 0,
32249 Pragma_CPP_Constructor => 0,
32250 Pragma_CPP_Virtual => 0,
32251 Pragma_CPP_Vtable => 0,
32252 Pragma_CPU => -1,
32253 Pragma_C_Pass_By_Copy => 0,
32254 Pragma_Comment => -1,
32255 Pragma_Common_Object => 0,
32256 Pragma_CUDA_Device => -1,
32257 Pragma_CUDA_Execute => -1,
32258 Pragma_CUDA_Global => -1,
32259 Pragma_Compile_Time_Error => -1,
32260 Pragma_Compile_Time_Warning => -1,
32261 Pragma_Complete_Representation => 0,
32262 Pragma_Complex_Representation => 0,
32263 Pragma_Component_Alignment => 0,
32264 Pragma_Constant_After_Elaboration => 0,
32265 Pragma_Contract_Cases => -1,
32266 Pragma_Controlled => 0,
32267 Pragma_Convention => 0,
32268 Pragma_Convention_Identifier => 0,
32269 Pragma_Deadline_Floor => -1,
32270 Pragma_Debug => -1,
32271 Pragma_Debug_Policy => 0,
32272 Pragma_Default_Initial_Condition => -1,
32273 Pragma_Default_Scalar_Storage_Order => 0,
32274 Pragma_Default_Storage_Pool => 0,
32275 Pragma_Depends => -1,
32276 Pragma_Detect_Blocking => 0,
32277 Pragma_Disable_Atomic_Synchronization => 0,
32278 Pragma_Discard_Names => 0,
32279 Pragma_Dispatching_Domain => -1,
32280 Pragma_Effective_Reads => 0,
32281 Pragma_Effective_Writes => 0,
32282 Pragma_Elaborate => 0,
32283 Pragma_Elaborate_All => 0,
32284 Pragma_Elaborate_Body => 0,
32285 Pragma_Elaboration_Checks => 0,
32286 Pragma_Eliminate => 0,
32287 Pragma_Enable_Atomic_Synchronization => 0,
32288 Pragma_Exceptional_Cases => -1,
32289 Pragma_Export => -1,
32290 Pragma_Export_Function => -1,
32291 Pragma_Export_Object => -1,
32292 Pragma_Export_Procedure => -1,
32293 Pragma_Export_Valued_Procedure => -1,
32294 Pragma_Extend_System => -1,
32295 Pragma_Extensions_Allowed => 0,
32296 Pragma_Extensions_Visible => 0,
32297 Pragma_External => -1,
32298 Pragma_External_Name_Casing => 0,
32299 Pragma_Fast_Math => 0,
32300 Pragma_Favor_Top_Level => 0,
32301 Pragma_Finalize_Storage_Only => 0,
32302 Pragma_Ghost => 0,
32303 Pragma_Global => -1,
32304 Pragma_GNAT_Annotate => 93,
32305 Pragma_Ident => -1,
32306 Pragma_Ignore_Pragma => 0,
32307 Pragma_Implementation_Defined => -1,
32308 Pragma_Implemented => -1,
32309 Pragma_Implicit_Packing => 0,
32310 Pragma_Import => 93,
32311 Pragma_Import_Function => 0,
32312 Pragma_Import_Object => 0,
32313 Pragma_Import_Procedure => 0,
32314 Pragma_Import_Valued_Procedure => 0,
32315 Pragma_Independent => 0,
32316 Pragma_Independent_Components => 0,
32317 Pragma_Initial_Condition => -1,
32318 Pragma_Initialize_Scalars => 0,
32319 Pragma_Initializes => -1,
32320 Pragma_Inline => 0,
32321 Pragma_Inline_Always => 0,
32322 Pragma_Inline_Generic => 0,
32323 Pragma_Inspection_Point => -1,
32324 Pragma_Interface => 92,
32325 Pragma_Interface_Name => 0,
32326 Pragma_Interrupt_Handler => -1,
32327 Pragma_Interrupt_Priority => -1,
32328 Pragma_Interrupt_State => -1,
32329 Pragma_Invariant => -1,
32330 Pragma_Keep_Names => 0,
32331 Pragma_License => 0,
32332 Pragma_Link_With => -1,
32333 Pragma_Linker_Alias => -1,
32334 Pragma_Linker_Constructor => -1,
32335 Pragma_Linker_Destructor => -1,
32336 Pragma_Linker_Options => -1,
32337 Pragma_Linker_Section => -1,
32338 Pragma_List => 0,
32339 Pragma_Lock_Free => 0,
32340 Pragma_Locking_Policy => 0,
32341 Pragma_Loop_Invariant => -1,
32342 Pragma_Loop_Optimize => 0,
32343 Pragma_Loop_Variant => -1,
32344 Pragma_Machine_Attribute => -1,
32345 Pragma_Main => -1,
32346 Pragma_Main_Storage => -1,
32347 Pragma_Max_Entry_Queue_Depth => 0,
32348 Pragma_Max_Entry_Queue_Length => 0,
32349 Pragma_Max_Queue_Length => 0,
32350 Pragma_Memory_Size => 0,
32351 Pragma_No_Body => 0,
32352 Pragma_No_Caching => 0,
32353 Pragma_No_Component_Reordering => -1,
32354 Pragma_No_Elaboration_Code_All => 0,
32355 Pragma_No_Heap_Finalization => 0,
32356 Pragma_No_Inline => 0,
32357 Pragma_No_Return => 0,
32358 Pragma_No_Run_Time => -1,
32359 Pragma_No_Strict_Aliasing => -1,
32360 Pragma_No_Tagged_Streams => 0,
32361 Pragma_Normalize_Scalars => 0,
32362 Pragma_Obsolescent => 0,
32363 Pragma_Optimize => 0,
32364 Pragma_Optimize_Alignment => 0,
32365 Pragma_Ordered => 0,
32366 Pragma_Overflow_Mode => 0,
32367 Pragma_Overriding_Renamings => 0,
32368 Pragma_Pack => 0,
32369 Pragma_Page => 0,
32370 Pragma_Part_Of => 0,
32371 Pragma_Partition_Elaboration_Policy => 0,
32372 Pragma_Passive => 0,
32373 Pragma_Persistent_BSS => 0,
32374 Pragma_Post => -1,
32375 Pragma_Postcondition => -1,
32376 Pragma_Post_Class => -1,
32377 Pragma_Pre => -1,
32378 Pragma_Precondition => -1,
32379 Pragma_Predicate => -1,
32380 Pragma_Predicate_Failure => -1,
32381 Pragma_Preelaborable_Initialization => -1,
32382 Pragma_Preelaborate => 0,
32383 Pragma_Prefix_Exception_Messages => 0,
32384 Pragma_Pre_Class => -1,
32385 Pragma_Priority => -1,
32386 Pragma_Priority_Specific_Dispatching => 0,
32387 Pragma_Profile => 0,
32388 Pragma_Profile_Warnings => 0,
32389 Pragma_Propagate_Exceptions => 0,
32390 Pragma_Provide_Shift_Operators => 0,
32391 Pragma_Psect_Object => 0,
32392 Pragma_Pure => 0,
32393 Pragma_Pure_Function => 0,
32394 Pragma_Queuing_Policy => 0,
32395 Pragma_Rational => 0,
32396 Pragma_Ravenscar => 0,
32397 Pragma_Refined_Depends => -1,
32398 Pragma_Refined_Global => -1,
32399 Pragma_Refined_Post => -1,
32400 Pragma_Refined_State => 0,
32401 Pragma_Relative_Deadline => 0,
32402 Pragma_Remote_Access_Type => -1,
32403 Pragma_Remote_Call_Interface => -1,
32404 Pragma_Remote_Types => -1,
32405 Pragma_Rename_Pragma => 0,
32406 Pragma_Restricted_Run_Time => 0,
32407 Pragma_Restriction_Warnings => 0,
32408 Pragma_Restrictions => 0,
32409 Pragma_Reviewable => -1,
32410 Pragma_Secondary_Stack_Size => -1,
32411 Pragma_Share_Generic => 0,
32412 Pragma_Shared => 0,
32413 Pragma_Shared_Passive => 0,
32414 Pragma_Short_Circuit_And_Or => 0,
32415 Pragma_Short_Descriptors => 0,
32416 Pragma_Simple_Storage_Pool_Type => 0,
32417 Pragma_Source_File_Name => 0,
32418 Pragma_Source_File_Name_Project => 0,
32419 Pragma_Source_Reference => 0,
32420 Pragma_SPARK_Mode => 0,
32421 Pragma_Static_Elaboration_Desired => 0,
32422 Pragma_Storage_Size => -1,
32423 Pragma_Storage_Unit => 0,
32424 Pragma_Stream_Convert => 0,
32425 Pragma_Style_Checks => 0,
32426 Pragma_Subprogram_Variant => -1,
32427 Pragma_Subtitle => 0,
32428 Pragma_Suppress => 0,
32429 Pragma_Suppress_All => 0,
32430 Pragma_Suppress_Debug_Info => 0,
32431 Pragma_Suppress_Exception_Locations => 0,
32432 Pragma_Suppress_Initialization => 0,
32433 Pragma_System_Name => 0,
32434 Pragma_Task_Dispatching_Policy => 0,
32435 Pragma_Task_Info => -1,
32436 Pragma_Task_Name => -1,
32437 Pragma_Task_Storage => -1,
32438 Pragma_Test_Case => -1,
32439 Pragma_Thread_Local_Storage => -1,
32440 Pragma_Time_Slice => -1,
32441 Pragma_Title => 0,
32442 Pragma_Type_Invariant => -1,
32443 Pragma_Type_Invariant_Class => -1,
32444 Pragma_Unchecked_Union => 0,
32445 Pragma_Unevaluated_Use_Of_Old => 0,
32446 Pragma_Unimplemented_Unit => 0,
32447 Pragma_Universal_Aliasing => 0,
32448 Pragma_Unmodified => 0,
32449 Pragma_Unreferenced => 0,
32450 Pragma_Unreferenced_Objects => 0,
32451 Pragma_Unreserve_All_Interrupts => 0,
32452 Pragma_Unsuppress => 0,
32453 Pragma_Unused => 0,
32454 Pragma_Use_VADS_Size => 0,
32455 Pragma_Validity_Checks => 0,
32456 Pragma_Volatile => 0,
32457 Pragma_Volatile_Components => 0,
32458 Pragma_Volatile_Full_Access => 0,
32459 Pragma_Volatile_Function => 0,
32460 Pragma_Warning_As_Error => 0,
32461 Pragma_Warnings => 0,
32462 Pragma_Weak_External => 0,
32463 Pragma_Wide_Character_Encoding => 0,
32464 Unknown_Pragma => 0);
32466 function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
32467 Id : Pragma_Id;
32468 P : Node_Id;
32469 C : Int;
32470 AN : Nat;
32472 function Arg_No return Nat;
32473 -- Returns an integer showing what argument we are in. A value of
32474 -- zero means we are not in any of the arguments.
32476 ------------
32477 -- Arg_No --
32478 ------------
32480 function Arg_No return Nat is
32481 A : Node_Id;
32482 N : Nat;
32484 begin
32485 A := First (Pragma_Argument_Associations (Parent (P)));
32486 N := 1;
32487 loop
32488 if No (A) then
32489 return 0;
32490 elsif A = P then
32491 return N;
32492 end if;
32494 Next (A);
32495 N := N + 1;
32496 end loop;
32497 end Arg_No;
32499 -- Start of processing for Non_Significant_Pragma_Reference
32501 begin
32502 -- Reference might appear either directly as expression of a pragma
32503 -- argument association, e.g. pragma Export (...), or within an
32504 -- aggregate with component associations, e.g. pragma Refined_State
32505 -- ((... => ...)).
32507 P := Parent (N);
32508 loop
32509 case Nkind (P) is
32510 when N_Pragma_Argument_Association =>
32511 exit;
32512 when N_Aggregate | N_Component_Association =>
32513 P := Parent (P);
32514 when others =>
32515 return False;
32516 end case;
32517 end loop;
32519 AN := Arg_No;
32521 if AN = 0 then
32522 return False;
32523 end if;
32525 Id := Get_Pragma_Id (Parent (P));
32526 C := Sig_Flags (Id);
32528 case C is
32529 when -1 =>
32530 return False;
32532 when 0 =>
32533 return True;
32535 when 92 .. 99 =>
32536 return AN < (C - 90);
32538 when others =>
32539 return AN /= C;
32540 end case;
32541 end Is_Non_Significant_Pragma_Reference;
32543 ------------------------------
32544 -- Is_Pragma_String_Literal --
32545 ------------------------------
32547 -- This function returns true if the corresponding pragma argument is a
32548 -- static string expression. These are the only cases in which string
32549 -- literals can appear as pragma arguments. We also allow a string literal
32550 -- as the first argument to pragma Assert (although it will of course
32551 -- always generate a type error).
32553 function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
32554 Pragn : constant Node_Id := Parent (Par);
32555 Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
32556 Pname : constant Name_Id := Pragma_Name (Pragn);
32557 Argn : Natural;
32558 N : Node_Id;
32560 begin
32561 Argn := 1;
32562 N := First (Assoc);
32563 loop
32564 exit when N = Par;
32565 Argn := Argn + 1;
32566 Next (N);
32567 end loop;
32569 if Pname = Name_Assert then
32570 return True;
32572 elsif Pname = Name_Export then
32573 return Argn > 2;
32575 elsif Pname = Name_Ident then
32576 return Argn = 1;
32578 elsif Pname = Name_Import then
32579 return Argn > 2;
32581 elsif Pname = Name_Interface_Name then
32582 return Argn > 1;
32584 elsif Pname = Name_Linker_Alias then
32585 return Argn = 2;
32587 elsif Pname = Name_Linker_Section then
32588 return Argn = 2;
32590 elsif Pname = Name_Machine_Attribute then
32591 return Argn = 2;
32593 elsif Pname = Name_Source_File_Name then
32594 return True;
32596 elsif Pname = Name_Source_Reference then
32597 return Argn = 2;
32599 elsif Pname = Name_Title then
32600 return True;
32602 elsif Pname = Name_Subtitle then
32603 return True;
32605 else
32606 return False;
32607 end if;
32608 end Is_Pragma_String_Literal;
32610 ---------------------------
32611 -- Is_Private_SPARK_Mode --
32612 ---------------------------
32614 function Is_Private_SPARK_Mode (N : Node_Id) return Boolean is
32615 begin
32616 pragma Assert
32617 (Nkind (N) = N_Pragma
32618 and then Pragma_Name (N) = Name_SPARK_Mode
32619 and then Is_List_Member (N));
32621 -- For pragma SPARK_Mode to be private, it has to appear in the private
32622 -- declarations of a package.
32624 return
32625 Present (Parent (N))
32626 and then Nkind (Parent (N)) = N_Package_Specification
32627 and then List_Containing (N) = Private_Declarations (Parent (N));
32628 end Is_Private_SPARK_Mode;
32630 -------------------------------------
32631 -- Is_Unconstrained_Or_Tagged_Item --
32632 -------------------------------------
32634 function Is_Unconstrained_Or_Tagged_Item
32635 (Item : Entity_Id) return Boolean
32637 function Has_Unconstrained_Component (Typ : Entity_Id) return Boolean;
32638 -- Determine whether record type Typ has at least one unconstrained
32639 -- component.
32641 ---------------------------------
32642 -- Has_Unconstrained_Component --
32643 ---------------------------------
32645 function Has_Unconstrained_Component (Typ : Entity_Id) return Boolean is
32646 Comp : Entity_Id;
32648 begin
32649 Comp := First_Component (Typ);
32650 while Present (Comp) loop
32651 if Is_Unconstrained_Or_Tagged_Item (Comp) then
32652 return True;
32653 end if;
32655 Next_Component (Comp);
32656 end loop;
32658 return False;
32659 end Has_Unconstrained_Component;
32661 -- Local variables
32663 Typ : constant Entity_Id := Etype (Item);
32665 -- Start of processing for Is_Unconstrained_Or_Tagged_Item
32667 begin
32668 if Is_Tagged_Type (Typ) then
32669 return True;
32671 elsif Is_Array_Type (Typ) and then not Is_Constrained (Typ) then
32672 return True;
32674 elsif Is_Record_Type (Typ) then
32675 if Has_Discriminants (Typ) and then not Is_Constrained (Typ) then
32676 return True;
32677 else
32678 return Has_Unconstrained_Component (Typ);
32679 end if;
32681 elsif Is_Private_Type (Typ) and then Has_Discriminants (Typ) then
32682 return True;
32684 else
32685 return False;
32686 end if;
32687 end Is_Unconstrained_Or_Tagged_Item;
32689 -----------------------------
32690 -- Is_Valid_Assertion_Kind --
32691 -----------------------------
32693 function Is_Valid_Assertion_Kind (Nam : Name_Id) return Boolean is
32694 begin
32695 case Nam is
32696 when
32697 -- RM defined
32699 Name_Assert
32700 | Name_Static_Predicate
32701 | Name_Dynamic_Predicate
32702 | Name_Pre
32703 | Name_uPre
32704 | Name_Post
32705 | Name_uPost
32706 | Name_Type_Invariant
32707 | Name_uType_Invariant
32709 -- Impl defined
32711 | Name_Assert_And_Cut
32712 | Name_Assume
32713 | Name_Contract_Cases
32714 | Name_Debug
32715 | Name_Default_Initial_Condition
32716 | Name_Ghost
32717 | Name_Ghost_Predicate
32718 | Name_Initial_Condition
32719 | Name_Invariant
32720 | Name_uInvariant
32721 | Name_Loop_Invariant
32722 | Name_Loop_Variant
32723 | Name_Postcondition
32724 | Name_Precondition
32725 | Name_Predicate
32726 | Name_Refined_Post
32727 | Name_Statement_Assertions
32728 | Name_Subprogram_Variant
32730 return True;
32732 when others =>
32733 return False;
32734 end case;
32735 end Is_Valid_Assertion_Kind;
32737 --------------------------------------
32738 -- Process_Compilation_Unit_Pragmas --
32739 --------------------------------------
32741 procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
32742 begin
32743 -- A special check for pragma Suppress_All, a very strange DEC pragma,
32744 -- strange because it comes at the end of the unit. Rational has the
32745 -- same name for a pragma, but treats it as a program unit pragma, In
32746 -- GNAT we just decide to allow it anywhere at all. If it appeared then
32747 -- the flag Has_Pragma_Suppress_All was set on the compilation unit
32748 -- node, and we insert a pragma Suppress (All_Checks) at the start of
32749 -- the context clause to ensure the correct processing.
32751 if Has_Pragma_Suppress_All (N) then
32752 Prepend_To (Context_Items (N),
32753 Make_Pragma (Sloc (N),
32754 Chars => Name_Suppress,
32755 Pragma_Argument_Associations => New_List (
32756 Make_Pragma_Argument_Association (Sloc (N),
32757 Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
32758 end if;
32760 -- Nothing else to do at the current time
32762 end Process_Compilation_Unit_Pragmas;
32764 --------------------------------------------
32765 -- Validate_Compile_Time_Warning_Or_Error --
32766 --------------------------------------------
32768 procedure Validate_Compile_Time_Warning_Or_Error
32769 (N : Node_Id;
32770 Eloc : Source_Ptr)
32772 Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
32773 Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
32774 Arg2 : constant Node_Id := Next (Arg1);
32776 Pname : constant Name_Id := Pragma_Name_Unmapped (N);
32777 Prag_Id : constant Pragma_Id := Get_Pragma_Id (Pname);
32779 begin
32780 Analyze_And_Resolve (Arg1x, Standard_Boolean);
32782 if Compile_Time_Known_Value (Arg1x) then
32783 if Is_True (Expr_Value (Arg1x)) then
32785 -- We have already verified that the second argument is a static
32786 -- string expression. Its string value must be retrieved
32787 -- explicitly if it is a declared constant, otherwise it has
32788 -- been constant-folded previously.
32790 declare
32791 Cent : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
32792 Str : constant String_Id :=
32793 Strval (Expr_Value_S (Get_Pragma_Arg (Arg2)));
32794 Str_Len : constant Nat := String_Length (Str);
32796 Force : constant Boolean :=
32797 Prag_Id = Pragma_Compile_Time_Warning
32798 and then Is_Spec_Name (Unit_Name (Current_Sem_Unit))
32799 and then (Ekind (Cent) /= E_Package
32800 or else not In_Private_Part (Cent));
32801 -- Set True if this is the warning case, and we are in the
32802 -- visible part of a package spec, or in a subprogram spec,
32803 -- in which case we want to force the client to see the
32804 -- warning, even though it is not in the main unit.
32806 C : Character;
32807 CC : Char_Code;
32808 Cont : Boolean;
32809 Ptr : Nat;
32811 begin
32812 -- Loop through segments of message separated by line feeds.
32813 -- We output these segments as separate messages with
32814 -- continuation marks for all but the first.
32816 Cont := False;
32817 Ptr := 1;
32818 loop
32819 Error_Msg_Strlen := 0;
32821 -- Loop to copy characters from argument to error message
32822 -- string buffer.
32824 loop
32825 exit when Ptr > Str_Len;
32826 CC := Get_String_Char (Str, Ptr);
32827 Ptr := Ptr + 1;
32829 -- Ignore wide chars ??? else store character
32831 if In_Character_Range (CC) then
32832 C := Get_Character (CC);
32833 exit when C = ASCII.LF;
32834 Error_Msg_Strlen := Error_Msg_Strlen + 1;
32835 Error_Msg_String (Error_Msg_Strlen) := C;
32836 end if;
32837 end loop;
32839 -- Here with one line ready to go
32841 Error_Msg_Warn := Prag_Id = Pragma_Compile_Time_Warning;
32843 -- If this is a warning in a spec, then we want clients
32844 -- to see the warning, so mark the message with the
32845 -- special sequence !! to force the warning. In the case
32846 -- of a package spec, we do not force this if we are in
32847 -- the private part of the spec.
32849 if Force then
32850 if Cont = False then
32851 Error_Msg
32852 ("<<~!!", Eloc, Is_Compile_Time_Pragma => True);
32853 Cont := True;
32854 else
32855 Error_Msg
32856 ("\<<~!!", Eloc, Is_Compile_Time_Pragma => True);
32857 end if;
32859 -- Error, rather than warning, or in a body, so we do not
32860 -- need to force visibility for client (error will be
32861 -- output in any case, and this is the situation in which
32862 -- we do not want a client to get a warning, since the
32863 -- warning is in the body or the spec private part).
32865 else
32866 if Cont = False then
32867 Error_Msg
32868 ("<<~", Eloc, Is_Compile_Time_Pragma => True);
32869 Cont := True;
32870 else
32871 Error_Msg
32872 ("\<<~", Eloc, Is_Compile_Time_Pragma => True);
32873 end if;
32874 end if;
32876 exit when Ptr > Str_Len;
32877 end loop;
32878 end;
32879 end if;
32881 -- Arg1x is not known at compile time, so possibly issue an error
32882 -- or warning. This can happen only if the pragma's processing
32883 -- was deferred until after the back end is run (see
32884 -- Process_Compile_Time_Warning_Or_Error). Note that the warning
32885 -- control switch applies to only the warning case.
32887 elsif Prag_Id = Pragma_Compile_Time_Error then
32888 Error_Msg_N ("condition is not known at compile time", Arg1x);
32890 elsif Warn_On_Unknown_Compile_Time_Warning then
32891 Error_Msg_N ("?_c?condition is not known at compile time", Arg1x);
32892 end if;
32893 end Validate_Compile_Time_Warning_Or_Error;
32895 ------------------------------------
32896 -- Record_Possible_Body_Reference --
32897 ------------------------------------
32899 procedure Record_Possible_Body_Reference
32900 (State_Id : Entity_Id;
32901 Ref : Node_Id)
32903 Context : Node_Id;
32904 Spec_Id : Entity_Id;
32906 begin
32907 -- Ensure that we are dealing with a reference to a state
32909 pragma Assert (Ekind (State_Id) = E_Abstract_State);
32911 -- Climb the tree starting from the reference looking for a package body
32912 -- whose spec declares the referenced state. This criteria automatically
32913 -- excludes references in package specs which are legal. Note that it is
32914 -- not wise to emit an error now as the package body may lack pragma
32915 -- Refined_State or the referenced state may not be mentioned in the
32916 -- refinement. This approach avoids the generation of misleading errors.
32918 Context := Ref;
32919 while Present (Context) loop
32920 if Nkind (Context) = N_Package_Body then
32921 Spec_Id := Corresponding_Spec (Context);
32923 if Contains (Abstract_States (Spec_Id), State_Id) then
32924 if No (Body_References (State_Id)) then
32925 Set_Body_References (State_Id, New_Elmt_List);
32926 end if;
32928 Append_Elmt (Ref, To => Body_References (State_Id));
32929 exit;
32930 end if;
32931 end if;
32933 Context := Parent (Context);
32934 end loop;
32935 end Record_Possible_Body_Reference;
32937 ------------------------------------------
32938 -- Relocate_Pragmas_To_Anonymous_Object --
32939 ------------------------------------------
32941 procedure Relocate_Pragmas_To_Anonymous_Object
32942 (Typ_Decl : Node_Id;
32943 Obj_Decl : Node_Id)
32945 Decl : Node_Id;
32946 Def : Node_Id;
32947 Next_Decl : Node_Id;
32949 begin
32950 if Nkind (Typ_Decl) = N_Protected_Type_Declaration then
32951 Def := Protected_Definition (Typ_Decl);
32952 else
32953 pragma Assert (Nkind (Typ_Decl) = N_Task_Type_Declaration);
32954 Def := Task_Definition (Typ_Decl);
32955 end if;
32957 -- The concurrent definition has a visible declaration list. Inspect it
32958 -- and relocate all canidate pragmas.
32960 if Present (Def) and then Present (Visible_Declarations (Def)) then
32961 Decl := First (Visible_Declarations (Def));
32962 while Present (Decl) loop
32964 -- Preserve the following declaration for iteration purposes due
32965 -- to possible relocation of a pragma.
32967 Next_Decl := Next (Decl);
32969 if Nkind (Decl) = N_Pragma
32970 and then Pragma_On_Anonymous_Object_OK (Get_Pragma_Id (Decl))
32971 then
32972 Remove (Decl);
32973 Insert_After (Obj_Decl, Decl);
32975 -- Skip internally generated code
32977 elsif not Comes_From_Source (Decl) then
32978 null;
32980 -- No candidate pragmas are available for relocation
32982 else
32983 exit;
32984 end if;
32986 Decl := Next_Decl;
32987 end loop;
32988 end if;
32989 end Relocate_Pragmas_To_Anonymous_Object;
32991 ------------------------------
32992 -- Relocate_Pragmas_To_Body --
32993 ------------------------------
32995 procedure Relocate_Pragmas_To_Body
32996 (Subp_Body : Node_Id;
32997 Target_Body : Node_Id := Empty)
32999 procedure Relocate_Pragma (Prag : Node_Id);
33000 -- Remove a single pragma from its current list and add it to the
33001 -- declarations of the proper body (either Subp_Body or Target_Body).
33003 ---------------------
33004 -- Relocate_Pragma --
33005 ---------------------
33007 procedure Relocate_Pragma (Prag : Node_Id) is
33008 Decls : List_Id;
33009 Target : Node_Id;
33011 begin
33012 -- When subprogram stubs or expression functions are involves, the
33013 -- destination declaration list belongs to the proper body.
33015 if Present (Target_Body) then
33016 Target := Target_Body;
33017 else
33018 Target := Subp_Body;
33019 end if;
33021 Decls := Declarations (Target);
33023 if No (Decls) then
33024 Decls := New_List;
33025 Set_Declarations (Target, Decls);
33026 end if;
33028 -- Unhook the pragma from its current list
33030 Remove (Prag);
33031 Prepend (Prag, Decls);
33032 end Relocate_Pragma;
33034 -- Local variables
33036 Body_Id : constant Entity_Id :=
33037 Defining_Unit_Name (Specification (Subp_Body));
33038 Next_Stmt : Node_Id;
33039 Stmt : Node_Id;
33041 -- Start of processing for Relocate_Pragmas_To_Body
33043 begin
33044 -- Do not process a body that comes from a separate unit as no construct
33045 -- can possibly follow it.
33047 if not Is_List_Member (Subp_Body) then
33048 return;
33050 -- Do not relocate pragmas that follow a stub if the stub does not have
33051 -- a proper body.
33053 elsif Nkind (Subp_Body) = N_Subprogram_Body_Stub
33054 and then No (Target_Body)
33055 then
33056 return;
33058 -- Do not process internally generated routine _Wrapped_Statements
33060 elsif Ekind (Body_Id) = E_Procedure
33061 and then Chars (Body_Id) = Name_uWrapped_Statements
33062 then
33063 return;
33064 end if;
33066 -- Look at what is following the body. We are interested in certain kind
33067 -- of pragmas (either from source or byproducts of expansion) that can
33068 -- apply to a body [stub].
33070 Stmt := Next (Subp_Body);
33071 while Present (Stmt) loop
33073 -- Preserve the following statement for iteration purposes due to a
33074 -- possible relocation of a pragma.
33076 Next_Stmt := Next (Stmt);
33078 -- Move a candidate pragma following the body to the declarations of
33079 -- the body.
33081 if Nkind (Stmt) = N_Pragma
33082 and then Pragma_On_Body_Or_Stub_OK (Get_Pragma_Id (Stmt))
33083 then
33085 -- If a source pragma Warnings follows the body, it applies to
33086 -- following statements and does not belong in the body.
33088 if Get_Pragma_Id (Stmt) = Pragma_Warnings
33089 and then Comes_From_Source (Stmt)
33090 then
33091 null;
33092 else
33093 Relocate_Pragma (Stmt);
33094 end if;
33096 -- Skip internally generated code
33098 elsif not Comes_From_Source (Stmt) then
33099 null;
33101 -- No candidate pragmas are available for relocation
33103 else
33104 exit;
33105 end if;
33107 Stmt := Next_Stmt;
33108 end loop;
33109 end Relocate_Pragmas_To_Body;
33111 -------------------
33112 -- Resolve_State --
33113 -------------------
33115 procedure Resolve_State (N : Node_Id) is
33116 Func : Entity_Id;
33117 State : Entity_Id;
33119 begin
33120 if Is_Entity_Name (N) and then Present (Entity (N)) then
33121 Func := Entity (N);
33123 -- Handle overloading of state names by functions. Traverse the
33124 -- homonym chain looking for an abstract state.
33126 if Ekind (Func) = E_Function and then Has_Homonym (Func) then
33127 pragma Assert (Is_Overloaded (N));
33129 State := Homonym (Func);
33130 while Present (State) loop
33131 if Ekind (State) = E_Abstract_State then
33133 -- Resolve the overloading by setting the proper entity of
33134 -- the reference to that of the state.
33136 Set_Etype (N, Standard_Void_Type);
33137 Set_Entity (N, State);
33138 Set_Is_Overloaded (N, False);
33140 Generate_Reference (State, N);
33141 return;
33142 end if;
33144 State := Homonym (State);
33145 end loop;
33147 -- A function can never act as a state. If the homonym chain does
33148 -- not contain a corresponding state, then something went wrong in
33149 -- the overloading mechanism.
33151 raise Program_Error;
33152 end if;
33153 end if;
33154 end Resolve_State;
33156 ----------------------------
33157 -- Rewrite_Assertion_Kind --
33158 ----------------------------
33160 procedure Rewrite_Assertion_Kind
33161 (N : Node_Id;
33162 From_Policy : Boolean := False)
33164 Nam : Name_Id;
33166 begin
33167 Nam := No_Name;
33168 if Nkind (N) = N_Attribute_Reference
33169 and then Attribute_Name (N) = Name_Class
33170 and then Nkind (Prefix (N)) = N_Identifier
33171 then
33172 case Chars (Prefix (N)) is
33173 when Name_Pre =>
33174 Nam := Name_uPre;
33176 when Name_Post =>
33177 Nam := Name_uPost;
33179 when Name_Type_Invariant =>
33180 Nam := Name_uType_Invariant;
33182 when Name_Invariant =>
33183 Nam := Name_uInvariant;
33185 when others =>
33186 return;
33187 end case;
33189 -- Recommend standard use of aspect names Pre/Post
33191 elsif Nkind (N) = N_Identifier
33192 and then From_Policy
33193 and then Serious_Errors_Detected = 0
33194 then
33195 if Chars (N) = Name_Precondition
33196 or else Chars (N) = Name_Postcondition
33197 then
33198 Error_Msg_N ("Check_Policy is a non-standard pragma??", N);
33199 Error_Msg_N
33200 ("\use Assertion_Policy and aspect names Pre/Post for "
33201 & "Ada2012 conformance?", N);
33202 end if;
33204 return;
33205 end if;
33207 if Nam /= No_Name then
33208 Rewrite (N, Make_Identifier (Sloc (N), Chars => Nam));
33209 end if;
33210 end Rewrite_Assertion_Kind;
33212 --------
33213 -- rv --
33214 --------
33216 procedure rv is
33217 begin
33218 Dummy := Dummy + 1;
33219 end rv;
33221 --------------------------------
33222 -- Set_Encoded_Interface_Name --
33223 --------------------------------
33225 procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
33226 Str : constant String_Id := Strval (S);
33227 Len : constant Nat := String_Length (Str);
33228 CC : Char_Code;
33229 C : Character;
33230 J : Pos;
33232 Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
33234 procedure Encode;
33235 -- Stores encoded value of character code CC. The encoding we use an
33236 -- underscore followed by four lower case hex digits.
33238 ------------
33239 -- Encode --
33240 ------------
33242 procedure Encode is
33243 begin
33244 Store_String_Char (Get_Char_Code ('_'));
33245 Store_String_Char
33246 (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
33247 Store_String_Char
33248 (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
33249 Store_String_Char
33250 (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
33251 Store_String_Char
33252 (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
33253 end Encode;
33255 -- Start of processing for Set_Encoded_Interface_Name
33257 begin
33258 -- If first character is asterisk, this is a link name, and we leave it
33259 -- completely unmodified. We also ignore null strings (the latter case
33260 -- happens only in error cases).
33262 if Len = 0
33263 or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
33264 then
33265 Set_Interface_Name (E, S);
33267 else
33268 J := 1;
33269 loop
33270 CC := Get_String_Char (Str, J);
33272 exit when not In_Character_Range (CC);
33274 C := Get_Character (CC);
33276 exit when C /= '_' and then C /= '$'
33277 and then C not in '0' .. '9'
33278 and then C not in 'a' .. 'z'
33279 and then C not in 'A' .. 'Z';
33281 if J = Len then
33282 Set_Interface_Name (E, S);
33283 return;
33285 else
33286 J := J + 1;
33287 end if;
33288 end loop;
33290 -- Here we need to encode. The encoding we use as follows:
33291 -- three underscores + four hex digits (lower case)
33293 Start_String;
33295 for J in 1 .. String_Length (Str) loop
33296 CC := Get_String_Char (Str, J);
33298 if not In_Character_Range (CC) then
33299 Encode;
33300 else
33301 C := Get_Character (CC);
33303 if C = '_' or else C = '$'
33304 or else C in '0' .. '9'
33305 or else C in 'a' .. 'z'
33306 or else C in 'A' .. 'Z'
33307 then
33308 Store_String_Char (CC);
33309 else
33310 Encode;
33311 end if;
33312 end if;
33313 end loop;
33315 Set_Interface_Name (E,
33316 Make_String_Literal (Sloc (S),
33317 Strval => End_String));
33318 end if;
33319 end Set_Encoded_Interface_Name;
33321 ------------------------
33322 -- Set_Elab_Unit_Name --
33323 ------------------------
33325 procedure Set_Elab_Unit_Name (N : Node_Id; With_Item : Node_Id) is
33326 Pref : Node_Id;
33327 Scop : Entity_Id;
33329 begin
33330 if Nkind (N) = N_Identifier
33331 and then Nkind (With_Item) = N_Identifier
33332 then
33333 Set_Entity (N, Entity (With_Item));
33335 elsif Nkind (N) = N_Selected_Component then
33336 Change_Selected_Component_To_Expanded_Name (N);
33337 Set_Entity (N, Entity (With_Item));
33338 Set_Entity (Selector_Name (N), Entity (N));
33340 Pref := Prefix (N);
33341 Scop := Scope (Entity (N));
33342 while Nkind (Pref) = N_Selected_Component loop
33343 Change_Selected_Component_To_Expanded_Name (Pref);
33344 Set_Entity (Selector_Name (Pref), Scop);
33345 Set_Entity (Pref, Scop);
33346 Pref := Prefix (Pref);
33347 Scop := Scope (Scop);
33348 end loop;
33350 Set_Entity (Pref, Scop);
33351 end if;
33353 Generate_Reference (Entity (With_Item), N, Set_Ref => False);
33354 end Set_Elab_Unit_Name;
33356 -----------------------
33357 -- Set_Overflow_Mode --
33358 -----------------------
33360 procedure Set_Overflow_Mode (N : Node_Id) is
33362 function Get_Overflow_Mode (Arg : Node_Id) return Overflow_Mode_Type;
33363 -- Function to process one pragma argument, Arg
33365 -----------------------
33366 -- Get_Overflow_Mode --
33367 -----------------------
33369 function Get_Overflow_Mode (Arg : Node_Id) return Overflow_Mode_Type is
33370 Argx : constant Node_Id := Get_Pragma_Arg (Arg);
33372 begin
33373 if Chars (Argx) = Name_Strict then
33374 return Strict;
33376 elsif Chars (Argx) = Name_Minimized then
33377 return Minimized;
33379 elsif Chars (Argx) = Name_Eliminated then
33380 return Eliminated;
33382 else
33383 raise Program_Error;
33384 end if;
33385 end Get_Overflow_Mode;
33387 -- Local variables
33389 Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
33390 Arg2 : constant Node_Id := Next (Arg1);
33392 -- Start of processing for Set_Overflow_Mode
33394 begin
33395 -- Process first argument
33397 Scope_Suppress.Overflow_Mode_General :=
33398 Get_Overflow_Mode (Arg1);
33400 -- Case of only one argument
33402 if No (Arg2) then
33403 Scope_Suppress.Overflow_Mode_Assertions :=
33404 Scope_Suppress.Overflow_Mode_General;
33406 -- Case of two arguments present
33408 else
33409 Scope_Suppress.Overflow_Mode_Assertions :=
33410 Get_Overflow_Mode (Arg2);
33411 end if;
33412 end Set_Overflow_Mode;
33414 -------------------
33415 -- Test_Case_Arg --
33416 -------------------
33418 function Test_Case_Arg
33419 (Prag : Node_Id;
33420 Arg_Nam : Name_Id;
33421 From_Aspect : Boolean := False) return Node_Id
33423 Aspect : constant Node_Id := Corresponding_Aspect (Prag);
33424 Arg : Node_Id;
33425 Args : Node_Id;
33427 begin
33428 pragma Assert
33429 (Arg_Nam in Name_Ensures | Name_Mode | Name_Name | Name_Requires);
33431 -- The caller requests the aspect argument
33433 if From_Aspect then
33434 if Present (Aspect)
33435 and then Nkind (Expression (Aspect)) = N_Aggregate
33436 then
33437 Args := Expression (Aspect);
33439 -- "Name" and "Mode" may appear without an identifier as a
33440 -- positional association.
33442 if Present (Expressions (Args)) then
33443 Arg := First (Expressions (Args));
33445 if Present (Arg) and then Arg_Nam = Name_Name then
33446 return Arg;
33447 end if;
33449 -- Skip "Name"
33451 Arg := Next (Arg);
33453 if Present (Arg) and then Arg_Nam = Name_Mode then
33454 return Arg;
33455 end if;
33456 end if;
33458 -- Some or all arguments may appear as component associatons
33460 if Present (Component_Associations (Args)) then
33461 Arg := First (Component_Associations (Args));
33462 while Present (Arg) loop
33463 if Chars (First (Choices (Arg))) = Arg_Nam then
33464 return Arg;
33465 end if;
33467 Next (Arg);
33468 end loop;
33469 end if;
33470 end if;
33472 -- Otherwise retrieve the argument directly from the pragma
33474 else
33475 Arg := First (Pragma_Argument_Associations (Prag));
33477 if Present (Arg) and then Arg_Nam = Name_Name then
33478 return Arg;
33479 end if;
33481 -- Skip argument "Name"
33483 Arg := Next (Arg);
33485 if Present (Arg) and then Arg_Nam = Name_Mode then
33486 return Arg;
33487 end if;
33489 -- Skip argument "Mode"
33491 Arg := Next (Arg);
33493 -- Arguments "Requires" and "Ensures" are optional and may not be
33494 -- present at all.
33496 while Present (Arg) loop
33497 if Chars (Arg) = Arg_Nam then
33498 return Arg;
33499 end if;
33501 Next (Arg);
33502 end loop;
33503 end if;
33505 return Empty;
33506 end Test_Case_Arg;
33508 --------------------------------------------
33509 -- Defer_Compile_Time_Warning_Error_To_BE --
33510 --------------------------------------------
33512 procedure Defer_Compile_Time_Warning_Error_To_BE (N : Node_Id) is
33513 Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
33514 begin
33515 Compile_Time_Warnings_Errors.Append
33516 (New_Val => CTWE_Entry'(Eloc => Sloc (Arg1),
33517 Scope => Current_Scope,
33518 Prag => N));
33520 -- If the Boolean expression contains T'Size, and we're not in the main
33521 -- unit being compiled, then we need to copy the pragma into the main
33522 -- unit, because otherwise T'Size might never be computed, leaving it
33523 -- as 0.
33525 if not In_Extended_Main_Code_Unit (N) then
33526 Insert_Library_Level_Action (New_Copy_Tree (N));
33527 end if;
33528 end Defer_Compile_Time_Warning_Error_To_BE;
33530 ------------------------------------------
33531 -- Validate_Compile_Time_Warning_Errors --
33532 ------------------------------------------
33534 procedure Validate_Compile_Time_Warning_Errors is
33535 procedure Set_Scope (S : Entity_Id);
33536 -- Install all enclosing scopes of S along with S itself
33538 procedure Unset_Scope (S : Entity_Id);
33539 -- Uninstall all enclosing scopes of S along with S itself
33541 ---------------
33542 -- Set_Scope --
33543 ---------------
33545 procedure Set_Scope (S : Entity_Id) is
33546 begin
33547 if S /= Standard_Standard then
33548 Set_Scope (Scope (S));
33549 end if;
33551 Push_Scope (S);
33552 end Set_Scope;
33554 -----------------
33555 -- Unset_Scope --
33556 -----------------
33558 procedure Unset_Scope (S : Entity_Id) is
33559 begin
33560 if S /= Standard_Standard then
33561 Unset_Scope (Scope (S));
33562 end if;
33564 Pop_Scope;
33565 end Unset_Scope;
33567 -- Start of processing for Validate_Compile_Time_Warning_Errors
33569 begin
33570 Expander_Mode_Save_And_Set (False);
33571 In_Compile_Time_Warning_Or_Error := True;
33573 for N in Compile_Time_Warnings_Errors.First ..
33574 Compile_Time_Warnings_Errors.Last
33575 loop
33576 declare
33577 T : CTWE_Entry renames Compile_Time_Warnings_Errors.Table (N);
33579 begin
33580 Set_Scope (T.Scope);
33581 Reset_Analyzed_Flags (T.Prag);
33582 Validate_Compile_Time_Warning_Or_Error (T.Prag, T.Eloc);
33583 Unset_Scope (T.Scope);
33584 end;
33585 end loop;
33587 In_Compile_Time_Warning_Or_Error := False;
33588 Expander_Mode_Restore;
33589 end Validate_Compile_Time_Warning_Errors;
33591 end Sem_Prag;