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-2018, 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------------------------------------------------------------------------------
25
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).
31
32with Aspects;   use Aspects;
33with Atree;     use Atree;
34with Casing;    use Casing;
35with Checks;    use Checks;
36with Contracts; use Contracts;
37with Csets;     use Csets;
38with Debug;     use Debug;
39with Einfo;     use Einfo;
40with Elists;    use Elists;
41with Errout;    use Errout;
42with Exp_Dist;  use Exp_Dist;
43with Exp_Util;  use Exp_Util;
44with Freeze;    use Freeze;
45with Ghost;     use Ghost;
46with Gnatvsn;   use Gnatvsn;
47with Lib;       use Lib;
48with Lib.Writ;  use Lib.Writ;
49with Lib.Xref;  use Lib.Xref;
50with Namet.Sp;  use Namet.Sp;
51with Nlists;    use Nlists;
52with Nmake;     use Nmake;
53with Output;    use Output;
54with Par_SCO;   use Par_SCO;
55with Restrict;  use Restrict;
56with Rident;    use Rident;
57with Rtsfind;   use Rtsfind;
58with Sem;       use Sem;
59with Sem_Aux;   use Sem_Aux;
60with Sem_Ch3;   use Sem_Ch3;
61with Sem_Ch6;   use Sem_Ch6;
62with Sem_Ch8;   use Sem_Ch8;
63with Sem_Ch12;  use Sem_Ch12;
64with Sem_Ch13;  use Sem_Ch13;
65with Sem_Disp;  use Sem_Disp;
66with Sem_Dist;  use Sem_Dist;
67with Sem_Elab;  use Sem_Elab;
68with Sem_Elim;  use Sem_Elim;
69with Sem_Eval;  use Sem_Eval;
70with Sem_Intr;  use Sem_Intr;
71with Sem_Mech;  use Sem_Mech;
72with Sem_Res;   use Sem_Res;
73with Sem_Type;  use Sem_Type;
74with Sem_Util;  use Sem_Util;
75with Sem_Warn;  use Sem_Warn;
76with Stand;     use Stand;
77with Sinfo;     use Sinfo;
78with Sinfo.CN;  use Sinfo.CN;
79with Sinput;    use Sinput;
80with Stringt;   use Stringt;
81with Stylesw;   use Stylesw;
82with Table;
83with Targparm;  use Targparm;
84with Tbuild;    use Tbuild;
85with Ttypes;
86with Uintp;     use Uintp;
87with Uname;     use Uname;
88with Urealp;    use Urealp;
89with Validsw;   use Validsw;
90with Warnsw;    use Warnsw;
91
92with System.Case_Util;
93
94package body Sem_Prag is
95
96   ----------------------------------------------
97   -- Common Handling of Import-Export Pragmas --
98   ----------------------------------------------
99
100   --  In the following section, a number of Import_xxx and Export_xxx pragmas
101   --  are defined by GNAT. These are compatible with the DEC pragmas of the
102   --  same name, and all have the following common form and processing:
103
104   --  pragma Export_xxx
105   --        [Internal                 =>] LOCAL_NAME
106   --     [, [External                 =>] EXTERNAL_SYMBOL]
107   --     [, other optional parameters   ]);
108
109   --  pragma Import_xxx
110   --        [Internal                 =>] LOCAL_NAME
111   --     [, [External                 =>] EXTERNAL_SYMBOL]
112   --     [, other optional parameters   ]);
113
114   --   EXTERNAL_SYMBOL ::=
115   --     IDENTIFIER
116   --   | static_string_EXPRESSION
117
118   --  The internal LOCAL_NAME designates the entity that is imported or
119   --  exported, and must refer to an entity in the current declarative
120   --  part (as required by the rules for LOCAL_NAME).
121
122   --  The external linker name is designated by the External parameter if
123   --  given, or the Internal parameter if not (if there is no External
124   --  parameter, the External parameter is a copy of the Internal name).
125
126   --  If the External parameter is given as a string, then this string is
127   --  treated as an external name (exactly as though it had been given as an
128   --  External_Name parameter for a normal Import pragma).
129
130   --  If the External parameter is given as an identifier (or there is no
131   --  External parameter, so that the Internal identifier is used), then
132   --  the external name is the characters of the identifier, translated
133   --  to all lower case letters.
134
135   --  Note: the external name specified or implied by any of these special
136   --  Import_xxx or Export_xxx pragmas override an external or link name
137   --  specified in a previous Import or Export pragma.
138
139   --  Note: these and all other DEC-compatible GNAT pragmas allow full use of
140   --  named notation, following the standard rules for subprogram calls, i.e.
141   --  parameters can be given in any order if named notation is used, and
142   --  positional and named notation can be mixed, subject to the rule that all
143   --  positional parameters must appear first.
144
145   --  Note: All these pragmas are implemented exactly following the DEC design
146   --  and implementation and are intended to be fully compatible with the use
147   --  of these pragmas in the DEC Ada compiler.
148
149   --------------------------------------------
150   -- Checking for Duplicated External Names --
151   --------------------------------------------
152
153   --  It is suspicious if two separate Export pragmas use the same external
154   --  name. The following table is used to diagnose this situation so that
155   --  an appropriate warning can be issued.
156
157   --  The Node_Id stored is for the N_String_Literal node created to hold
158   --  the value of the external name. The Sloc of this node is used to
159   --  cross-reference the location of the duplication.
160
161   package Externals is new Table.Table (
162     Table_Component_Type => Node_Id,
163     Table_Index_Type     => Int,
164     Table_Low_Bound      => 0,
165     Table_Initial        => 100,
166     Table_Increment      => 100,
167     Table_Name           => "Name_Externals");
168
169   -------------------------------------
170   -- Local Subprograms and Variables --
171   -------------------------------------
172
173   function Adjust_External_Name_Case (N : Node_Id) return Node_Id;
174   --  This routine is used for possible casing adjustment of an explicit
175   --  external name supplied as a string literal (the node N), according to
176   --  the casing requirement of Opt.External_Name_Casing. If this is set to
177   --  As_Is, then the string literal is returned unchanged, but if it is set
178   --  to Uppercase or Lowercase, then a new string literal with appropriate
179   --  casing is constructed.
180
181   procedure Analyze_Part_Of
182     (Indic    : Node_Id;
183      Item_Id  : Entity_Id;
184      Encap    : Node_Id;
185      Encap_Id : out Entity_Id;
186      Legal    : out Boolean);
187   --  Subsidiary to Analyze_Part_Of_In_Decl_Part, Analyze_Part_Of_Option and
188   --  Analyze_Pragma. Perform full analysis of indicator Part_Of. Indic is the
189   --  Part_Of indicator. Item_Id is the entity of an abstract state, object or
190   --  package instantiation. Encap denotes the encapsulating state or single
191   --  concurrent type. Encap_Id is the entity of Encap. Flag Legal is set when
192   --  the indicator is legal.
193
194   function Appears_In (List : Elist_Id; Item_Id : Entity_Id) return Boolean;
195   --  Subsidiary to analysis of pragmas Depends, Global and Refined_Depends.
196   --  Query whether a particular item appears in a mixed list of nodes and
197   --  entities. It is assumed that all nodes in the list have entities.
198
199   procedure Check_Postcondition_Use_In_Inlined_Subprogram
200     (Prag    : Node_Id;
201      Spec_Id : Entity_Id);
202   --  Subsidiary to the analysis of pragmas Contract_Cases, Postcondition,
203   --  Precondition, Refined_Post, and Test_Case. Emit a warning when pragma
204   --  Prag is associated with subprogram Spec_Id subject to Inline_Always,
205   --  and assertions are enabled.
206
207   procedure Check_State_And_Constituent_Use
208     (States   : Elist_Id;
209      Constits : Elist_Id;
210      Context  : Node_Id);
211   --  Subsidiary to the analysis of pragmas [Refined_]Depends, [Refined_]
212   --  Global and Initializes. Determine whether a state from list States and a
213   --  corresponding constituent from list Constits (if any) appear in the same
214   --  context denoted by Context. If this is the case, emit an error.
215
216   procedure Contract_Freeze_Error
217     (Contract_Id : Entity_Id;
218      Freeze_Id   : Entity_Id);
219   --  Subsidiary to the analysis of pragmas Contract_Cases, Part_Of, Post, and
220   --  Pre. Emit a freezing-related error message where Freeze_Id is the entity
221   --  of a body which caused contract freezing and Contract_Id denotes the
222   --  entity of the affected contstruct.
223
224   procedure Duplication_Error (Prag : Node_Id; Prev : Node_Id);
225   --  Subsidiary to all Find_Related_xxx routines. Emit an error on pragma
226   --  Prag that duplicates previous pragma Prev.
227
228   function Find_Encapsulating_State
229     (States     : Elist_Id;
230      Constit_Id : Entity_Id) return Entity_Id;
231   --  Given the entity of a constituent Constit_Id, find the corresponding
232   --  encapsulating state which appears in States. The routine returns Empty
233   --  if no such state is found.
234
235   function Find_Related_Context
236     (Prag      : Node_Id;
237      Do_Checks : Boolean := False) return Node_Id;
238   --  Subsidiary to the analysis of pragmas
239   --    Async_Readers
240   --    Async_Writers
241   --    Constant_After_Elaboration
242   --    Effective_Reads
243   --    Effective_Writers
244   --    Part_Of
245   --  Find the first source declaration or statement found while traversing
246   --  the previous node chain starting from pragma Prag. If flag Do_Checks is
247   --  set, the routine reports duplicate pragmas. The routine returns Empty
248   --  when reaching the start of the node chain.
249
250   function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id;
251   --  If Def_Id refers to a renamed subprogram, then the base subprogram (the
252   --  original one, following the renaming chain) is returned. Otherwise the
253   --  entity is returned unchanged. Should be in Einfo???
254
255   function Get_SPARK_Mode_Type (N : Name_Id) return SPARK_Mode_Type;
256   --  Subsidiary to the analysis of pragma SPARK_Mode as well as subprogram
257   --  Get_SPARK_Mode_From_Annotation. Convert a name into a corresponding
258   --  value of type SPARK_Mode_Type.
259
260   function Has_Extra_Parentheses (Clause : Node_Id) return Boolean;
261   --  Subsidiary to the analysis of pragmas Depends and Refined_Depends.
262   --  Determine whether dependency clause Clause is surrounded by extra
263   --  parentheses. If this is the case, issue an error message.
264
265   function Is_Unconstrained_Or_Tagged_Item (Item : Entity_Id) return Boolean;
266   --  Subsidiary to Collect_Subprogram_Inputs_Outputs and the analysis of
267   --  pragma Depends. Determine whether the type of dependency item Item is
268   --  tagged, unconstrained array, unconstrained record or a record with at
269   --  least one unconstrained component.
270
271   procedure Record_Possible_Body_Reference
272     (State_Id : Entity_Id;
273      Ref      : Node_Id);
274   --  Subsidiary to the analysis of pragmas [Refined_]Depends and [Refined_]
275   --  Global. Given an abstract state denoted by State_Id and a reference Ref
276   --  to it, determine whether the reference appears in a package body that
277   --  will eventually refine the state. If this is the case, record the
278   --  reference for future checks (see Analyze_Refined_State_In_Decls).
279
280   procedure Resolve_State (N : Node_Id);
281   --  Handle the overloading of state names by functions. When N denotes a
282   --  function, this routine finds the corresponding state and sets the entity
283   --  of N to that of the state.
284
285   procedure Rewrite_Assertion_Kind
286     (N           : Node_Id;
287      From_Policy : Boolean := False);
288   --  If N is Pre'Class, Post'Class, Invariant'Class, or Type_Invariant'Class,
289   --  then it is rewritten as an identifier with the corresponding special
290   --  name _Pre, _Post, _Invariant, or _Type_Invariant. Used by pragmas Check
291   --  and Check_Policy. If the names are Precondition or Postcondition, this
292   --  combination is deprecated in favor of Assertion_Policy and Ada2012
293   --  Aspect names. The parameter From_Policy indicates that the pragma
294   --  is the old non-standard Check_Policy and not a rewritten pragma.
295
296   procedure Set_Elab_Unit_Name (N : Node_Id; With_Item : Node_Id);
297   --  Place semantic information on the argument of an Elaborate/Elaborate_All
298   --  pragma. Entity name for unit and its parents is taken from item in
299   --  previous with_clause that mentions the unit.
300
301   Dummy : Integer := 0;
302   pragma Volatile (Dummy);
303   --  Dummy volatile integer used in bodies of ip/rv to prevent optimization
304
305   procedure ip;
306   pragma No_Inline (ip);
307   --  A dummy procedure called when pragma Inspection_Point is analyzed. This
308   --  is just to help debugging the front end. If a pragma Inspection_Point
309   --  is added to a source program, then breaking on ip will get you to that
310   --  point in the program.
311
312   procedure rv;
313   pragma No_Inline (rv);
314   --  This is a dummy function called by the processing for pragma Reviewable.
315   --  It is there for assisting front end debugging. By placing a Reviewable
316   --  pragma in the source program, a breakpoint on rv catches this place in
317   --  the source, allowing convenient stepping to the point of interest.
318
319   -------------------------------
320   -- Adjust_External_Name_Case --
321   -------------------------------
322
323   function Adjust_External_Name_Case (N : Node_Id) return Node_Id is
324      CC : Char_Code;
325
326   begin
327      --  Adjust case of literal if required
328
329      if Opt.External_Name_Exp_Casing = As_Is then
330         return N;
331
332      else
333         --  Copy existing string
334
335         Start_String;
336
337         --  Set proper casing
338
339         for J in 1 .. String_Length (Strval (N)) loop
340            CC := Get_String_Char (Strval (N), J);
341
342            if Opt.External_Name_Exp_Casing = Uppercase
343              and then CC >= Get_Char_Code ('a')
344              and then CC <= Get_Char_Code ('z')
345            then
346               Store_String_Char (CC - 32);
347
348            elsif Opt.External_Name_Exp_Casing = Lowercase
349              and then CC >= Get_Char_Code ('A')
350              and then CC <= Get_Char_Code ('Z')
351            then
352               Store_String_Char (CC + 32);
353
354            else
355               Store_String_Char (CC);
356            end if;
357         end loop;
358
359         return
360           Make_String_Literal (Sloc (N),
361             Strval => End_String);
362      end if;
363   end Adjust_External_Name_Case;
364
365   -----------------------------------------
366   -- Analyze_Contract_Cases_In_Decl_Part --
367   -----------------------------------------
368
369   --  WARNING: This routine manages Ghost regions. Return statements must be
370   --  replaced by gotos which jump to the end of the routine and restore the
371   --  Ghost mode.
372
373   procedure Analyze_Contract_Cases_In_Decl_Part
374     (N         : Node_Id;
375      Freeze_Id : Entity_Id := Empty)
376   is
377      Subp_Decl : constant Node_Id   := Find_Related_Declaration_Or_Body (N);
378      Spec_Id   : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
379
380      Others_Seen : Boolean := False;
381      --  This flag is set when an "others" choice is encountered. It is used
382      --  to detect multiple illegal occurrences of "others".
383
384      procedure Analyze_Contract_Case (CCase : Node_Id);
385      --  Verify the legality of a single contract case
386
387      ---------------------------
388      -- Analyze_Contract_Case --
389      ---------------------------
390
391      procedure Analyze_Contract_Case (CCase : Node_Id) is
392         Case_Guard  : Node_Id;
393         Conseq      : Node_Id;
394         Errors      : Nat;
395         Extra_Guard : Node_Id;
396
397      begin
398         if Nkind (CCase) = N_Component_Association then
399            Case_Guard := First (Choices (CCase));
400            Conseq     := Expression (CCase);
401
402            --  Each contract case must have exactly one case guard
403
404            Extra_Guard := Next (Case_Guard);
405
406            if Present (Extra_Guard) then
407               Error_Msg_N
408                 ("contract case must have exactly one case guard",
409                  Extra_Guard);
410            end if;
411
412            --  Check placement of OTHERS if available (SPARK RM 6.1.3(1))
413
414            if Nkind (Case_Guard) = N_Others_Choice then
415               if Others_Seen then
416                  Error_Msg_N
417                    ("only one others choice allowed in contract cases",
418                     Case_Guard);
419               else
420                  Others_Seen := True;
421               end if;
422
423            elsif Others_Seen then
424               Error_Msg_N
425                 ("others must be the last choice in contract cases", N);
426            end if;
427
428            --  Preanalyze the case guard and consequence
429
430            if Nkind (Case_Guard) /= N_Others_Choice then
431               Errors := Serious_Errors_Detected;
432               Preanalyze_Assert_Expression (Case_Guard, Standard_Boolean);
433
434               --  Emit a clarification message when the case guard contains
435               --  at least one undefined reference, possibly due to contract
436               --  freezing.
437
438               if Errors /= Serious_Errors_Detected
439                 and then Present (Freeze_Id)
440                 and then Has_Undefined_Reference (Case_Guard)
441               then
442                  Contract_Freeze_Error (Spec_Id, Freeze_Id);
443               end if;
444            end if;
445
446            Errors := Serious_Errors_Detected;
447            Preanalyze_Assert_Expression (Conseq, Standard_Boolean);
448
449            --  Emit a clarification message when the consequence contains
450            --  at least one undefined reference, possibly due to contract
451            --  freezing.
452
453            if Errors /= Serious_Errors_Detected
454              and then Present (Freeze_Id)
455              and then Has_Undefined_Reference (Conseq)
456            then
457               Contract_Freeze_Error (Spec_Id, Freeze_Id);
458            end if;
459
460         --  The contract case is malformed
461
462         else
463            Error_Msg_N ("wrong syntax in contract case", CCase);
464         end if;
465      end Analyze_Contract_Case;
466
467      --  Local variables
468
469      CCases : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
470
471      Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
472      --  Save the Ghost mode to restore on exit
473
474      CCase         : Node_Id;
475      Restore_Scope : Boolean := False;
476
477   --  Start of processing for Analyze_Contract_Cases_In_Decl_Part
478
479   begin
480      --  Do not analyze the pragma multiple times
481
482      if Is_Analyzed_Pragma (N) then
483         return;
484      end if;
485
486      --  Set the Ghost mode in effect from the pragma. Due to the delayed
487      --  analysis of the pragma, the Ghost mode at point of declaration and
488      --  point of analysis may not necessarily be the same. Use the mode in
489      --  effect at the point of declaration.
490
491      Set_Ghost_Mode (N);
492
493      --  Single and multiple contract cases must appear in aggregate form. If
494      --  this is not the case, then either the parser of the analysis of the
495      --  pragma failed to produce an aggregate.
496
497      pragma Assert (Nkind (CCases) = N_Aggregate);
498
499      if Present (Component_Associations (CCases)) then
500
501         --  Ensure that the formal parameters are visible when analyzing all
502         --  clauses. This falls out of the general rule of aspects pertaining
503         --  to subprogram declarations.
504
505         if not In_Open_Scopes (Spec_Id) then
506            Restore_Scope := True;
507            Push_Scope (Spec_Id);
508
509            if Is_Generic_Subprogram (Spec_Id) then
510               Install_Generic_Formals (Spec_Id);
511            else
512               Install_Formals (Spec_Id);
513            end if;
514         end if;
515
516         CCase := First (Component_Associations (CCases));
517         while Present (CCase) loop
518            Analyze_Contract_Case (CCase);
519            Next (CCase);
520         end loop;
521
522         if Restore_Scope then
523            End_Scope;
524         end if;
525
526         --  Currently it is not possible to inline pre/postconditions on a
527         --  subprogram subject to pragma Inline_Always.
528
529         Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
530
531      --  Otherwise the pragma is illegal
532
533      else
534         Error_Msg_N ("wrong syntax for constract cases", N);
535      end if;
536
537      Set_Is_Analyzed_Pragma (N);
538
539      Restore_Ghost_Mode (Saved_GM);
540   end Analyze_Contract_Cases_In_Decl_Part;
541
542   ----------------------------------
543   -- Analyze_Depends_In_Decl_Part --
544   ----------------------------------
545
546   procedure Analyze_Depends_In_Decl_Part (N : Node_Id) is
547      Loc       : constant Source_Ptr := Sloc (N);
548      Subp_Decl : constant Node_Id    := Find_Related_Declaration_Or_Body (N);
549      Spec_Id   : constant Entity_Id  := Unique_Defining_Entity (Subp_Decl);
550
551      All_Inputs_Seen : Elist_Id := No_Elist;
552      --  A list containing the entities of all the inputs processed so far.
553      --  The list is populated with unique entities because the same input
554      --  may appear in multiple input lists.
555
556      All_Outputs_Seen : Elist_Id := No_Elist;
557      --  A list containing the entities of all the outputs processed so far.
558      --  The list is populated with unique entities because output items are
559      --  unique in a dependence relation.
560
561      Constits_Seen : Elist_Id := No_Elist;
562      --  A list containing the entities of all constituents processed so far.
563      --  It aids in detecting illegal usage of a state and a corresponding
564      --  constituent in pragma [Refinde_]Depends.
565
566      Global_Seen : Boolean := False;
567      --  A flag set when pragma Global has been processed
568
569      Null_Output_Seen : Boolean := False;
570      --  A flag used to track the legality of a null output
571
572      Result_Seen : Boolean := False;
573      --  A flag set when Spec_Id'Result is processed
574
575      States_Seen : Elist_Id := No_Elist;
576      --  A list containing the entities of all states processed so far. It
577      --  helps in detecting illegal usage of a state and a corresponding
578      --  constituent in pragma [Refined_]Depends.
579
580      Subp_Inputs  : Elist_Id := No_Elist;
581      Subp_Outputs : Elist_Id := No_Elist;
582      --  Two lists containing the full set of inputs and output of the related
583      --  subprograms. Note that these lists contain both nodes and entities.
584
585      Task_Input_Seen  : Boolean := False;
586      Task_Output_Seen : Boolean := False;
587      --  Flags used to track the implicit dependence of a task unit on itself
588
589      procedure Add_Item_To_Name_Buffer (Item_Id : Entity_Id);
590      --  Subsidiary routine to Check_Role and Check_Usage. Add the item kind
591      --  to the name buffer. The individual kinds are as follows:
592      --    E_Abstract_State           - "state"
593      --    E_Constant                 - "constant"
594      --    E_Generic_In_Out_Parameter - "generic parameter"
595      --    E_Generic_In_Parameter     - "generic parameter"
596      --    E_In_Parameter             - "parameter"
597      --    E_In_Out_Parameter         - "parameter"
598      --    E_Loop_Parameter           - "loop parameter"
599      --    E_Out_Parameter            - "parameter"
600      --    E_Protected_Type           - "current instance of protected type"
601      --    E_Task_Type                - "current instance of task type"
602      --    E_Variable                 - "global"
603
604      procedure Analyze_Dependency_Clause
605        (Clause  : Node_Id;
606         Is_Last : Boolean);
607      --  Verify the legality of a single dependency clause. Flag Is_Last
608      --  denotes whether Clause is the last clause in the relation.
609
610      procedure Check_Function_Return;
611      --  Verify that Funtion'Result appears as one of the outputs
612      --  (SPARK RM 6.1.5(10)).
613
614      procedure Check_Role
615        (Item     : Node_Id;
616         Item_Id  : Entity_Id;
617         Is_Input : Boolean;
618         Self_Ref : Boolean);
619      --  Ensure that an item fulfills its designated input and/or output role
620      --  as specified by pragma Global (if any) or the enclosing context. If
621      --  this is not the case, emit an error. Item and Item_Id denote the
622      --  attributes of an item. Flag Is_Input should be set when item comes
623      --  from an input list. Flag Self_Ref should be set when the item is an
624      --  output and the dependency clause has operator "+".
625
626      procedure Check_Usage
627        (Subp_Items : Elist_Id;
628         Used_Items : Elist_Id;
629         Is_Input   : Boolean);
630      --  Verify that all items from Subp_Items appear in Used_Items. Emit an
631      --  error if this is not the case.
632
633      procedure Normalize_Clause (Clause : Node_Id);
634      --  Remove a self-dependency "+" from the input list of a clause
635
636      -----------------------------
637      -- Add_Item_To_Name_Buffer --
638      -----------------------------
639
640      procedure Add_Item_To_Name_Buffer (Item_Id : Entity_Id) is
641      begin
642         if Ekind (Item_Id) = E_Abstract_State then
643            Add_Str_To_Name_Buffer ("state");
644
645         elsif Ekind (Item_Id) = E_Constant then
646            Add_Str_To_Name_Buffer ("constant");
647
648         elsif Ekind_In (Item_Id, E_Generic_In_Out_Parameter,
649                                  E_Generic_In_Parameter)
650         then
651            Add_Str_To_Name_Buffer ("generic parameter");
652
653         elsif Is_Formal (Item_Id) then
654            Add_Str_To_Name_Buffer ("parameter");
655
656         elsif Ekind (Item_Id) = E_Loop_Parameter then
657            Add_Str_To_Name_Buffer ("loop parameter");
658
659         elsif Ekind (Item_Id) = E_Protected_Type
660           or else Is_Single_Protected_Object (Item_Id)
661         then
662            Add_Str_To_Name_Buffer ("current instance of protected type");
663
664         elsif Ekind (Item_Id) = E_Task_Type
665           or else Is_Single_Task_Object (Item_Id)
666         then
667            Add_Str_To_Name_Buffer ("current instance of task type");
668
669         elsif Ekind (Item_Id) = E_Variable then
670            Add_Str_To_Name_Buffer ("global");
671
672         --  The routine should not be called with non-SPARK items
673
674         else
675            raise Program_Error;
676         end if;
677      end Add_Item_To_Name_Buffer;
678
679      -------------------------------
680      -- Analyze_Dependency_Clause --
681      -------------------------------
682
683      procedure Analyze_Dependency_Clause
684        (Clause  : Node_Id;
685         Is_Last : Boolean)
686      is
687         procedure Analyze_Input_List (Inputs : Node_Id);
688         --  Verify the legality of a single input list
689
690         procedure Analyze_Input_Output
691           (Item          : Node_Id;
692            Is_Input      : Boolean;
693            Self_Ref      : Boolean;
694            Top_Level     : Boolean;
695            Seen          : in out Elist_Id;
696            Null_Seen     : in out Boolean;
697            Non_Null_Seen : in out Boolean);
698         --  Verify the legality of a single input or output item. Flag
699         --  Is_Input should be set whenever Item is an input, False when it
700         --  denotes an output. Flag Self_Ref should be set when the item is an
701         --  output and the dependency clause has a "+". Flag Top_Level should
702         --  be set whenever Item appears immediately within an input or output
703         --  list. Seen is a collection of all abstract states, objects and
704         --  formals processed so far. Flag Null_Seen denotes whether a null
705         --  input or output has been encountered. Flag Non_Null_Seen denotes
706         --  whether a non-null input or output has been encountered.
707
708         ------------------------
709         -- Analyze_Input_List --
710         ------------------------
711
712         procedure Analyze_Input_List (Inputs : Node_Id) is
713            Inputs_Seen : Elist_Id := No_Elist;
714            --  A list containing the entities of all inputs that appear in the
715            --  current input list.
716
717            Non_Null_Input_Seen : Boolean := False;
718            Null_Input_Seen     : Boolean := False;
719            --  Flags used to check the legality of an input list
720
721            Input : Node_Id;
722
723         begin
724            --  Multiple inputs appear as an aggregate
725
726            if Nkind (Inputs) = N_Aggregate then
727               if Present (Component_Associations (Inputs)) then
728                  SPARK_Msg_N
729                    ("nested dependency relations not allowed", Inputs);
730
731               elsif Present (Expressions (Inputs)) then
732                  Input := First (Expressions (Inputs));
733                  while Present (Input) loop
734                     Analyze_Input_Output
735                       (Item          => Input,
736                        Is_Input      => True,
737                        Self_Ref      => False,
738                        Top_Level     => False,
739                        Seen          => Inputs_Seen,
740                        Null_Seen     => Null_Input_Seen,
741                        Non_Null_Seen => Non_Null_Input_Seen);
742
743                     Next (Input);
744                  end loop;
745
746               --  Syntax error, always report
747
748               else
749                  Error_Msg_N ("malformed input dependency list", Inputs);
750               end if;
751
752            --  Process a solitary input
753
754            else
755               Analyze_Input_Output
756                 (Item          => Inputs,
757                  Is_Input      => True,
758                  Self_Ref      => False,
759                  Top_Level     => False,
760                  Seen          => Inputs_Seen,
761                  Null_Seen     => Null_Input_Seen,
762                  Non_Null_Seen => Non_Null_Input_Seen);
763            end if;
764
765            --  Detect an illegal dependency clause of the form
766
767            --    (null =>[+] null)
768
769            if Null_Output_Seen and then Null_Input_Seen then
770               SPARK_Msg_N
771                 ("null dependency clause cannot have a null input list",
772                  Inputs);
773            end if;
774         end Analyze_Input_List;
775
776         --------------------------
777         -- Analyze_Input_Output --
778         --------------------------
779
780         procedure Analyze_Input_Output
781           (Item          : Node_Id;
782            Is_Input      : Boolean;
783            Self_Ref      : Boolean;
784            Top_Level     : Boolean;
785            Seen          : in out Elist_Id;
786            Null_Seen     : in out Boolean;
787            Non_Null_Seen : in out Boolean)
788         is
789            procedure Current_Task_Instance_Seen;
790            --  Set the appropriate global flag when the current instance of a
791            --  task unit is encountered.
792
793            --------------------------------
794            -- Current_Task_Instance_Seen --
795            --------------------------------
796
797            procedure Current_Task_Instance_Seen is
798            begin
799               if Is_Input then
800                  Task_Input_Seen := True;
801               else
802                  Task_Output_Seen := True;
803               end if;
804            end Current_Task_Instance_Seen;
805
806            --  Local variables
807
808            Is_Output : constant Boolean := not Is_Input;
809            Grouped   : Node_Id;
810            Item_Id   : Entity_Id;
811
812         --  Start of processing for Analyze_Input_Output
813
814         begin
815            --  Multiple input or output items appear as an aggregate
816
817            if Nkind (Item) = N_Aggregate then
818               if not Top_Level then
819                  SPARK_Msg_N ("nested grouping of items not allowed", Item);
820
821               elsif Present (Component_Associations (Item)) then
822                  SPARK_Msg_N
823                    ("nested dependency relations not allowed", Item);
824
825               --  Recursively analyze the grouped items
826
827               elsif Present (Expressions (Item)) then
828                  Grouped := First (Expressions (Item));
829                  while Present (Grouped) loop
830                     Analyze_Input_Output
831                       (Item          => Grouped,
832                        Is_Input      => Is_Input,
833                        Self_Ref      => Self_Ref,
834                        Top_Level     => False,
835                        Seen          => Seen,
836                        Null_Seen     => Null_Seen,
837                        Non_Null_Seen => Non_Null_Seen);
838
839                     Next (Grouped);
840                  end loop;
841
842               --  Syntax error, always report
843
844               else
845                  Error_Msg_N ("malformed dependency list", Item);
846               end if;
847
848            --  Process attribute 'Result in the context of a dependency clause
849
850            elsif Is_Attribute_Result (Item) then
851               Non_Null_Seen := True;
852
853               Analyze (Item);
854
855               --  Attribute 'Result is allowed to appear on the output side of
856               --  a dependency clause (SPARK RM 6.1.5(6)).
857
858               if Is_Input then
859                  SPARK_Msg_N ("function result cannot act as input", Item);
860
861               elsif Null_Seen then
862                  SPARK_Msg_N
863                    ("cannot mix null and non-null dependency items", Item);
864
865               else
866                  Result_Seen := True;
867               end if;
868
869            --  Detect multiple uses of null in a single dependency list or
870            --  throughout the whole relation. Verify the placement of a null
871            --  output list relative to the other clauses (SPARK RM 6.1.5(12)).
872
873            elsif Nkind (Item) = N_Null then
874               if Null_Seen then
875                  SPARK_Msg_N
876                    ("multiple null dependency relations not allowed", Item);
877
878               elsif Non_Null_Seen then
879                  SPARK_Msg_N
880                    ("cannot mix null and non-null dependency items", Item);
881
882               else
883                  Null_Seen := True;
884
885                  if Is_Output then
886                     if not Is_Last then
887                        SPARK_Msg_N
888                          ("null output list must be the last clause in a "
889                           & "dependency relation", Item);
890
891                     --  Catch a useless dependence of the form:
892                     --    null =>+ ...
893
894                     elsif Self_Ref then
895                        SPARK_Msg_N
896                          ("useless dependence, null depends on itself", Item);
897                     end if;
898                  end if;
899               end if;
900
901            --  Default case
902
903            else
904               Non_Null_Seen := True;
905
906               if Null_Seen then
907                  SPARK_Msg_N ("cannot mix null and non-null items", Item);
908               end if;
909
910               Analyze       (Item);
911               Resolve_State (Item);
912
913               --  Find the entity of the item. If this is a renaming, climb
914               --  the renaming chain to reach the root object. Renamings of
915               --  non-entire objects do not yield an entity (Empty).
916
917               Item_Id := Entity_Of (Item);
918
919               if Present (Item_Id) then
920
921                  --  Constants
922
923                  if Ekind_In (Item_Id, E_Constant, E_Loop_Parameter)
924                      or else
925
926                    --  Current instances of concurrent types
927
928                    Ekind_In (Item_Id, E_Protected_Type, E_Task_Type)
929                      or else
930
931                    --  Formal parameters
932
933                    Ekind_In (Item_Id, E_Generic_In_Out_Parameter,
934                                       E_Generic_In_Parameter,
935                                       E_In_Parameter,
936                                       E_In_Out_Parameter,
937                                       E_Out_Parameter)
938                      or else
939
940                    --  States, variables
941
942                    Ekind_In (Item_Id, E_Abstract_State, E_Variable)
943                  then
944                     --  The item denotes a concurrent type. Note that single
945                     --  protected/task types are not considered here because
946                     --  they behave as objects in the context of pragma
947                     --  [Refined_]Depends.
948
949                     if Ekind_In (Item_Id, E_Protected_Type, E_Task_Type) then
950
951                        --  This use is legal as long as the concurrent type is
952                        --  the current instance of an enclosing type.
953
954                        if Is_CCT_Instance (Item_Id, Spec_Id) then
955
956                           --  The dependence of a task unit on itself is
957                           --  implicit and may or may not be explicitly
958                           --  specified (SPARK RM 6.1.4).
959
960                           if Ekind (Item_Id) = E_Task_Type then
961                              Current_Task_Instance_Seen;
962                           end if;
963
964                        --  Otherwise this is not the current instance
965
966                        else
967                           SPARK_Msg_N
968                             ("invalid use of subtype mark in dependency "
969                              & "relation", Item);
970                        end if;
971
972                     --  The dependency of a task unit on itself is implicit
973                     --  and may or may not be explicitly specified
974                     --  (SPARK RM 6.1.4).
975
976                     elsif Is_Single_Task_Object (Item_Id)
977                       and then Is_CCT_Instance (Etype (Item_Id), Spec_Id)
978                     then
979                        Current_Task_Instance_Seen;
980                     end if;
981
982                     --  Ensure that the item fulfills its role as input and/or
983                     --  output as specified by pragma Global or the enclosing
984                     --  context.
985
986                     Check_Role (Item, Item_Id, Is_Input, Self_Ref);
987
988                     --  Detect multiple uses of the same state, variable or
989                     --  formal parameter. If this is not the case, add the
990                     --  item to the list of processed relations.
991
992                     if Contains (Seen, Item_Id) then
993                        SPARK_Msg_NE
994                          ("duplicate use of item &", Item, Item_Id);
995                     else
996                        Append_New_Elmt (Item_Id, Seen);
997                     end if;
998
999                     --  Detect illegal use of an input related to a null
1000                     --  output. Such input items cannot appear in other
1001                     --  input lists (SPARK RM 6.1.5(13)).
1002
1003                     if Is_Input
1004                       and then Null_Output_Seen
1005                       and then Contains (All_Inputs_Seen, Item_Id)
1006                     then
1007                        SPARK_Msg_N
1008                          ("input of a null output list cannot appear in "
1009                           & "multiple input lists", Item);
1010                     end if;
1011
1012                     --  Add an input or a self-referential output to the list
1013                     --  of all processed inputs.
1014
1015                     if Is_Input or else Self_Ref then
1016                        Append_New_Elmt (Item_Id, All_Inputs_Seen);
1017                     end if;
1018
1019                     --  State related checks (SPARK RM 6.1.5(3))
1020
1021                     if Ekind (Item_Id) = E_Abstract_State then
1022
1023                        --  Package and subprogram bodies are instantiated
1024                        --  individually in a separate compiler pass. Due to
1025                        --  this mode of instantiation, the refinement of a
1026                        --  state may no longer be visible when a subprogram
1027                        --  body contract is instantiated. Since the generic
1028                        --  template is legal, do not perform this check in
1029                        --  the instance to circumvent this oddity.
1030
1031                        if Is_Generic_Instance (Spec_Id) then
1032                           null;
1033
1034                        --  An abstract state with visible refinement cannot
1035                        --  appear in pragma [Refined_]Depends as its place
1036                        --  must be taken by some of its constituents
1037                        --  (SPARK RM 6.1.4(7)).
1038
1039                        elsif Has_Visible_Refinement (Item_Id) then
1040                           SPARK_Msg_NE
1041                             ("cannot mention state & in dependence relation",
1042                              Item, Item_Id);
1043                           SPARK_Msg_N ("\use its constituents instead", Item);
1044                           return;
1045
1046                        --  If the reference to the abstract state appears in
1047                        --  an enclosing package body that will eventually
1048                        --  refine the state, record the reference for future
1049                        --  checks.
1050
1051                        else
1052                           Record_Possible_Body_Reference
1053                             (State_Id => Item_Id,
1054                              Ref      => Item);
1055                        end if;
1056                     end if;
1057
1058                     --  When the item renames an entire object, replace the
1059                     --  item with a reference to the object.
1060
1061                     if Entity (Item) /= Item_Id then
1062                        Rewrite (Item,
1063                          New_Occurrence_Of (Item_Id, Sloc (Item)));
1064                        Analyze (Item);
1065                     end if;
1066
1067                     --  Add the entity of the current item to the list of
1068                     --  processed items.
1069
1070                     if Ekind (Item_Id) = E_Abstract_State then
1071                        Append_New_Elmt (Item_Id, States_Seen);
1072
1073                     --  The variable may eventually become a constituent of a
1074                     --  single protected/task type. Record the reference now
1075                     --  and verify its legality when analyzing the contract of
1076                     --  the variable (SPARK RM 9.3).
1077
1078                     elsif Ekind (Item_Id) = E_Variable then
1079                        Record_Possible_Part_Of_Reference
1080                          (Var_Id => Item_Id,
1081                           Ref    => Item);
1082                     end if;
1083
1084                     if Ekind_In (Item_Id, E_Abstract_State,
1085                                           E_Constant,
1086                                           E_Variable)
1087                       and then Present (Encapsulating_State (Item_Id))
1088                     then
1089                        Append_New_Elmt (Item_Id, Constits_Seen);
1090                     end if;
1091
1092                  --  All other input/output items are illegal
1093                  --  (SPARK RM 6.1.5(1)).
1094
1095                  else
1096                     SPARK_Msg_N
1097                       ("item must denote parameter, variable, state or "
1098                        & "current instance of concurrent type", Item);
1099                  end if;
1100
1101               --  All other input/output items are illegal
1102               --  (SPARK RM 6.1.5(1)). This is a syntax error, always report.
1103
1104               else
1105                  Error_Msg_N
1106                    ("item must denote parameter, variable, state or current "
1107                     & "instance of concurrent type", Item);
1108               end if;
1109            end if;
1110         end Analyze_Input_Output;
1111
1112         --  Local variables
1113
1114         Inputs   : Node_Id;
1115         Output   : Node_Id;
1116         Self_Ref : Boolean;
1117
1118         Non_Null_Output_Seen : Boolean := False;
1119         --  Flag used to check the legality of an output list
1120
1121      --  Start of processing for Analyze_Dependency_Clause
1122
1123      begin
1124         Inputs   := Expression (Clause);
1125         Self_Ref := False;
1126
1127         --  An input list with a self-dependency appears as operator "+" where
1128         --  the actuals inputs are the right operand.
1129
1130         if Nkind (Inputs) = N_Op_Plus then
1131            Inputs   := Right_Opnd (Inputs);
1132            Self_Ref := True;
1133         end if;
1134
1135         --  Process the output_list of a dependency_clause
1136
1137         Output := First (Choices (Clause));
1138         while Present (Output) loop
1139            Analyze_Input_Output
1140              (Item          => Output,
1141               Is_Input      => False,
1142               Self_Ref      => Self_Ref,
1143               Top_Level     => True,
1144               Seen          => All_Outputs_Seen,
1145               Null_Seen     => Null_Output_Seen,
1146               Non_Null_Seen => Non_Null_Output_Seen);
1147
1148            Next (Output);
1149         end loop;
1150
1151         --  Process the input_list of a dependency_clause
1152
1153         Analyze_Input_List (Inputs);
1154      end Analyze_Dependency_Clause;
1155
1156      ---------------------------
1157      -- Check_Function_Return --
1158      ---------------------------
1159
1160      procedure Check_Function_Return is
1161      begin
1162         if Ekind_In (Spec_Id, E_Function, E_Generic_Function)
1163           and then not Result_Seen
1164         then
1165            SPARK_Msg_NE
1166              ("result of & must appear in exactly one output list",
1167               N, Spec_Id);
1168         end if;
1169      end Check_Function_Return;
1170
1171      ----------------
1172      -- Check_Role --
1173      ----------------
1174
1175      procedure Check_Role
1176        (Item     : Node_Id;
1177         Item_Id  : Entity_Id;
1178         Is_Input : Boolean;
1179         Self_Ref : Boolean)
1180      is
1181         procedure Find_Role
1182           (Item_Is_Input  : out Boolean;
1183            Item_Is_Output : out Boolean);
1184         --  Find the input/output role of Item_Id. Flags Item_Is_Input and
1185         --  Item_Is_Output are set depending on the role.
1186
1187         procedure Role_Error
1188           (Item_Is_Input  : Boolean;
1189            Item_Is_Output : Boolean);
1190         --  Emit an error message concerning the incorrect use of Item in
1191         --  pragma [Refined_]Depends. Flags Item_Is_Input and Item_Is_Output
1192         --  denote whether the item is an input and/or an output.
1193
1194         ---------------
1195         -- Find_Role --
1196         ---------------
1197
1198         procedure Find_Role
1199           (Item_Is_Input  : out Boolean;
1200            Item_Is_Output : out Boolean)
1201         is
1202         begin
1203            case Ekind (Item_Id) is
1204
1205               --  Abstract states
1206
1207               when E_Abstract_State =>
1208
1209                  --  When pragma Global is present it determines the mode of
1210                  --  the abstract state.
1211
1212                  if Global_Seen then
1213                     Item_Is_Input  := Appears_In (Subp_Inputs, Item_Id);
1214                     Item_Is_Output := Appears_In (Subp_Outputs, Item_Id);
1215
1216                  --  Otherwise the state has a default IN OUT mode, because it
1217                  --  behaves as a variable.
1218
1219                  else
1220                     Item_Is_Input  := True;
1221                     Item_Is_Output := True;
1222                  end if;
1223
1224               --  Constants and IN parameters
1225
1226               when E_Constant
1227                  | E_Generic_In_Parameter
1228                  | E_In_Parameter
1229                  | E_Loop_Parameter
1230               =>
1231                  --  When pragma Global is present it determines the mode
1232                  --  of constant objects as inputs (and such objects cannot
1233                  --  appear as outputs in the Global contract).
1234
1235                  if Global_Seen then
1236                     Item_Is_Input := Appears_In (Subp_Inputs, Item_Id);
1237                  else
1238                     Item_Is_Input := True;
1239                  end if;
1240
1241                  Item_Is_Output := False;
1242
1243               --  Variables and IN OUT parameters
1244
1245               when E_Generic_In_Out_Parameter
1246                  | E_In_Out_Parameter
1247                  | E_Variable
1248               =>
1249                  --  When pragma Global is present it determines the mode of
1250                  --  the object.
1251
1252                  if Global_Seen then
1253
1254                     --  A variable has mode IN when its type is unconstrained
1255                     --  or tagged because array bounds, discriminants or tags
1256                     --  can be read.
1257
1258                     Item_Is_Input :=
1259                       Appears_In (Subp_Inputs, Item_Id)
1260                         or else Is_Unconstrained_Or_Tagged_Item (Item_Id);
1261
1262                     Item_Is_Output := Appears_In (Subp_Outputs, Item_Id);
1263
1264                  --  Otherwise the variable has a default IN OUT mode
1265
1266                  else
1267                     Item_Is_Input  := True;
1268                     Item_Is_Output := True;
1269                  end if;
1270
1271               when E_Out_Parameter =>
1272
1273                  --  An OUT parameter of the related subprogram; it cannot
1274                  --  appear in Global.
1275
1276                  if Scope (Item_Id) = Spec_Id then
1277
1278                     --  The parameter has mode IN if its type is unconstrained
1279                     --  or tagged because array bounds, discriminants or tags
1280                     --  can be read.
1281
1282                     Item_Is_Input :=
1283                       Is_Unconstrained_Or_Tagged_Item (Item_Id);
1284
1285                     Item_Is_Output := True;
1286
1287                  --  An OUT parameter of an enclosing subprogram; it can
1288                  --  appear in Global and behaves as a read-write variable.
1289
1290                  else
1291                     --  When pragma Global is present it determines the mode
1292                     --  of the object.
1293
1294                     if Global_Seen then
1295
1296                        --  A variable has mode IN when its type is
1297                        --  unconstrained or tagged because array
1298                        --  bounds, discriminants or tags can be read.
1299
1300                        Item_Is_Input :=
1301                          Appears_In (Subp_Inputs, Item_Id)
1302                            or else Is_Unconstrained_Or_Tagged_Item (Item_Id);
1303
1304                        Item_Is_Output := Appears_In (Subp_Outputs, Item_Id);
1305
1306                     --  Otherwise the variable has a default IN OUT mode
1307
1308                     else
1309                        Item_Is_Input  := True;
1310                        Item_Is_Output := True;
1311                     end if;
1312                  end if;
1313
1314               --  Protected types
1315
1316               when E_Protected_Type =>
1317                  if Global_Seen then
1318
1319                     --  A variable has mode IN when its type is unconstrained
1320                     --  or tagged because array bounds, discriminants or tags
1321                     --  can be read.
1322
1323                     Item_Is_Input :=
1324                       Appears_In (Subp_Inputs, Item_Id)
1325                         or else Is_Unconstrained_Or_Tagged_Item (Item_Id);
1326
1327                     Item_Is_Output := Appears_In (Subp_Outputs, Item_Id);
1328
1329                  else
1330                     --  A protected type acts as a formal parameter of mode IN
1331                     --  when it applies to a protected function.
1332
1333                     if Ekind (Spec_Id) = E_Function then
1334                        Item_Is_Input  := True;
1335                        Item_Is_Output := False;
1336
1337                     --  Otherwise the protected type acts as a formal of mode
1338                     --  IN OUT.
1339
1340                     else
1341                        Item_Is_Input  := True;
1342                        Item_Is_Output := True;
1343                     end if;
1344                  end if;
1345
1346               --  Task types
1347
1348               when E_Task_Type =>
1349
1350                  --  When pragma Global is present it determines the mode of
1351                  --  the object.
1352
1353                  if Global_Seen then
1354                     Item_Is_Input :=
1355                       Appears_In (Subp_Inputs, Item_Id)
1356                         or else Is_Unconstrained_Or_Tagged_Item (Item_Id);
1357
1358                     Item_Is_Output := Appears_In (Subp_Outputs, Item_Id);
1359
1360                  --  Otherwise task types act as IN OUT parameters
1361
1362                  else
1363                     Item_Is_Input  := True;
1364                     Item_Is_Output := True;
1365                  end if;
1366
1367               when others =>
1368                  raise Program_Error;
1369            end case;
1370         end Find_Role;
1371
1372         ----------------
1373         -- Role_Error --
1374         ----------------
1375
1376         procedure Role_Error
1377           (Item_Is_Input  : Boolean;
1378            Item_Is_Output : Boolean)
1379         is
1380            Error_Msg : Name_Id;
1381
1382         begin
1383            Name_Len := 0;
1384
1385            --  When the item is not part of the input and the output set of
1386            --  the related subprogram, then it appears as extra in pragma
1387            --  [Refined_]Depends.
1388
1389            if not Item_Is_Input and then not Item_Is_Output then
1390               Add_Item_To_Name_Buffer (Item_Id);
1391               Add_Str_To_Name_Buffer
1392                 (" & cannot appear in dependence relation");
1393
1394               Error_Msg := Name_Find;
1395               SPARK_Msg_NE (Get_Name_String (Error_Msg), Item, Item_Id);
1396
1397               Error_Msg_Name_1 := Chars (Spec_Id);
1398               SPARK_Msg_NE
1399                 (Fix_Msg (Spec_Id, "\& is not part of the input or output "
1400                  & "set of subprogram %"), Item, Item_Id);
1401
1402            --  The mode of the item and its role in pragma [Refined_]Depends
1403            --  are in conflict. Construct a detailed message explaining the
1404            --  illegality (SPARK RM 6.1.5(5-6)).
1405
1406            else
1407               if Item_Is_Input then
1408                  Add_Str_To_Name_Buffer ("read-only");
1409               else
1410                  Add_Str_To_Name_Buffer ("write-only");
1411               end if;
1412
1413               Add_Char_To_Name_Buffer (' ');
1414               Add_Item_To_Name_Buffer (Item_Id);
1415               Add_Str_To_Name_Buffer  (" & cannot appear as ");
1416
1417               if Item_Is_Input then
1418                  Add_Str_To_Name_Buffer ("output");
1419               else
1420                  Add_Str_To_Name_Buffer ("input");
1421               end if;
1422
1423               Add_Str_To_Name_Buffer (" in dependence relation");
1424               Error_Msg := Name_Find;
1425               SPARK_Msg_NE (Get_Name_String (Error_Msg), Item, Item_Id);
1426            end if;
1427         end Role_Error;
1428
1429         --  Local variables
1430
1431         Item_Is_Input  : Boolean;
1432         Item_Is_Output : Boolean;
1433
1434      --  Start of processing for Check_Role
1435
1436      begin
1437         Find_Role (Item_Is_Input, Item_Is_Output);
1438
1439         --  Input item
1440
1441         if Is_Input then
1442            if not Item_Is_Input then
1443               Role_Error (Item_Is_Input, Item_Is_Output);
1444            end if;
1445
1446         --  Self-referential item
1447
1448         elsif Self_Ref then
1449            if not Item_Is_Input or else not Item_Is_Output then
1450               Role_Error (Item_Is_Input, Item_Is_Output);
1451            end if;
1452
1453         --  Output item
1454
1455         elsif not Item_Is_Output then
1456            Role_Error (Item_Is_Input, Item_Is_Output);
1457         end if;
1458      end Check_Role;
1459
1460      -----------------
1461      -- Check_Usage --
1462      -----------------
1463
1464      procedure Check_Usage
1465        (Subp_Items : Elist_Id;
1466         Used_Items : Elist_Id;
1467         Is_Input   : Boolean)
1468      is
1469         procedure Usage_Error (Item_Id : Entity_Id);
1470         --  Emit an error concerning the illegal usage of an item
1471
1472         -----------------
1473         -- Usage_Error --
1474         -----------------
1475
1476         procedure Usage_Error (Item_Id : Entity_Id) is
1477            Error_Msg : Name_Id;
1478
1479         begin
1480            --  Input case
1481
1482            if Is_Input then
1483
1484               --  Unconstrained and tagged items are not part of the explicit
1485               --  input set of the related subprogram, they do not have to be
1486               --  present in a dependence relation and should not be flagged
1487               --  (SPARK RM 6.1.5(5)).
1488
1489               if not Is_Unconstrained_Or_Tagged_Item (Item_Id) then
1490                  Name_Len := 0;
1491
1492                  Add_Item_To_Name_Buffer (Item_Id);
1493                  Add_Str_To_Name_Buffer
1494                    (" & is missing from input dependence list");
1495
1496                  Error_Msg := Name_Find;
1497                  SPARK_Msg_NE (Get_Name_String (Error_Msg), N, Item_Id);
1498                  SPARK_Msg_NE
1499                    ("\add `null ='> &` dependency to ignore this input",
1500                     N, Item_Id);
1501               end if;
1502
1503            --  Output case (SPARK RM 6.1.5(10))
1504
1505            else
1506               Name_Len := 0;
1507
1508               Add_Item_To_Name_Buffer (Item_Id);
1509               Add_Str_To_Name_Buffer
1510                 (" & is missing from output dependence list");
1511
1512               Error_Msg := Name_Find;
1513               SPARK_Msg_NE (Get_Name_String (Error_Msg), N, Item_Id);
1514            end if;
1515         end Usage_Error;
1516
1517         --  Local variables
1518
1519         Elmt    : Elmt_Id;
1520         Item    : Node_Id;
1521         Item_Id : Entity_Id;
1522
1523      --  Start of processing for Check_Usage
1524
1525      begin
1526         if No (Subp_Items) then
1527            return;
1528         end if;
1529
1530         --  Each input or output of the subprogram must appear in a dependency
1531         --  relation.
1532
1533         Elmt := First_Elmt (Subp_Items);
1534         while Present (Elmt) loop
1535            Item := Node (Elmt);
1536
1537            if Nkind (Item) = N_Defining_Identifier then
1538               Item_Id := Item;
1539            else
1540               Item_Id := Entity_Of (Item);
1541            end if;
1542
1543            --  The item does not appear in a dependency
1544
1545            if Present (Item_Id)
1546              and then not Contains (Used_Items, Item_Id)
1547            then
1548               if Is_Formal (Item_Id) then
1549                  Usage_Error (Item_Id);
1550
1551               --  The current instance of a protected type behaves as a formal
1552               --  parameter (SPARK RM 6.1.4).
1553
1554               elsif Ekind (Item_Id) = E_Protected_Type
1555                 or else Is_Single_Protected_Object (Item_Id)
1556               then
1557                  Usage_Error (Item_Id);
1558
1559               --  The current instance of a task type behaves as a formal
1560               --  parameter (SPARK RM 6.1.4).
1561
1562               elsif Ekind (Item_Id) = E_Task_Type
1563                 or else Is_Single_Task_Object (Item_Id)
1564               then
1565                  --  The dependence of a task unit on itself is implicit and
1566                  --  may or may not be explicitly specified (SPARK RM 6.1.4).
1567                  --  Emit an error if only one input/output is present.
1568
1569                  if Task_Input_Seen /= Task_Output_Seen then
1570                     Usage_Error (Item_Id);
1571                  end if;
1572
1573               --  States and global objects are not used properly only when
1574               --  the subprogram is subject to pragma Global.
1575
1576               elsif Global_Seen then
1577                  Usage_Error (Item_Id);
1578               end if;
1579            end if;
1580
1581            Next_Elmt (Elmt);
1582         end loop;
1583      end Check_Usage;
1584
1585      ----------------------
1586      -- Normalize_Clause --
1587      ----------------------
1588
1589      procedure Normalize_Clause (Clause : Node_Id) is
1590         procedure Create_Or_Modify_Clause
1591           (Output   : Node_Id;
1592            Outputs  : Node_Id;
1593            Inputs   : Node_Id;
1594            After    : Node_Id;
1595            In_Place : Boolean;
1596            Multiple : Boolean);
1597         --  Create a brand new clause to represent the self-reference or
1598         --  modify the input and/or output lists of an existing clause. Output
1599         --  denotes a self-referencial output. Outputs is the output list of a
1600         --  clause. Inputs is the input list of a clause. After denotes the
1601         --  clause after which the new clause is to be inserted. Flag In_Place
1602         --  should be set when normalizing the last output of an output list.
1603         --  Flag Multiple should be set when Output comes from a list with
1604         --  multiple items.
1605
1606         -----------------------------
1607         -- Create_Or_Modify_Clause --
1608         -----------------------------
1609
1610         procedure Create_Or_Modify_Clause
1611           (Output   : Node_Id;
1612            Outputs  : Node_Id;
1613            Inputs   : Node_Id;
1614            After    : Node_Id;
1615            In_Place : Boolean;
1616            Multiple : Boolean)
1617         is
1618            procedure Propagate_Output
1619              (Output : Node_Id;
1620               Inputs : Node_Id);
1621            --  Handle the various cases of output propagation to the input
1622            --  list. Output denotes a self-referencial output item. Inputs
1623            --  is the input list of a clause.
1624
1625            ----------------------
1626            -- Propagate_Output --
1627            ----------------------
1628
1629            procedure Propagate_Output
1630              (Output : Node_Id;
1631               Inputs : Node_Id)
1632            is
1633               function In_Input_List
1634                 (Item   : Entity_Id;
1635                  Inputs : List_Id) return Boolean;
1636               --  Determine whether a particulat item appears in the input
1637               --  list of a clause.
1638
1639               -------------------
1640               -- In_Input_List --
1641               -------------------
1642
1643               function In_Input_List
1644                 (Item   : Entity_Id;
1645                  Inputs : List_Id) return Boolean
1646               is
1647                  Elmt : Node_Id;
1648
1649               begin
1650                  Elmt := First (Inputs);
1651                  while Present (Elmt) loop
1652                     if Entity_Of (Elmt) = Item then
1653                        return True;
1654                     end if;
1655
1656                     Next (Elmt);
1657                  end loop;
1658
1659                  return False;
1660               end In_Input_List;
1661
1662               --  Local variables
1663
1664               Output_Id : constant Entity_Id := Entity_Of (Output);
1665               Grouped   : List_Id;
1666
1667            --  Start of processing for Propagate_Output
1668
1669            begin
1670               --  The clause is of the form:
1671
1672               --    (Output =>+ null)
1673
1674               --  Remove null input and replace it with a copy of the output:
1675
1676               --    (Output => Output)
1677
1678               if Nkind (Inputs) = N_Null then
1679                  Rewrite (Inputs, New_Copy_Tree (Output));
1680
1681               --  The clause is of the form:
1682
1683               --    (Output =>+ (Input1, ..., InputN))
1684
1685               --  Determine whether the output is not already mentioned in the
1686               --  input list and if not, add it to the list of inputs:
1687
1688               --    (Output => (Output, Input1, ..., InputN))
1689
1690               elsif Nkind (Inputs) = N_Aggregate then
1691                  Grouped := Expressions (Inputs);
1692
1693                  if not In_Input_List
1694                           (Item   => Output_Id,
1695                            Inputs => Grouped)
1696                  then
1697                     Prepend_To (Grouped, New_Copy_Tree (Output));
1698                  end if;
1699
1700               --  The clause is of the form:
1701
1702               --    (Output =>+ Input)
1703
1704               --  If the input does not mention the output, group the two
1705               --  together:
1706
1707               --    (Output => (Output, Input))
1708
1709               elsif Entity_Of (Inputs) /= Output_Id then
1710                  Rewrite (Inputs,
1711                    Make_Aggregate (Loc,
1712                      Expressions => New_List (
1713                        New_Copy_Tree (Output),
1714                        New_Copy_Tree (Inputs))));
1715               end if;
1716            end Propagate_Output;
1717
1718            --  Local variables
1719
1720            Loc        : constant Source_Ptr := Sloc (Clause);
1721            New_Clause : Node_Id;
1722
1723         --  Start of processing for Create_Or_Modify_Clause
1724
1725         begin
1726            --  A null output depending on itself does not require any
1727            --  normalization.
1728
1729            if Nkind (Output) = N_Null then
1730               return;
1731
1732            --  A function result cannot depend on itself because it cannot
1733            --  appear in the input list of a relation (SPARK RM 6.1.5(10)).
1734
1735            elsif Is_Attribute_Result (Output) then
1736               SPARK_Msg_N ("function result cannot depend on itself", Output);
1737               return;
1738            end if;
1739
1740            --  When performing the transformation in place, simply add the
1741            --  output to the list of inputs (if not already there). This
1742            --  case arises when dealing with the last output of an output
1743            --  list. Perform the normalization in place to avoid generating
1744            --  a malformed tree.
1745
1746            if In_Place then
1747               Propagate_Output (Output, Inputs);
1748
1749               --  A list with multiple outputs is slowly trimmed until only
1750               --  one element remains. When this happens, replace aggregate
1751               --  with the element itself.
1752
1753               if Multiple then
1754                  Remove  (Output);
1755                  Rewrite (Outputs, Output);
1756               end if;
1757
1758            --  Default case
1759
1760            else
1761               --  Unchain the output from its output list as it will appear in
1762               --  a new clause. Note that we cannot simply rewrite the output
1763               --  as null because this will violate the semantics of pragma
1764               --  Depends.
1765
1766               Remove (Output);
1767
1768               --  Generate a new clause of the form:
1769               --    (Output => Inputs)
1770
1771               New_Clause :=
1772                 Make_Component_Association (Loc,
1773                   Choices    => New_List (Output),
1774                   Expression => New_Copy_Tree (Inputs));
1775
1776               --  The new clause contains replicated content that has already
1777               --  been analyzed. There is not need to reanalyze or renormalize
1778               --  it again.
1779
1780               Set_Analyzed (New_Clause);
1781
1782               Propagate_Output
1783                 (Output => First (Choices (New_Clause)),
1784                  Inputs => Expression (New_Clause));
1785
1786               Insert_After (After, New_Clause);
1787            end if;
1788         end Create_Or_Modify_Clause;
1789
1790         --  Local variables
1791
1792         Outputs     : constant Node_Id := First (Choices (Clause));
1793         Inputs      : Node_Id;
1794         Last_Output : Node_Id;
1795         Next_Output : Node_Id;
1796         Output      : Node_Id;
1797
1798      --  Start of processing for Normalize_Clause
1799
1800      begin
1801         --  A self-dependency appears as operator "+". Remove the "+" from the
1802         --  tree by moving the real inputs to their proper place.
1803
1804         if Nkind (Expression (Clause)) = N_Op_Plus then
1805            Rewrite (Expression (Clause), Right_Opnd (Expression (Clause)));
1806            Inputs := Expression (Clause);
1807
1808            --  Multiple outputs appear as an aggregate
1809
1810            if Nkind (Outputs) = N_Aggregate then
1811               Last_Output := Last (Expressions (Outputs));
1812
1813               Output := First (Expressions (Outputs));
1814               while Present (Output) loop
1815
1816                  --  Normalization may remove an output from its list,
1817                  --  preserve the subsequent output now.
1818
1819                  Next_Output := Next (Output);
1820
1821                  Create_Or_Modify_Clause
1822                    (Output   => Output,
1823                     Outputs  => Outputs,
1824                     Inputs   => Inputs,
1825                     After    => Clause,
1826                     In_Place => Output = Last_Output,
1827                     Multiple => True);
1828
1829                  Output := Next_Output;
1830               end loop;
1831
1832            --  Solitary output
1833
1834            else
1835               Create_Or_Modify_Clause
1836                 (Output   => Outputs,
1837                  Outputs  => Empty,
1838                  Inputs   => Inputs,
1839                  After    => Empty,
1840                  In_Place => True,
1841                  Multiple => False);
1842            end if;
1843         end if;
1844      end Normalize_Clause;
1845
1846      --  Local variables
1847
1848      Deps    : constant Node_Id   := Expression (Get_Argument (N, Spec_Id));
1849      Subp_Id : constant Entity_Id := Defining_Entity (Subp_Decl);
1850
1851      Clause        : Node_Id;
1852      Errors        : Nat;
1853      Last_Clause   : Node_Id;
1854      Restore_Scope : Boolean := False;
1855
1856   --  Start of processing for Analyze_Depends_In_Decl_Part
1857
1858   begin
1859      --  Do not analyze the pragma multiple times
1860
1861      if Is_Analyzed_Pragma (N) then
1862         return;
1863      end if;
1864
1865      --  Empty dependency list
1866
1867      if Nkind (Deps) = N_Null then
1868
1869         --  Gather all states, objects and formal parameters that the
1870         --  subprogram may depend on. These items are obtained from the
1871         --  parameter profile or pragma [Refined_]Global (if available).
1872
1873         Collect_Subprogram_Inputs_Outputs
1874           (Subp_Id      => Subp_Id,
1875            Subp_Inputs  => Subp_Inputs,
1876            Subp_Outputs => Subp_Outputs,
1877            Global_Seen  => Global_Seen);
1878
1879         --  Verify that every input or output of the subprogram appear in a
1880         --  dependency.
1881
1882         Check_Usage (Subp_Inputs, All_Inputs_Seen, True);
1883         Check_Usage (Subp_Outputs, All_Outputs_Seen, False);
1884         Check_Function_Return;
1885
1886      --  Dependency clauses appear as component associations of an aggregate
1887
1888      elsif Nkind (Deps) = N_Aggregate then
1889
1890         --  Do not attempt to perform analysis of a syntactically illegal
1891         --  clause as this will lead to misleading errors.
1892
1893         if Has_Extra_Parentheses (Deps) then
1894            return;
1895         end if;
1896
1897         if Present (Component_Associations (Deps)) then
1898            Last_Clause := Last (Component_Associations (Deps));
1899
1900            --  Gather all states, objects and formal parameters that the
1901            --  subprogram may depend on. These items are obtained from the
1902            --  parameter profile or pragma [Refined_]Global (if available).
1903
1904            Collect_Subprogram_Inputs_Outputs
1905              (Subp_Id      => Subp_Id,
1906               Subp_Inputs  => Subp_Inputs,
1907               Subp_Outputs => Subp_Outputs,
1908               Global_Seen  => Global_Seen);
1909
1910            --  When pragma [Refined_]Depends appears on a single concurrent
1911            --  type, it is relocated to the anonymous object.
1912
1913            if Is_Single_Concurrent_Object (Spec_Id) then
1914               null;
1915
1916            --  Ensure that the formal parameters are visible when analyzing
1917            --  all clauses. This falls out of the general rule of aspects
1918            --  pertaining to subprogram declarations.
1919
1920            elsif not In_Open_Scopes (Spec_Id) then
1921               Restore_Scope := True;
1922               Push_Scope (Spec_Id);
1923
1924               if Ekind (Spec_Id) = E_Task_Type then
1925                  if Has_Discriminants (Spec_Id) then
1926                     Install_Discriminants (Spec_Id);
1927                  end if;
1928
1929               elsif Is_Generic_Subprogram (Spec_Id) then
1930                  Install_Generic_Formals (Spec_Id);
1931
1932               else
1933                  Install_Formals (Spec_Id);
1934               end if;
1935            end if;
1936
1937            Clause := First (Component_Associations (Deps));
1938            while Present (Clause) loop
1939               Errors := Serious_Errors_Detected;
1940
1941               --  The normalization mechanism may create extra clauses that
1942               --  contain replicated input and output names. There is no need
1943               --  to reanalyze them.
1944
1945               if not Analyzed (Clause) then
1946                  Set_Analyzed (Clause);
1947
1948                  Analyze_Dependency_Clause
1949                    (Clause  => Clause,
1950                     Is_Last => Clause = Last_Clause);
1951               end if;
1952
1953               --  Do not normalize a clause if errors were detected (count
1954               --  of Serious_Errors has increased) because the inputs and/or
1955               --  outputs may denote illegal items. Normalization is disabled
1956               --  in ASIS mode as it alters the tree by introducing new nodes
1957               --  similar to expansion.
1958
1959               if Serious_Errors_Detected = Errors and then not ASIS_Mode then
1960                  Normalize_Clause (Clause);
1961               end if;
1962
1963               Next (Clause);
1964            end loop;
1965
1966            if Restore_Scope then
1967               End_Scope;
1968            end if;
1969
1970            --  Verify that every input or output of the subprogram appear in a
1971            --  dependency.
1972
1973            Check_Usage (Subp_Inputs, All_Inputs_Seen, True);
1974            Check_Usage (Subp_Outputs, All_Outputs_Seen, False);
1975            Check_Function_Return;
1976
1977         --  The dependency list is malformed. This is a syntax error, always
1978         --  report.
1979
1980         else
1981            Error_Msg_N ("malformed dependency relation", Deps);
1982            return;
1983         end if;
1984
1985      --  The top level dependency relation is malformed. This is a syntax
1986      --  error, always report.
1987
1988      else
1989         Error_Msg_N ("malformed dependency relation", Deps);
1990         goto Leave;
1991      end if;
1992
1993      --  Ensure that a state and a corresponding constituent do not appear
1994      --  together in pragma [Refined_]Depends.
1995
1996      Check_State_And_Constituent_Use
1997        (States   => States_Seen,
1998         Constits => Constits_Seen,
1999         Context  => N);
2000
2001      <<Leave>>
2002      Set_Is_Analyzed_Pragma (N);
2003   end Analyze_Depends_In_Decl_Part;
2004
2005   --------------------------------------------
2006   -- Analyze_External_Property_In_Decl_Part --
2007   --------------------------------------------
2008
2009   procedure Analyze_External_Property_In_Decl_Part
2010     (N        : Node_Id;
2011      Expr_Val : out Boolean)
2012   is
2013      Arg1     : constant Node_Id := First (Pragma_Argument_Associations (N));
2014      Obj_Decl : constant Node_Id := Find_Related_Context (N);
2015      Obj_Id   : constant Entity_Id := Defining_Entity (Obj_Decl);
2016      Expr     : Node_Id;
2017
2018   begin
2019      Expr_Val := False;
2020
2021      --  Do not analyze the pragma multiple times
2022
2023      if Is_Analyzed_Pragma (N) then
2024         return;
2025      end if;
2026
2027      Error_Msg_Name_1 := Pragma_Name (N);
2028
2029      --  An external property pragma must apply to an effectively volatile
2030      --  object other than a formal subprogram parameter (SPARK RM 7.1.3(2)).
2031      --  The check is performed at the end of the declarative region due to a
2032      --  possible out-of-order arrangement of pragmas:
2033
2034      --    Obj : ...;
2035      --    pragma Async_Readers (Obj);
2036      --    pragma Volatile (Obj);
2037
2038      if not Is_Effectively_Volatile (Obj_Id) then
2039         SPARK_Msg_N
2040           ("external property % must apply to a volatile object", N);
2041      end if;
2042
2043      --  Ensure that the Boolean expression (if present) is static. A missing
2044      --  argument defaults the value to True (SPARK RM 7.1.2(5)).
2045
2046      Expr_Val := True;
2047
2048      if Present (Arg1) then
2049         Expr := Get_Pragma_Arg (Arg1);
2050
2051         if Is_OK_Static_Expression (Expr) then
2052            Expr_Val := Is_True (Expr_Value (Expr));
2053         end if;
2054      end if;
2055
2056      Set_Is_Analyzed_Pragma (N);
2057   end Analyze_External_Property_In_Decl_Part;
2058
2059   ---------------------------------
2060   -- Analyze_Global_In_Decl_Part --
2061   ---------------------------------
2062
2063   procedure Analyze_Global_In_Decl_Part (N : Node_Id) is
2064      Subp_Decl : constant Node_Id   := Find_Related_Declaration_Or_Body (N);
2065      Spec_Id   : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
2066      Subp_Id   : constant Entity_Id := Defining_Entity (Subp_Decl);
2067
2068      Constits_Seen : Elist_Id := No_Elist;
2069      --  A list containing the entities of all constituents processed so far.
2070      --  It aids in detecting illegal usage of a state and a corresponding
2071      --  constituent in pragma [Refinde_]Global.
2072
2073      Seen : Elist_Id := No_Elist;
2074      --  A list containing the entities of all the items processed so far. It
2075      --  plays a role in detecting distinct entities.
2076
2077      States_Seen : Elist_Id := No_Elist;
2078      --  A list containing the entities of all states processed so far. It
2079      --  helps in detecting illegal usage of a state and a corresponding
2080      --  constituent in pragma [Refined_]Global.
2081
2082      In_Out_Seen : Boolean := False;
2083      Input_Seen  : Boolean := False;
2084      Output_Seen : Boolean := False;
2085      Proof_Seen  : Boolean := False;
2086      --  Flags used to verify the consistency of modes
2087
2088      procedure Analyze_Global_List
2089        (List        : Node_Id;
2090         Global_Mode : Name_Id := Name_Input);
2091      --  Verify the legality of a single global list declaration. Global_Mode
2092      --  denotes the current mode in effect.
2093
2094      -------------------------
2095      -- Analyze_Global_List --
2096      -------------------------
2097
2098      procedure Analyze_Global_List
2099        (List        : Node_Id;
2100         Global_Mode : Name_Id := Name_Input)
2101      is
2102         procedure Analyze_Global_Item
2103           (Item        : Node_Id;
2104            Global_Mode : Name_Id);
2105         --  Verify the legality of a single global item declaration denoted by
2106         --  Item. Global_Mode denotes the current mode in effect.
2107
2108         procedure Check_Duplicate_Mode
2109           (Mode   : Node_Id;
2110            Status : in out Boolean);
2111         --  Flag Status denotes whether a particular mode has been seen while
2112         --  processing a global list. This routine verifies that Mode is not a
2113         --  duplicate mode and sets the flag Status (SPARK RM 6.1.4(9)).
2114
2115         procedure Check_Mode_Restriction_In_Enclosing_Context
2116           (Item    : Node_Id;
2117            Item_Id : Entity_Id);
2118         --  Verify that an item of mode In_Out or Output does not appear as an
2119         --  input in the Global aspect of an enclosing subprogram. If this is
2120         --  the case, emit an error. Item and Item_Id are respectively the
2121         --  item and its entity.
2122
2123         procedure Check_Mode_Restriction_In_Function (Mode : Node_Id);
2124         --  Mode denotes either In_Out or Output. Depending on the kind of the
2125         --  related subprogram, emit an error if those two modes apply to a
2126         --  function (SPARK RM 6.1.4(10)).
2127
2128         -------------------------
2129         -- Analyze_Global_Item --
2130         -------------------------
2131
2132         procedure Analyze_Global_Item
2133           (Item        : Node_Id;
2134            Global_Mode : Name_Id)
2135         is
2136            Item_Id : Entity_Id;
2137
2138         begin
2139            --  Detect one of the following cases
2140
2141            --    with Global => (null, Name)
2142            --    with Global => (Name_1, null, Name_2)
2143            --    with Global => (Name, null)
2144
2145            if Nkind (Item) = N_Null then
2146               SPARK_Msg_N ("cannot mix null and non-null global items", Item);
2147               return;
2148            end if;
2149
2150            Analyze       (Item);
2151            Resolve_State (Item);
2152
2153            --  Find the entity of the item. If this is a renaming, climb the
2154            --  renaming chain to reach the root object. Renamings of non-
2155            --  entire objects do not yield an entity (Empty).
2156
2157            Item_Id := Entity_Of (Item);
2158
2159            if Present (Item_Id) then
2160
2161               --  A global item may denote a formal parameter of an enclosing
2162               --  subprogram (SPARK RM 6.1.4(6)). Do this check first to
2163               --  provide a better error diagnostic.
2164
2165               if Is_Formal (Item_Id) then
2166                  if Scope (Item_Id) = Spec_Id then
2167                     SPARK_Msg_NE
2168                       (Fix_Msg (Spec_Id, "global item cannot reference "
2169                        & "parameter of subprogram &"), Item, Spec_Id);
2170                     return;
2171                  end if;
2172
2173               --  A global item may denote a concurrent type as long as it is
2174               --  the current instance of an enclosing protected or task type
2175               --  (SPARK RM 6.1.4).
2176
2177               elsif Ekind_In (Item_Id, E_Protected_Type, E_Task_Type) then
2178                  if Is_CCT_Instance (Item_Id, Spec_Id) then
2179
2180                     --  Pragma [Refined_]Global associated with a protected
2181                     --  subprogram cannot mention the current instance of a
2182                     --  protected type because the instance behaves as a
2183                     --  formal parameter.
2184
2185                     if Ekind (Item_Id) = E_Protected_Type then
2186                        if Scope (Spec_Id) = Item_Id then
2187                           Error_Msg_Name_1 := Chars (Item_Id);
2188                           SPARK_Msg_NE
2189                             (Fix_Msg (Spec_Id, "global item of subprogram & "
2190                              & "cannot reference current instance of "
2191                              & "protected type %"), Item, Spec_Id);
2192                           return;
2193                        end if;
2194
2195                     --  Pragma [Refined_]Global associated with a task type
2196                     --  cannot mention the current instance of a task type
2197                     --  because the instance behaves as a formal parameter.
2198
2199                     else pragma Assert (Ekind (Item_Id) = E_Task_Type);
2200                        if Spec_Id = Item_Id then
2201                           Error_Msg_Name_1 := Chars (Item_Id);
2202                           SPARK_Msg_NE
2203                             (Fix_Msg (Spec_Id, "global item of subprogram & "
2204                              & "cannot reference current instance of task "
2205                              & "type %"), Item, Spec_Id);
2206                           return;
2207                        end if;
2208                     end if;
2209
2210                  --  Otherwise the global item denotes a subtype mark that is
2211                  --  not a current instance.
2212
2213                  else
2214                     SPARK_Msg_N
2215                       ("invalid use of subtype mark in global list", Item);
2216                     return;
2217                  end if;
2218
2219               --  A global item may denote the anonymous object created for a
2220               --  single protected/task type as long as the current instance
2221               --  is the same single type (SPARK RM 6.1.4).
2222
2223               elsif Is_Single_Concurrent_Object (Item_Id)
2224                 and then Is_CCT_Instance (Etype (Item_Id), Spec_Id)
2225               then
2226                  --  Pragma [Refined_]Global associated with a protected
2227                  --  subprogram cannot mention the current instance of a
2228                  --  protected type because the instance behaves as a formal
2229                  --  parameter.
2230
2231                  if Is_Single_Protected_Object (Item_Id) then
2232                     if Scope (Spec_Id) = Etype (Item_Id) then
2233                        Error_Msg_Name_1 := Chars (Item_Id);
2234                        SPARK_Msg_NE
2235                          (Fix_Msg (Spec_Id, "global item of subprogram & "
2236                           & "cannot reference current instance of protected "
2237                           & "type %"), Item, Spec_Id);
2238                        return;
2239                     end if;
2240
2241                  --  Pragma [Refined_]Global associated with a task type
2242                  --  cannot mention the current instance of a task type
2243                  --  because the instance behaves as a formal parameter.
2244
2245                  else pragma Assert (Is_Single_Task_Object (Item_Id));
2246                     if Spec_Id = Item_Id then
2247                        Error_Msg_Name_1 := Chars (Item_Id);
2248                        SPARK_Msg_NE
2249                          (Fix_Msg (Spec_Id, "global item of subprogram & "
2250                           & "cannot reference current instance of task "
2251                           & "type %"), Item, Spec_Id);
2252                        return;
2253                     end if;
2254                  end if;
2255
2256               --  A formal object may act as a global item inside a generic
2257
2258               elsif Is_Formal_Object (Item_Id) then
2259                  null;
2260
2261               --  The only legal references are those to abstract states,
2262               --  objects and various kinds of constants (SPARK RM 6.1.4(4)).
2263
2264               elsif not Ekind_In (Item_Id, E_Abstract_State,
2265                                            E_Constant,
2266                                            E_Loop_Parameter,
2267                                            E_Variable)
2268               then
2269                  SPARK_Msg_N
2270                    ("global item must denote object, state or current "
2271                     & "instance of concurrent type", Item);
2272                  return;
2273               end if;
2274
2275               --  State related checks
2276
2277               if Ekind (Item_Id) = E_Abstract_State then
2278
2279                  --  Package and subprogram bodies are instantiated
2280                  --  individually in a separate compiler pass. Due to this
2281                  --  mode of instantiation, the refinement of a state may
2282                  --  no longer be visible when a subprogram body contract
2283                  --  is instantiated. Since the generic template is legal,
2284                  --  do not perform this check in the instance to circumvent
2285                  --  this oddity.
2286
2287                  if Is_Generic_Instance (Spec_Id) then
2288                     null;
2289
2290                  --  An abstract state with visible refinement cannot appear
2291                  --  in pragma [Refined_]Global as its place must be taken by
2292                  --  some of its constituents (SPARK RM 6.1.4(7)).
2293
2294                  elsif Has_Visible_Refinement (Item_Id) then
2295                     SPARK_Msg_NE
2296                       ("cannot mention state & in global refinement",
2297                        Item, Item_Id);
2298                     SPARK_Msg_N ("\use its constituents instead", Item);
2299                     return;
2300
2301                  --  An external state cannot appear as a global item of a
2302                  --  nonvolatile function (SPARK RM 7.1.3(8)).
2303
2304                  elsif Is_External_State (Item_Id)
2305                    and then Ekind_In (Spec_Id, E_Function, E_Generic_Function)
2306                    and then not Is_Volatile_Function (Spec_Id)
2307                  then
2308                     SPARK_Msg_NE
2309                       ("external state & cannot act as global item of "
2310                        & "nonvolatile function", Item, Item_Id);
2311                     return;
2312
2313                  --  If the reference to the abstract state appears in an
2314                  --  enclosing package body that will eventually refine the
2315                  --  state, record the reference for future checks.
2316
2317                  else
2318                     Record_Possible_Body_Reference
2319                       (State_Id => Item_Id,
2320                        Ref      => Item);
2321                  end if;
2322
2323               --  Constant related checks
2324
2325               elsif Ekind (Item_Id) = E_Constant then
2326
2327                  --  A constant is a read-only item, therefore it cannot act
2328                  --  as an output.
2329
2330                  if Nam_In (Global_Mode, Name_In_Out, Name_Output) then
2331                     SPARK_Msg_NE
2332                       ("constant & cannot act as output", Item, Item_Id);
2333                     return;
2334                  end if;
2335
2336               --  Loop parameter related checks
2337
2338               elsif Ekind (Item_Id) = E_Loop_Parameter then
2339
2340                  --  A loop parameter is a read-only item, therefore it cannot
2341                  --  act as an output.
2342
2343                  if Nam_In (Global_Mode, Name_In_Out, Name_Output) then
2344                     SPARK_Msg_NE
2345                       ("loop parameter & cannot act as output",
2346                        Item, Item_Id);
2347                     return;
2348                  end if;
2349
2350               --  Variable related checks. These are only relevant when
2351               --  SPARK_Mode is on as they are not standard Ada legality
2352               --  rules.
2353
2354               elsif SPARK_Mode = On
2355                 and then Ekind (Item_Id) = E_Variable
2356                 and then Is_Effectively_Volatile (Item_Id)
2357               then
2358                  --  An effectively volatile object cannot appear as a global
2359                  --  item of a nonvolatile function (SPARK RM 7.1.3(8)).
2360
2361                  if Ekind_In (Spec_Id, E_Function, E_Generic_Function)
2362                    and then not Is_Volatile_Function (Spec_Id)
2363                  then
2364                     Error_Msg_NE
2365                       ("volatile object & cannot act as global item of a "
2366                        & "function", Item, Item_Id);
2367                     return;
2368
2369                  --  An effectively volatile object with external property
2370                  --  Effective_Reads set to True must have mode Output or
2371                  --  In_Out (SPARK RM 7.1.3(10)).
2372
2373                  elsif Effective_Reads_Enabled (Item_Id)
2374                    and then Global_Mode = Name_Input
2375                  then
2376                     Error_Msg_NE
2377                       ("volatile object & with property Effective_Reads must "
2378                        & "have mode In_Out or Output", Item, Item_Id);
2379                     return;
2380                  end if;
2381               end if;
2382
2383               --  When the item renames an entire object, replace the item
2384               --  with a reference to the object.
2385
2386               if Entity (Item) /= Item_Id then
2387                  Rewrite (Item, New_Occurrence_Of (Item_Id, Sloc (Item)));
2388                  Analyze (Item);
2389               end if;
2390
2391            --  Some form of illegal construct masquerading as a name
2392            --  (SPARK RM 6.1.4(4)).
2393
2394            else
2395               Error_Msg_N
2396                 ("global item must denote object, state or current instance "
2397                  & "of concurrent type", Item);
2398               return;
2399            end if;
2400
2401            --  Verify that an output does not appear as an input in an
2402            --  enclosing subprogram.
2403
2404            if Nam_In (Global_Mode, Name_In_Out, Name_Output) then
2405               Check_Mode_Restriction_In_Enclosing_Context (Item, Item_Id);
2406            end if;
2407
2408            --  The same entity might be referenced through various way.
2409            --  Check the entity of the item rather than the item itself
2410            --  (SPARK RM 6.1.4(10)).
2411
2412            if Contains (Seen, Item_Id) then
2413               SPARK_Msg_N ("duplicate global item", Item);
2414
2415            --  Add the entity of the current item to the list of processed
2416            --  items.
2417
2418            else
2419               Append_New_Elmt (Item_Id, Seen);
2420
2421               if Ekind (Item_Id) = E_Abstract_State then
2422                  Append_New_Elmt (Item_Id, States_Seen);
2423
2424               --  The variable may eventually become a constituent of a single
2425               --  protected/task type. Record the reference now and verify its
2426               --  legality when analyzing the contract of the variable
2427               --  (SPARK RM 9.3).
2428
2429               elsif Ekind (Item_Id) = E_Variable then
2430                  Record_Possible_Part_Of_Reference
2431                    (Var_Id => Item_Id,
2432                     Ref    => Item);
2433               end if;
2434
2435               if Ekind_In (Item_Id, E_Abstract_State, E_Constant, E_Variable)
2436                 and then Present (Encapsulating_State (Item_Id))
2437               then
2438                  Append_New_Elmt (Item_Id, Constits_Seen);
2439               end if;
2440            end if;
2441         end Analyze_Global_Item;
2442
2443         --------------------------
2444         -- Check_Duplicate_Mode --
2445         --------------------------
2446
2447         procedure Check_Duplicate_Mode
2448           (Mode   : Node_Id;
2449            Status : in out Boolean)
2450         is
2451         begin
2452            if Status then
2453               SPARK_Msg_N ("duplicate global mode", Mode);
2454            end if;
2455
2456            Status := True;
2457         end Check_Duplicate_Mode;
2458
2459         -------------------------------------------------
2460         -- Check_Mode_Restriction_In_Enclosing_Context --
2461         -------------------------------------------------
2462
2463         procedure Check_Mode_Restriction_In_Enclosing_Context
2464           (Item    : Node_Id;
2465            Item_Id : Entity_Id)
2466         is
2467            Context : Entity_Id;
2468            Dummy   : Boolean;
2469            Inputs  : Elist_Id := No_Elist;
2470            Outputs : Elist_Id := No_Elist;
2471
2472         begin
2473            --  Traverse the scope stack looking for enclosing subprograms
2474            --  subject to pragma [Refined_]Global.
2475
2476            Context := Scope (Subp_Id);
2477            while Present (Context) and then Context /= Standard_Standard loop
2478               if Is_Subprogram (Context)
2479                 and then
2480                   (Present (Get_Pragma (Context, Pragma_Global))
2481                      or else
2482                    Present (Get_Pragma (Context, Pragma_Refined_Global)))
2483               then
2484                  Collect_Subprogram_Inputs_Outputs
2485                    (Subp_Id      => Context,
2486                     Subp_Inputs  => Inputs,
2487                     Subp_Outputs => Outputs,
2488                     Global_Seen  => Dummy);
2489
2490                  --  The item is classified as In_Out or Output but appears as
2491                  --  an Input in an enclosing subprogram (SPARK RM 6.1.4(12)).
2492
2493                  if Appears_In (Inputs, Item_Id)
2494                    and then not Appears_In (Outputs, Item_Id)
2495                  then
2496                     SPARK_Msg_NE
2497                       ("global item & cannot have mode In_Out or Output",
2498                        Item, Item_Id);
2499
2500                     SPARK_Msg_NE
2501                       (Fix_Msg (Subp_Id, "\item already appears as input of "
2502                        & "subprogram &"), Item, Context);
2503
2504                     --  Stop the traversal once an error has been detected
2505
2506                     exit;
2507                  end if;
2508               end if;
2509
2510               Context := Scope (Context);
2511            end loop;
2512         end Check_Mode_Restriction_In_Enclosing_Context;
2513
2514         ----------------------------------------
2515         -- Check_Mode_Restriction_In_Function --
2516         ----------------------------------------
2517
2518         procedure Check_Mode_Restriction_In_Function (Mode : Node_Id) is
2519         begin
2520            if Ekind_In (Spec_Id, E_Function, E_Generic_Function) then
2521               SPARK_Msg_N
2522                 ("global mode & is not applicable to functions", Mode);
2523            end if;
2524         end Check_Mode_Restriction_In_Function;
2525
2526         --  Local variables
2527
2528         Assoc : Node_Id;
2529         Item  : Node_Id;
2530         Mode  : Node_Id;
2531
2532      --  Start of processing for Analyze_Global_List
2533
2534      begin
2535         if Nkind (List) = N_Null then
2536            Set_Analyzed (List);
2537
2538         --  Single global item declaration
2539
2540         elsif Nkind_In (List, N_Expanded_Name,
2541                               N_Identifier,
2542                               N_Selected_Component)
2543         then
2544            Analyze_Global_Item (List, Global_Mode);
2545
2546         --  Simple global list or moded global list declaration
2547
2548         elsif Nkind (List) = N_Aggregate then
2549            Set_Analyzed (List);
2550
2551            --  The declaration of a simple global list appear as a collection
2552            --  of expressions.
2553
2554            if Present (Expressions (List)) then
2555               if Present (Component_Associations (List)) then
2556                  SPARK_Msg_N
2557                    ("cannot mix moded and non-moded global lists", List);
2558               end if;
2559
2560               Item := First (Expressions (List));
2561               while Present (Item) loop
2562                  Analyze_Global_Item (Item, Global_Mode);
2563                  Next (Item);
2564               end loop;
2565
2566            --  The declaration of a moded global list appears as a collection
2567            --  of component associations where individual choices denote
2568            --  modes.
2569
2570            elsif Present (Component_Associations (List)) then
2571               if Present (Expressions (List)) then
2572                  SPARK_Msg_N
2573                    ("cannot mix moded and non-moded global lists", List);
2574               end if;
2575
2576               Assoc := First (Component_Associations (List));
2577               while Present (Assoc) loop
2578                  Mode := First (Choices (Assoc));
2579
2580                  if Nkind (Mode) = N_Identifier then
2581                     if Chars (Mode) = Name_In_Out then
2582                        Check_Duplicate_Mode (Mode, In_Out_Seen);
2583                        Check_Mode_Restriction_In_Function (Mode);
2584
2585                     elsif Chars (Mode) = Name_Input then
2586                        Check_Duplicate_Mode (Mode, Input_Seen);
2587
2588                     elsif Chars (Mode) = Name_Output then
2589                        Check_Duplicate_Mode (Mode, Output_Seen);
2590                        Check_Mode_Restriction_In_Function (Mode);
2591
2592                     elsif Chars (Mode) = Name_Proof_In then
2593                        Check_Duplicate_Mode (Mode, Proof_Seen);
2594
2595                     else
2596                        SPARK_Msg_N ("invalid mode selector", Mode);
2597                     end if;
2598
2599                  else
2600                     SPARK_Msg_N ("invalid mode selector", Mode);
2601                  end if;
2602
2603                  --  Items in a moded list appear as a collection of
2604                  --  expressions. Reuse the existing machinery to analyze
2605                  --  them.
2606
2607                  Analyze_Global_List
2608                    (List        => Expression (Assoc),
2609                     Global_Mode => Chars (Mode));
2610
2611                  Next (Assoc);
2612               end loop;
2613
2614            --  Invalid tree
2615
2616            else
2617               raise Program_Error;
2618            end if;
2619
2620         --  Any other attempt to declare a global item is illegal. This is a
2621         --  syntax error, always report.
2622
2623         else
2624            Error_Msg_N ("malformed global list", List);
2625         end if;
2626      end Analyze_Global_List;
2627
2628      --  Local variables
2629
2630      Items : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
2631
2632      Restore_Scope : Boolean := False;
2633
2634   --  Start of processing for Analyze_Global_In_Decl_Part
2635
2636   begin
2637      --  Do not analyze the pragma multiple times
2638
2639      if Is_Analyzed_Pragma (N) then
2640         return;
2641      end if;
2642
2643      --  There is nothing to be done for a null global list
2644
2645      if Nkind (Items) = N_Null then
2646         Set_Analyzed (Items);
2647
2648      --  Analyze the various forms of global lists and items. Note that some
2649      --  of these may be malformed in which case the analysis emits error
2650      --  messages.
2651
2652      else
2653         --  When pragma [Refined_]Global appears on a single concurrent type,
2654         --  it is relocated to the anonymous object.
2655
2656         if Is_Single_Concurrent_Object (Spec_Id) then
2657            null;
2658
2659         --  Ensure that the formal parameters are visible when processing an
2660         --  item. This falls out of the general rule of aspects pertaining to
2661         --  subprogram declarations.
2662
2663         elsif not In_Open_Scopes (Spec_Id) then
2664            Restore_Scope := True;
2665            Push_Scope (Spec_Id);
2666
2667            if Ekind (Spec_Id) = E_Task_Type then
2668               if Has_Discriminants (Spec_Id) then
2669                  Install_Discriminants (Spec_Id);
2670               end if;
2671
2672            elsif Is_Generic_Subprogram (Spec_Id) then
2673               Install_Generic_Formals (Spec_Id);
2674
2675            else
2676               Install_Formals (Spec_Id);
2677            end if;
2678         end if;
2679
2680         Analyze_Global_List (Items);
2681
2682         if Restore_Scope then
2683            End_Scope;
2684         end if;
2685      end if;
2686
2687      --  Ensure that a state and a corresponding constituent do not appear
2688      --  together in pragma [Refined_]Global.
2689
2690      Check_State_And_Constituent_Use
2691        (States   => States_Seen,
2692         Constits => Constits_Seen,
2693         Context  => N);
2694
2695      Set_Is_Analyzed_Pragma (N);
2696   end Analyze_Global_In_Decl_Part;
2697
2698   --------------------------------------------
2699   -- Analyze_Initial_Condition_In_Decl_Part --
2700   --------------------------------------------
2701
2702   --  WARNING: This routine manages Ghost regions. Return statements must be
2703   --  replaced by gotos which jump to the end of the routine and restore the
2704   --  Ghost mode.
2705
2706   procedure Analyze_Initial_Condition_In_Decl_Part (N : Node_Id) is
2707      Pack_Decl : constant Node_Id   := Find_Related_Package_Or_Body (N);
2708      Pack_Id   : constant Entity_Id := Defining_Entity (Pack_Decl);
2709      Expr      : constant Node_Id   := Expression (Get_Argument (N, Pack_Id));
2710
2711      Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
2712      --  Save the Ghost mode to restore on exit
2713
2714   begin
2715      --  Do not analyze the pragma multiple times
2716
2717      if Is_Analyzed_Pragma (N) then
2718         return;
2719      end if;
2720
2721      --  Set the Ghost mode in effect from the pragma. Due to the delayed
2722      --  analysis of the pragma, the Ghost mode at point of declaration and
2723      --  point of analysis may not necessarily be the same. Use the mode in
2724      --  effect at the point of declaration.
2725
2726      Set_Ghost_Mode (N);
2727
2728      --  The expression is preanalyzed because it has not been moved to its
2729      --  final place yet. A direct analysis may generate side effects and this
2730      --  is not desired at this point.
2731
2732      Preanalyze_Assert_Expression (Expr, Standard_Boolean);
2733      Set_Is_Analyzed_Pragma (N);
2734
2735      Restore_Ghost_Mode (Saved_GM);
2736   end Analyze_Initial_Condition_In_Decl_Part;
2737
2738   --------------------------------------
2739   -- Analyze_Initializes_In_Decl_Part --
2740   --------------------------------------
2741
2742   procedure Analyze_Initializes_In_Decl_Part (N : Node_Id) is
2743      Pack_Decl : constant Node_Id   := Find_Related_Package_Or_Body (N);
2744      Pack_Id   : constant Entity_Id := Defining_Entity (Pack_Decl);
2745
2746      Constits_Seen : Elist_Id := No_Elist;
2747      --  A list containing the entities of all constituents processed so far.
2748      --  It aids in detecting illegal usage of a state and a corresponding
2749      --  constituent in pragma Initializes.
2750
2751      Items_Seen : Elist_Id := No_Elist;
2752      --  A list of all initialization items processed so far. This list is
2753      --  used to detect duplicate items.
2754
2755      States_And_Objs : Elist_Id := No_Elist;
2756      --  A list of all abstract states and objects declared in the visible
2757      --  declarations of the related package. This list is used to detect the
2758      --  legality of initialization items.
2759
2760      States_Seen : Elist_Id := No_Elist;
2761      --  A list containing the entities of all states processed so far. It
2762      --  helps in detecting illegal usage of a state and a corresponding
2763      --  constituent in pragma Initializes.
2764
2765      procedure Analyze_Initialization_Item (Item : Node_Id);
2766      --  Verify the legality of a single initialization item
2767
2768      procedure Analyze_Initialization_Item_With_Inputs (Item : Node_Id);
2769      --  Verify the legality of a single initialization item followed by a
2770      --  list of input items.
2771
2772      procedure Collect_States_And_Objects;
2773      --  Inspect the visible declarations of the related package and gather
2774      --  the entities of all abstract states and objects in States_And_Objs.
2775
2776      ---------------------------------
2777      -- Analyze_Initialization_Item --
2778      ---------------------------------
2779
2780      procedure Analyze_Initialization_Item (Item : Node_Id) is
2781         Item_Id : Entity_Id;
2782
2783      begin
2784         Analyze       (Item);
2785         Resolve_State (Item);
2786
2787         if Is_Entity_Name (Item) then
2788            Item_Id := Entity_Of (Item);
2789
2790            if Present (Item_Id)
2791              and then Ekind_In (Item_Id, E_Abstract_State,
2792                                          E_Constant,
2793                                          E_Variable)
2794            then
2795               --  When the initialization item is undefined, it appears as
2796               --  Any_Id. Do not continue with the analysis of the item.
2797
2798               if Item_Id = Any_Id then
2799                  null;
2800
2801               --  The state or variable must be declared in the visible
2802               --  declarations of the package (SPARK RM 7.1.5(7)).
2803
2804               elsif not Contains (States_And_Objs, Item_Id) then
2805                  Error_Msg_Name_1 := Chars (Pack_Id);
2806                  SPARK_Msg_NE
2807                    ("initialization item & must appear in the visible "
2808                     & "declarations of package %", Item, Item_Id);
2809
2810               --  Detect a duplicate use of the same initialization item
2811               --  (SPARK RM 7.1.5(5)).
2812
2813               elsif Contains (Items_Seen, Item_Id) then
2814                  SPARK_Msg_N ("duplicate initialization item", Item);
2815
2816               --  The item is legal, add it to the list of processed states
2817               --  and variables.
2818
2819               else
2820                  Append_New_Elmt (Item_Id, Items_Seen);
2821
2822                  if Ekind (Item_Id) = E_Abstract_State then
2823                     Append_New_Elmt (Item_Id, States_Seen);
2824                  end if;
2825
2826                  if Present (Encapsulating_State (Item_Id)) then
2827                     Append_New_Elmt (Item_Id, Constits_Seen);
2828                  end if;
2829               end if;
2830
2831            --  The item references something that is not a state or object
2832            --  (SPARK RM 7.1.5(3)).
2833
2834            else
2835               SPARK_Msg_N
2836                 ("initialization item must denote object or state", Item);
2837            end if;
2838
2839         --  Some form of illegal construct masquerading as a name
2840         --  (SPARK RM 7.1.5(3)). This is a syntax error, always report.
2841
2842         else
2843            Error_Msg_N
2844              ("initialization item must denote object or state", Item);
2845         end if;
2846      end Analyze_Initialization_Item;
2847
2848      ---------------------------------------------
2849      -- Analyze_Initialization_Item_With_Inputs --
2850      ---------------------------------------------
2851
2852      procedure Analyze_Initialization_Item_With_Inputs (Item : Node_Id) is
2853         Inputs_Seen : Elist_Id := No_Elist;
2854         --  A list of all inputs processed so far. This list is used to detect
2855         --  duplicate uses of an input.
2856
2857         Non_Null_Seen : Boolean := False;
2858         Null_Seen     : Boolean := False;
2859         --  Flags used to check the legality of an input list
2860
2861         procedure Analyze_Input_Item (Input : Node_Id);
2862         --  Verify the legality of a single input item
2863
2864         ------------------------
2865         -- Analyze_Input_Item --
2866         ------------------------
2867
2868         procedure Analyze_Input_Item (Input : Node_Id) is
2869            Input_Id : Entity_Id;
2870
2871         begin
2872            --  Null input list
2873
2874            if Nkind (Input) = N_Null then
2875               if Null_Seen then
2876                  SPARK_Msg_N
2877                    ("multiple null initializations not allowed", Item);
2878
2879               elsif Non_Null_Seen then
2880                  SPARK_Msg_N
2881                    ("cannot mix null and non-null initialization item", Item);
2882               else
2883                  Null_Seen := True;
2884               end if;
2885
2886            --  Input item
2887
2888            else
2889               Non_Null_Seen := True;
2890
2891               if Null_Seen then
2892                  SPARK_Msg_N
2893                    ("cannot mix null and non-null initialization item", Item);
2894               end if;
2895
2896               Analyze       (Input);
2897               Resolve_State (Input);
2898
2899               if Is_Entity_Name (Input) then
2900                  Input_Id := Entity_Of (Input);
2901
2902                  if Present (Input_Id)
2903                    and then Ekind_In (Input_Id, E_Abstract_State,
2904                                                 E_Constant,
2905                                                 E_Generic_In_Out_Parameter,
2906                                                 E_Generic_In_Parameter,
2907                                                 E_In_Parameter,
2908                                                 E_In_Out_Parameter,
2909                                                 E_Out_Parameter,
2910                                                 E_Protected_Type,
2911                                                 E_Task_Type,
2912                                                 E_Variable)
2913                  then
2914                     --  The input cannot denote states or objects declared
2915                     --  within the related package (SPARK RM 7.1.5(4)).
2916
2917                     if Within_Scope (Input_Id, Current_Scope) then
2918
2919                        --  Do not consider generic formal parameters or their
2920                        --  respective mappings to generic formals. Even though
2921                        --  the formals appear within the scope of the package,
2922                        --  it is allowed for an initialization item to depend
2923                        --  on an input item.
2924
2925                        if Ekind_In (Input_Id, E_Generic_In_Out_Parameter,
2926                                               E_Generic_In_Parameter)
2927                        then
2928                           null;
2929
2930                        elsif Ekind_In (Input_Id, E_Constant, E_Variable)
2931                          and then Present (Corresponding_Generic_Association
2932                                     (Declaration_Node (Input_Id)))
2933                        then
2934                           null;
2935
2936                        else
2937                           Error_Msg_Name_1 := Chars (Pack_Id);
2938                           SPARK_Msg_NE
2939                             ("input item & cannot denote a visible object or "
2940                              & "state of package %", Input, Input_Id);
2941                           return;
2942                        end if;
2943                     end if;
2944
2945                     --  Detect a duplicate use of the same input item
2946                     --  (SPARK RM 7.1.5(5)).
2947
2948                     if Contains (Inputs_Seen, Input_Id) then
2949                        SPARK_Msg_N ("duplicate input item", Input);
2950                        return;
2951                     end if;
2952
2953                     --  At this point it is known that the input is legal. Add
2954                     --  it to the list of processed inputs.
2955
2956                     Append_New_Elmt (Input_Id, Inputs_Seen);
2957
2958                     if Ekind (Input_Id) = E_Abstract_State then
2959                        Append_New_Elmt (Input_Id, States_Seen);
2960                     end if;
2961
2962                     if Ekind_In (Input_Id, E_Abstract_State,
2963                                            E_Constant,
2964                                            E_Variable)
2965                       and then Present (Encapsulating_State (Input_Id))
2966                     then
2967                        Append_New_Elmt (Input_Id, Constits_Seen);
2968                     end if;
2969
2970                  --  The input references something that is not a state or an
2971                  --  object (SPARK RM 7.1.5(3)).
2972
2973                  else
2974                     SPARK_Msg_N
2975                       ("input item must denote object or state", Input);
2976                  end if;
2977
2978               --  Some form of illegal construct masquerading as a name
2979               --  (SPARK RM 7.1.5(3)). This is a syntax error, always report.
2980
2981               else
2982                  Error_Msg_N
2983                    ("input item must denote object or state", Input);
2984               end if;
2985            end if;
2986         end Analyze_Input_Item;
2987
2988         --  Local variables
2989
2990         Inputs : constant Node_Id := Expression (Item);
2991         Elmt   : Node_Id;
2992         Input  : Node_Id;
2993
2994         Name_Seen : Boolean := False;
2995         --  A flag used to detect multiple item names
2996
2997      --  Start of processing for Analyze_Initialization_Item_With_Inputs
2998
2999      begin
3000         --  Inspect the name of an item with inputs
3001
3002         Elmt := First (Choices (Item));
3003         while Present (Elmt) loop
3004            if Name_Seen then
3005               SPARK_Msg_N ("only one item allowed in initialization", Elmt);
3006            else
3007               Name_Seen := True;
3008               Analyze_Initialization_Item (Elmt);
3009            end if;
3010
3011            Next (Elmt);
3012         end loop;
3013
3014         --  Multiple input items appear as an aggregate
3015
3016         if Nkind (Inputs) = N_Aggregate then
3017            if Present (Expressions (Inputs)) then
3018               Input := First (Expressions (Inputs));
3019               while Present (Input) loop
3020                  Analyze_Input_Item (Input);
3021                  Next (Input);
3022               end loop;
3023            end if;
3024
3025            if Present (Component_Associations (Inputs)) then
3026               SPARK_Msg_N
3027                 ("inputs must appear in named association form", Inputs);
3028            end if;
3029
3030         --  Single input item
3031
3032         else
3033            Analyze_Input_Item (Inputs);
3034         end if;
3035      end Analyze_Initialization_Item_With_Inputs;
3036
3037      --------------------------------
3038      -- Collect_States_And_Objects --
3039      --------------------------------
3040
3041      procedure Collect_States_And_Objects is
3042         Pack_Spec : constant Node_Id := Specification (Pack_Decl);
3043         Decl      : Node_Id;
3044
3045      begin
3046         --  Collect the abstract states defined in the package (if any)
3047
3048         if Present (Abstract_States (Pack_Id)) then
3049            States_And_Objs := New_Copy_Elist (Abstract_States (Pack_Id));
3050         end if;
3051
3052         --  Collect all objects that appear in the visible declarations of the
3053         --  related package.
3054
3055         if Present (Visible_Declarations (Pack_Spec)) then
3056            Decl := First (Visible_Declarations (Pack_Spec));
3057            while Present (Decl) loop
3058               if Comes_From_Source (Decl)
3059                 and then Nkind_In (Decl, N_Object_Declaration,
3060                                          N_Object_Renaming_Declaration)
3061               then
3062                  Append_New_Elmt (Defining_Entity (Decl), States_And_Objs);
3063
3064               elsif Is_Single_Concurrent_Type_Declaration (Decl) then
3065                  Append_New_Elmt
3066                    (Anonymous_Object (Defining_Entity (Decl)),
3067                     States_And_Objs);
3068               end if;
3069
3070               Next (Decl);
3071            end loop;
3072         end if;
3073      end Collect_States_And_Objects;
3074
3075      --  Local variables
3076
3077      Inits : constant Node_Id := Expression (Get_Argument (N, Pack_Id));
3078      Init  : Node_Id;
3079
3080   --  Start of processing for Analyze_Initializes_In_Decl_Part
3081
3082   begin
3083      --  Do not analyze the pragma multiple times
3084
3085      if Is_Analyzed_Pragma (N) then
3086         return;
3087      end if;
3088
3089      --  Nothing to do when the initialization list is empty
3090
3091      if Nkind (Inits) = N_Null then
3092         return;
3093      end if;
3094
3095      --  Single and multiple initialization clauses appear as an aggregate. If
3096      --  this is not the case, then either the parser or the analysis of the
3097      --  pragma failed to produce an aggregate.
3098
3099      pragma Assert (Nkind (Inits) = N_Aggregate);
3100
3101      --  Initialize the various lists used during analysis
3102
3103      Collect_States_And_Objects;
3104
3105      if Present (Expressions (Inits)) then
3106         Init := First (Expressions (Inits));
3107         while Present (Init) loop
3108            Analyze_Initialization_Item (Init);
3109            Next (Init);
3110         end loop;
3111      end if;
3112
3113      if Present (Component_Associations (Inits)) then
3114         Init := First (Component_Associations (Inits));
3115         while Present (Init) loop
3116            Analyze_Initialization_Item_With_Inputs (Init);
3117            Next (Init);
3118         end loop;
3119      end if;
3120
3121      --  Ensure that a state and a corresponding constituent do not appear
3122      --  together in pragma Initializes.
3123
3124      Check_State_And_Constituent_Use
3125        (States   => States_Seen,
3126         Constits => Constits_Seen,
3127         Context  => N);
3128
3129      Set_Is_Analyzed_Pragma (N);
3130   end Analyze_Initializes_In_Decl_Part;
3131
3132   ---------------------
3133   -- Analyze_Part_Of --
3134   ---------------------
3135
3136   procedure Analyze_Part_Of
3137     (Indic    : Node_Id;
3138      Item_Id  : Entity_Id;
3139      Encap    : Node_Id;
3140      Encap_Id : out Entity_Id;
3141      Legal    : out Boolean)
3142   is
3143      procedure Check_Part_Of_Abstract_State;
3144      pragma Inline (Check_Part_Of_Abstract_State);
3145      --  Verify the legality of indicator Part_Of when the encapsulator is an
3146      --  abstract state.
3147
3148      procedure Check_Part_Of_Concurrent_Type;
3149      pragma Inline (Check_Part_Of_Concurrent_Type);
3150      --  Verify the legality of indicator Part_Of when the encapsulator is a
3151      --  single concurrent type.
3152
3153      ----------------------------------
3154      -- Check_Part_Of_Abstract_State --
3155      ----------------------------------
3156
3157      procedure Check_Part_Of_Abstract_State is
3158         Pack_Id     : Entity_Id;
3159         Placement   : State_Space_Kind;
3160         Parent_Unit : Entity_Id;
3161
3162      begin
3163         --  Determine where the object, package instantiation or state lives
3164         --  with respect to the enclosing packages or package bodies.
3165
3166         Find_Placement_In_State_Space
3167           (Item_Id   => Item_Id,
3168            Placement => Placement,
3169            Pack_Id   => Pack_Id);
3170
3171         --  The item appears in a non-package construct with a declarative
3172         --  part (subprogram, block, etc). As such, the item is not allowed
3173         --  to be a part of an encapsulating state because the item is not
3174         --  visible.
3175
3176         if Placement = Not_In_Package then
3177            SPARK_Msg_N
3178              ("indicator Part_Of cannot appear in this context "
3179               & "(SPARK RM 7.2.6(5))", Indic);
3180
3181            Error_Msg_Name_1 := Chars (Scope (Encap_Id));
3182            SPARK_Msg_NE
3183              ("\& is not part of the hidden state of package %",
3184               Indic, Item_Id);
3185            return;
3186
3187         --  The item appears in the visible state space of some package. In
3188         --  general this scenario does not warrant Part_Of except when the
3189         --  package is a private child unit and the encapsulating state is
3190         --  declared in a parent unit or a public descendant of that parent
3191         --  unit.
3192
3193         elsif Placement = Visible_State_Space then
3194            if Is_Child_Unit (Pack_Id)
3195              and then Is_Private_Descendant (Pack_Id)
3196            then
3197               --  A variable or state abstraction which is part of the visible
3198               --  state of a private child unit or its public descendants must
3199               --  have its Part_Of indicator specified. The Part_Of indicator
3200               --  must denote a state declared by either the parent unit of
3201               --  the private unit or by a public descendant of that parent
3202               --  unit.
3203
3204               --  Find the nearest private ancestor (which can be the current
3205               --  unit itself).
3206
3207               Parent_Unit := Pack_Id;
3208               while Present (Parent_Unit) loop
3209                  exit when
3210                    Private_Present
3211                      (Parent (Unit_Declaration_Node (Parent_Unit)));
3212                  Parent_Unit := Scope (Parent_Unit);
3213               end loop;
3214
3215               Parent_Unit := Scope (Parent_Unit);
3216
3217               if not Is_Child_Or_Sibling (Pack_Id, Scope (Encap_Id)) then
3218                  SPARK_Msg_NE
3219                    ("indicator Part_Of must denote abstract state of & or of "
3220                     & "its public descendant (SPARK RM 7.2.6(3))",
3221                     Indic, Parent_Unit);
3222                  return;
3223
3224               elsif Scope (Encap_Id) = Parent_Unit
3225                 or else
3226                   (Is_Ancestor_Package (Parent_Unit, Scope (Encap_Id))
3227                     and then not Is_Private_Descendant (Scope (Encap_Id)))
3228               then
3229                  null;
3230
3231               else
3232                  SPARK_Msg_NE
3233                    ("indicator Part_Of must denote abstract state of & or of "
3234                     & "its public descendant (SPARK RM 7.2.6(3))",
3235                     Indic, Parent_Unit);
3236                  return;
3237               end if;
3238
3239            --  Indicator Part_Of is not needed when the related package is not
3240            --  a private child unit or a public descendant thereof.
3241
3242            else
3243               SPARK_Msg_N
3244                 ("indicator Part_Of cannot appear in this context "
3245                  & "(SPARK RM 7.2.6(5))", Indic);
3246
3247               Error_Msg_Name_1 := Chars (Pack_Id);
3248               SPARK_Msg_NE
3249                 ("\& is declared in the visible part of package %",
3250                  Indic, Item_Id);
3251               return;
3252            end if;
3253
3254         --  When the item appears in the private state space of a package, the
3255         --  encapsulating state must be declared in the same package.
3256
3257         elsif Placement = Private_State_Space then
3258            if Scope (Encap_Id) /= Pack_Id then
3259               SPARK_Msg_NE
3260                 ("indicator Part_Of must denote an abstract state of "
3261                  & "package & (SPARK RM 7.2.6(2))", Indic, Pack_Id);
3262
3263               Error_Msg_Name_1 := Chars (Pack_Id);
3264               SPARK_Msg_NE
3265                 ("\& is declared in the private part of package %",
3266                  Indic, Item_Id);
3267               return;
3268            end if;
3269
3270         --  Items declared in the body state space of a package do not need
3271         --  Part_Of indicators as the refinement has already been seen.
3272
3273         else
3274            SPARK_Msg_N
3275              ("indicator Part_Of cannot appear in this context "
3276               & "(SPARK RM 7.2.6(5))", Indic);
3277
3278            if Scope (Encap_Id) = Pack_Id then
3279               Error_Msg_Name_1 := Chars (Pack_Id);
3280               SPARK_Msg_NE
3281                 ("\& is declared in the body of package %", Indic, Item_Id);
3282            end if;
3283
3284            return;
3285         end if;
3286
3287         --  At this point it is known that the Part_Of indicator is legal
3288
3289         Legal := True;
3290      end Check_Part_Of_Abstract_State;
3291
3292      -----------------------------------
3293      -- Check_Part_Of_Concurrent_Type --
3294      -----------------------------------
3295
3296      procedure Check_Part_Of_Concurrent_Type is
3297         function In_Proper_Order
3298           (First  : Node_Id;
3299            Second : Node_Id) return Boolean;
3300         pragma Inline (In_Proper_Order);
3301         --  Determine whether node First precedes node Second
3302
3303         procedure Placement_Error;
3304         pragma Inline (Placement_Error);
3305         --  Emit an error concerning the illegal placement of the item with
3306         --  respect to the single concurrent type.
3307
3308         ---------------------
3309         -- In_Proper_Order --
3310         ---------------------
3311
3312         function In_Proper_Order
3313           (First  : Node_Id;
3314            Second : Node_Id) return Boolean
3315         is
3316            N : Node_Id;
3317
3318         begin
3319            if List_Containing (First) = List_Containing (Second) then
3320               N := First;
3321               while Present (N) loop
3322                  if N = Second then
3323                     return True;
3324                  end if;
3325
3326                  Next (N);
3327               end loop;
3328            end if;
3329
3330            return False;
3331         end In_Proper_Order;
3332
3333         ---------------------
3334         -- Placement_Error --
3335         ---------------------
3336
3337         procedure Placement_Error is
3338         begin
3339            SPARK_Msg_N
3340              ("indicator Part_Of must denote a previously declared single "
3341               & "protected type or single task type", Encap);
3342         end Placement_Error;
3343
3344         --  Local variables
3345
3346         Conc_Typ      : constant Entity_Id := Etype (Encap_Id);
3347         Encap_Decl    : constant Node_Id   := Declaration_Node (Encap_Id);
3348         Encap_Context : constant Node_Id   := Parent (Encap_Decl);
3349
3350         Item_Context : Node_Id;
3351         Item_Decl    : Node_Id;
3352         Prv_Decls    : List_Id;
3353         Vis_Decls    : List_Id;
3354
3355      --  Start of processing for Check_Part_Of_Concurrent_Type
3356
3357      begin
3358         --  Only abstract states and variables can act as constituents of an
3359         --  encapsulating single concurrent type.
3360
3361         if Ekind_In (Item_Id, E_Abstract_State, E_Variable) then
3362            null;
3363
3364         --  The constituent is a constant
3365
3366         elsif Ekind (Item_Id) = E_Constant then
3367            Error_Msg_Name_1 := Chars (Encap_Id);
3368            SPARK_Msg_NE
3369              (Fix_Msg (Conc_Typ, "constant & cannot act as constituent of "
3370               & "single protected type %"), Indic, Item_Id);
3371            return;
3372
3373         --  The constituent is a package instantiation
3374
3375         else
3376            Error_Msg_Name_1 := Chars (Encap_Id);
3377            SPARK_Msg_NE
3378              (Fix_Msg (Conc_Typ, "package instantiation & cannot act as "
3379               & "constituent of single protected type %"), Indic, Item_Id);
3380            return;
3381         end if;
3382
3383         --  When the item denotes an abstract state of a nested package, use
3384         --  the declaration of the package to detect proper placement.
3385
3386         --    package Pack is
3387         --       task T;
3388         --       package Nested
3389         --         with Abstract_State => (State with Part_Of => T)
3390
3391         if Ekind (Item_Id) = E_Abstract_State then
3392            Item_Decl := Unit_Declaration_Node (Scope (Item_Id));
3393         else
3394            Item_Decl := Declaration_Node (Item_Id);
3395         end if;
3396
3397         Item_Context := Parent (Item_Decl);
3398
3399         --  The item and the single concurrent type must appear in the same
3400         --  declarative region, with the item following the declaration of
3401         --  the single concurrent type (SPARK RM 9(3)).
3402
3403         if Item_Context = Encap_Context then
3404            if Nkind_In (Item_Context, N_Package_Specification,
3405                                       N_Protected_Definition,
3406                                       N_Task_Definition)
3407            then
3408               Prv_Decls := Private_Declarations (Item_Context);
3409               Vis_Decls := Visible_Declarations (Item_Context);
3410
3411               --  The placement is OK when the single concurrent type appears
3412               --  within the visible declarations and the item in the private
3413               --  declarations.
3414               --
3415               --    package Pack is
3416               --       protected PO ...
3417               --    private
3418               --       Constit : ... with Part_Of => PO;
3419               --    end Pack;
3420
3421               if List_Containing (Encap_Decl) = Vis_Decls
3422                 and then List_Containing (Item_Decl) = Prv_Decls
3423               then
3424                  null;
3425
3426               --  The placement is illegal when the item appears within the
3427               --  visible declarations and the single concurrent type is in
3428               --  the private declarations.
3429               --
3430               --    package Pack is
3431               --       Constit : ... with Part_Of => PO;
3432               --    private
3433               --       protected PO ...
3434               --    end Pack;
3435
3436               elsif List_Containing (Item_Decl) = Vis_Decls
3437                 and then List_Containing (Encap_Decl) = Prv_Decls
3438               then
3439                  Placement_Error;
3440                  return;
3441
3442               --  Otherwise both the item and the single concurrent type are
3443               --  in the same list. Ensure that the declaration of the single
3444               --  concurrent type precedes that of the item.
3445
3446               elsif not In_Proper_Order
3447                           (First  => Encap_Decl,
3448                            Second => Item_Decl)
3449               then
3450                  Placement_Error;
3451                  return;
3452               end if;
3453
3454            --  Otherwise both the item and the single concurrent type are
3455            --  in the same list. Ensure that the declaration of the single
3456            --  concurrent type precedes that of the item.
3457
3458            elsif not In_Proper_Order
3459                        (First  => Encap_Decl,
3460                         Second => Item_Decl)
3461            then
3462               Placement_Error;
3463               return;
3464            end if;
3465
3466         --  Otherwise the item and the single concurrent type reside within
3467         --  unrelated regions.
3468
3469         else
3470            Error_Msg_Name_1 := Chars (Encap_Id);
3471            SPARK_Msg_NE
3472              (Fix_Msg (Conc_Typ, "constituent & must be declared "
3473               & "immediately within the same region as single protected "
3474               & "type %"), Indic, Item_Id);
3475            return;
3476         end if;
3477
3478         --  At this point it is known that the Part_Of indicator is legal
3479
3480         Legal := True;
3481      end Check_Part_Of_Concurrent_Type;
3482
3483   --  Start of processing for Analyze_Part_Of
3484
3485   begin
3486      --  Assume that the indicator is illegal
3487
3488      Encap_Id := Empty;
3489      Legal    := False;
3490
3491      if Nkind_In (Encap, N_Expanded_Name,
3492                          N_Identifier,
3493                          N_Selected_Component)
3494      then
3495         Analyze       (Encap);
3496         Resolve_State (Encap);
3497
3498         Encap_Id := Entity (Encap);
3499
3500         --  The encapsulator is an abstract state
3501
3502         if Ekind (Encap_Id) = E_Abstract_State then
3503            null;
3504
3505         --  The encapsulator is a single concurrent type (SPARK RM 9.3)
3506
3507         elsif Is_Single_Concurrent_Object (Encap_Id) then
3508            null;
3509
3510         --  Otherwise the encapsulator is not a legal choice
3511
3512         else
3513            SPARK_Msg_N
3514              ("indicator Part_Of must denote abstract state, single "
3515               & "protected type or single task type", Encap);
3516            return;
3517         end if;
3518
3519      --  This is a syntax error, always report
3520
3521      else
3522         Error_Msg_N
3523           ("indicator Part_Of must denote abstract state, single protected "
3524            & "type or single task type", Encap);
3525         return;
3526      end if;
3527
3528      --  Catch a case where indicator Part_Of denotes the abstract view of a
3529      --  variable which appears as an abstract state (SPARK RM 10.1.2 2).
3530
3531      if From_Limited_With (Encap_Id)
3532        and then Present (Non_Limited_View (Encap_Id))
3533        and then Ekind (Non_Limited_View (Encap_Id)) = E_Variable
3534      then
3535         SPARK_Msg_N ("indicator Part_Of must denote abstract state", Encap);
3536         SPARK_Msg_N ("\& denotes abstract view of object", Encap);
3537         return;
3538      end if;
3539
3540      --  The encapsulator is an abstract state
3541
3542      if Ekind (Encap_Id) = E_Abstract_State then
3543         Check_Part_Of_Abstract_State;
3544
3545      --  The encapsulator is a single concurrent type
3546
3547      else
3548         Check_Part_Of_Concurrent_Type;
3549      end if;
3550   end Analyze_Part_Of;
3551
3552   ----------------------------------
3553   -- Analyze_Part_Of_In_Decl_Part --
3554   ----------------------------------
3555
3556   procedure Analyze_Part_Of_In_Decl_Part
3557     (N         : Node_Id;
3558      Freeze_Id : Entity_Id := Empty)
3559   is
3560      Encap    : constant Node_Id   :=
3561                   Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
3562      Errors   : constant Nat       := Serious_Errors_Detected;
3563      Var_Decl : constant Node_Id   := Find_Related_Context (N);
3564      Var_Id   : constant Entity_Id := Defining_Entity (Var_Decl);
3565      Constits : Elist_Id;
3566      Encap_Id : Entity_Id;
3567      Legal    : Boolean;
3568
3569   begin
3570      --  Detect any discrepancies between the placement of the variable with
3571      --  respect to general state space and the encapsulating state or single
3572      --  concurrent type.
3573
3574      Analyze_Part_Of
3575        (Indic    => N,
3576         Item_Id  => Var_Id,
3577         Encap    => Encap,
3578         Encap_Id => Encap_Id,
3579         Legal    => Legal);
3580
3581      --  The Part_Of indicator turns the variable into a constituent of the
3582      --  encapsulating state or single concurrent type.
3583
3584      if Legal then
3585         pragma Assert (Present (Encap_Id));
3586         Constits := Part_Of_Constituents (Encap_Id);
3587
3588         if No (Constits) then
3589            Constits := New_Elmt_List;
3590            Set_Part_Of_Constituents (Encap_Id, Constits);
3591         end if;
3592
3593         Append_Elmt (Var_Id, Constits);
3594         Set_Encapsulating_State (Var_Id, Encap_Id);
3595
3596         --  A Part_Of constituent partially refines an abstract state. This
3597         --  property does not apply to protected or task units.
3598
3599         if Ekind (Encap_Id) = E_Abstract_State then
3600            Set_Has_Partial_Visible_Refinement (Encap_Id);
3601         end if;
3602      end if;
3603
3604      --  Emit a clarification message when the encapsulator is undefined,
3605      --  possibly due to contract freezing.
3606
3607      if Errors /= Serious_Errors_Detected
3608        and then Present (Freeze_Id)
3609        and then Has_Undefined_Reference (Encap)
3610      then
3611         Contract_Freeze_Error (Var_Id, Freeze_Id);
3612      end if;
3613   end Analyze_Part_Of_In_Decl_Part;
3614
3615   --------------------
3616   -- Analyze_Pragma --
3617   --------------------
3618
3619   procedure Analyze_Pragma (N : Node_Id) is
3620      Loc : constant Source_Ptr := Sloc (N);
3621
3622      Pname : Name_Id := Pragma_Name (N);
3623      --  Name of the source pragma, or name of the corresponding aspect for
3624      --  pragmas which originate in a source aspect. In the latter case, the
3625      --  name may be different from the pragma name.
3626
3627      Prag_Id : constant Pragma_Id := Get_Pragma_Id (Pname);
3628
3629      Pragma_Exit : exception;
3630      --  This exception is used to exit pragma processing completely. It
3631      --  is used when an error is detected, and no further processing is
3632      --  required. It is also used if an earlier error has left the tree in
3633      --  a state where the pragma should not be processed.
3634
3635      Arg_Count : Nat;
3636      --  Number of pragma argument associations
3637
3638      Arg1 : Node_Id;
3639      Arg2 : Node_Id;
3640      Arg3 : Node_Id;
3641      Arg4 : Node_Id;
3642      --  First four pragma arguments (pragma argument association nodes, or
3643      --  Empty if the corresponding argument does not exist).
3644
3645      type Name_List is array (Natural range <>) of Name_Id;
3646      type Args_List is array (Natural range <>) of Node_Id;
3647      --  Types used for arguments to Check_Arg_Order and Gather_Associations
3648
3649      -----------------------
3650      -- Local Subprograms --
3651      -----------------------
3652
3653      procedure Acquire_Warning_Match_String (Arg : Node_Id);
3654      --  Used by pragma Warnings (Off, string), and Warn_As_Error (string) to
3655      --  get the given string argument, and place it in Name_Buffer, adding
3656      --  leading and trailing asterisks if they are not already present. The
3657      --  caller has already checked that Arg is a static string expression.
3658
3659      procedure Ada_2005_Pragma;
3660      --  Called for pragmas defined in Ada 2005, that are not in Ada 95. In
3661      --  Ada 95 mode, these are implementation defined pragmas, so should be
3662      --  caught by the No_Implementation_Pragmas restriction.
3663
3664      procedure Ada_2012_Pragma;
3665      --  Called for pragmas defined in Ada 2012, that are not in Ada 95 or 05.
3666      --  In Ada 95 or 05 mode, these are implementation defined pragmas, so
3667      --  should be caught by the No_Implementation_Pragmas restriction.
3668
3669      procedure Analyze_Depends_Global
3670        (Spec_Id   : out Entity_Id;
3671         Subp_Decl : out Node_Id;
3672         Legal     : out Boolean);
3673      --  Subsidiary to the analysis of pragmas Depends and Global. Verify the
3674      --  legality of the placement and related context of the pragma. Spec_Id
3675      --  is the entity of the related subprogram. Subp_Decl is the declaration
3676      --  of the related subprogram. Sets flag Legal when the pragma is legal.
3677
3678      procedure Analyze_If_Present (Id : Pragma_Id);
3679      --  Inspect the remainder of the list containing pragma N and look for
3680      --  a pragma that matches Id. If found, analyze the pragma.
3681
3682      procedure Analyze_Pre_Post_Condition;
3683      --  Subsidiary to the analysis of pragmas Precondition and Postcondition
3684
3685      procedure Analyze_Refined_Depends_Global_Post
3686        (Spec_Id : out Entity_Id;
3687         Body_Id : out Entity_Id;
3688         Legal   : out Boolean);
3689      --  Subsidiary routine to the analysis of body pragmas Refined_Depends,
3690      --  Refined_Global and Refined_Post. Verify the legality of the placement
3691      --  and related context of the pragma. Spec_Id is the entity of the
3692      --  related subprogram. Body_Id is the entity of the subprogram body.
3693      --  Flag Legal is set when the pragma is legal.
3694
3695      procedure Analyze_Unmodified_Or_Unused (Is_Unused : Boolean := False);
3696      --  Perform full analysis of pragma Unmodified and the write aspect of
3697      --  pragma Unused. Flag Is_Unused should be set when verifying the
3698      --  semantics of pragma Unused.
3699
3700      procedure Analyze_Unreferenced_Or_Unused (Is_Unused : Boolean := False);
3701      --  Perform full analysis of pragma Unreferenced and the read aspect of
3702      --  pragma Unused. Flag Is_Unused should be set when verifying the
3703      --  semantics of pragma Unused.
3704
3705      procedure Check_Ada_83_Warning;
3706      --  Issues a warning message for the current pragma if operating in Ada
3707      --  83 mode (used for language pragmas that are not a standard part of
3708      --  Ada 83). This procedure does not raise Pragma_Exit. Also notes use
3709      --  of 95 pragma.
3710
3711      procedure Check_Arg_Count (Required : Nat);
3712      --  Check argument count for pragma is equal to given parameter. If not,
3713      --  then issue an error message and raise Pragma_Exit.
3714
3715      --  Note: all routines whose name is Check_Arg_Is_xxx take an argument
3716      --  Arg which can either be a pragma argument association, in which case
3717      --  the check is applied to the expression of the association or an
3718      --  expression directly.
3719
3720      procedure Check_Arg_Is_External_Name (Arg : Node_Id);
3721      --  Check that an argument has the right form for an EXTERNAL_NAME
3722      --  parameter of an extended import/export pragma. The rule is that the
3723      --  name must be an identifier or string literal (in Ada 83 mode) or a
3724      --  static string expression (in Ada 95 mode).
3725
3726      procedure Check_Arg_Is_Identifier (Arg : Node_Id);
3727      --  Check the specified argument Arg to make sure that it is an
3728      --  identifier. If not give error and raise Pragma_Exit.
3729
3730      procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id);
3731      --  Check the specified argument Arg to make sure that it is an integer
3732      --  literal. If not give error and raise Pragma_Exit.
3733
3734      procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id);
3735      --  Check the specified argument Arg to make sure that it has the proper
3736      --  syntactic form for a local name and meets the semantic requirements
3737      --  for a local name. The local name is analyzed as part of the
3738      --  processing for this call. In addition, the local name is required
3739      --  to represent an entity at the library level.
3740
3741      procedure Check_Arg_Is_Local_Name (Arg : Node_Id);
3742      --  Check the specified argument Arg to make sure that it has the proper
3743      --  syntactic form for a local name and meets the semantic requirements
3744      --  for a local name. The local name is analyzed as part of the
3745      --  processing for this call.
3746
3747      procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id);
3748      --  Check the specified argument Arg to make sure that it is a valid
3749      --  locking policy name. If not give error and raise Pragma_Exit.
3750
3751      procedure Check_Arg_Is_Partition_Elaboration_Policy (Arg : Node_Id);
3752      --  Check the specified argument Arg to make sure that it is a valid
3753      --  elaboration policy name. If not give error and raise Pragma_Exit.
3754
3755      procedure Check_Arg_Is_One_Of
3756        (Arg                : Node_Id;
3757         N1, N2             : Name_Id);
3758      procedure Check_Arg_Is_One_Of
3759        (Arg                : Node_Id;
3760         N1, N2, N3         : Name_Id);
3761      procedure Check_Arg_Is_One_Of
3762        (Arg                : Node_Id;
3763         N1, N2, N3, N4     : Name_Id);
3764      procedure Check_Arg_Is_One_Of
3765        (Arg                : Node_Id;
3766         N1, N2, N3, N4, N5 : Name_Id);
3767      --  Check the specified argument Arg to make sure that it is an
3768      --  identifier whose name matches either N1 or N2 (or N3, N4, N5 if
3769      --  present). If not then give error and raise Pragma_Exit.
3770
3771      procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id);
3772      --  Check the specified argument Arg to make sure that it is a valid
3773      --  queuing policy name. If not give error and raise Pragma_Exit.
3774
3775      procedure Check_Arg_Is_OK_Static_Expression
3776        (Arg : Node_Id;
3777         Typ : Entity_Id := Empty);
3778      --  Check the specified argument Arg to make sure that it is a static
3779      --  expression of the given type (i.e. it will be analyzed and resolved
3780      --  using this type, which can be any valid argument to Resolve, e.g.
3781      --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
3782      --  Typ is left Empty, then any static expression is allowed. Includes
3783      --  checking that the argument does not raise Constraint_Error.
3784
3785      procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id);
3786      --  Check the specified argument Arg to make sure that it is a valid task
3787      --  dispatching policy name. If not give error and raise Pragma_Exit.
3788
3789      procedure Check_Arg_Order (Names : Name_List);
3790      --  Checks for an instance of two arguments with identifiers for the
3791      --  current pragma which are not in the sequence indicated by Names,
3792      --  and if so, generates a fatal message about bad order of arguments.
3793
3794      procedure Check_At_Least_N_Arguments (N : Nat);
3795      --  Check there are at least N arguments present
3796
3797      procedure Check_At_Most_N_Arguments (N : Nat);
3798      --  Check there are no more than N arguments present
3799
3800      procedure Check_Component
3801        (Comp            : Node_Id;
3802         UU_Typ          : Entity_Id;
3803         In_Variant_Part : Boolean := False);
3804      --  Examine an Unchecked_Union component for correct use of per-object
3805      --  constrained subtypes, and for restrictions on finalizable components.
3806      --  UU_Typ is the related Unchecked_Union type. Flag In_Variant_Part
3807      --  should be set when Comp comes from a record variant.
3808
3809      procedure Check_Duplicate_Pragma (E : Entity_Id);
3810      --  Check if a rep item of the same name as the current pragma is already
3811      --  chained as a rep pragma to the given entity. If so give a message
3812      --  about the duplicate, and then raise Pragma_Exit so does not return.
3813      --  Note that if E is a type, then this routine avoids flagging a pragma
3814      --  which applies to a parent type from which E is derived.
3815
3816      procedure Check_Duplicated_Export_Name (Nam : Node_Id);
3817      --  Nam is an N_String_Literal node containing the external name set by
3818      --  an Import or Export pragma (or extended Import or Export pragma).
3819      --  This procedure checks for possible duplications if this is the export
3820      --  case, and if found, issues an appropriate error message.
3821
3822      procedure Check_Expr_Is_OK_Static_Expression
3823        (Expr : Node_Id;
3824         Typ  : Entity_Id := Empty);
3825      --  Check the specified expression Expr to make sure that it is a static
3826      --  expression of the given type (i.e. it will be analyzed and resolved
3827      --  using this type, which can be any valid argument to Resolve, e.g.
3828      --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
3829      --  Typ is left Empty, then any static expression is allowed. Includes
3830      --  checking that the expression does not raise Constraint_Error.
3831
3832      procedure Check_First_Subtype (Arg : Node_Id);
3833      --  Checks that Arg, whose expression is an entity name, references a
3834      --  first subtype.
3835
3836      procedure Check_Identifier (Arg : Node_Id; Id : Name_Id);
3837      --  Checks that the given argument has an identifier, and if so, requires
3838      --  it to match the given identifier name. If there is no identifier, or
3839      --  a non-matching identifier, then an error message is given and
3840      --  Pragma_Exit is raised.
3841
3842      procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
3843      --  Checks that the given argument has an identifier, and if so, requires
3844      --  it to match one of the given identifier names. If there is no
3845      --  identifier, or a non-matching identifier, then an error message is
3846      --  given and Pragma_Exit is raised.
3847
3848      procedure Check_In_Main_Program;
3849      --  Common checks for pragmas that appear within a main program
3850      --  (Priority, Main_Storage, Time_Slice, Relative_Deadline, CPU).
3851
3852      procedure Check_Interrupt_Or_Attach_Handler;
3853      --  Common processing for first argument of pragma Interrupt_Handler or
3854      --  pragma Attach_Handler.
3855
3856      procedure Check_Loop_Pragma_Placement;
3857      --  Verify whether pragmas Loop_Invariant, Loop_Optimize and Loop_Variant
3858      --  appear immediately within a construct restricted to loops, and that
3859      --  pragmas Loop_Invariant and Loop_Variant are grouped together.
3860
3861      procedure Check_Is_In_Decl_Part_Or_Package_Spec;
3862      --  Check that pragma appears in a declarative part, or in a package
3863      --  specification, i.e. that it does not occur in a statement sequence
3864      --  in a body.
3865
3866      procedure Check_No_Identifier (Arg : Node_Id);
3867      --  Checks that the given argument does not have an identifier. If
3868      --  an identifier is present, then an error message is issued, and
3869      --  Pragma_Exit is raised.
3870
3871      procedure Check_No_Identifiers;
3872      --  Checks that none of the arguments to the pragma has an identifier.
3873      --  If any argument has an identifier, then an error message is issued,
3874      --  and Pragma_Exit is raised.
3875
3876      procedure Check_No_Link_Name;
3877      --  Checks that no link name is specified
3878
3879      procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id);
3880      --  Checks if the given argument has an identifier, and if so, requires
3881      --  it to match the given identifier name. If there is a non-matching
3882      --  identifier, then an error message is given and Pragma_Exit is raised.
3883
3884      procedure Check_Optional_Identifier (Arg : Node_Id; Id : String);
3885      --  Checks if the given argument has an identifier, and if so, requires
3886      --  it to match the given identifier name. If there is a non-matching
3887      --  identifier, then an error message is given and Pragma_Exit is raised.
3888      --  In this version of the procedure, the identifier name is given as
3889      --  a string with lower case letters.
3890
3891      procedure Check_Static_Boolean_Expression (Expr : Node_Id);
3892      --  Subsidiary to the analysis of pragmas Async_Readers, Async_Writers,
3893      --  Constant_After_Elaboration, Effective_Reads, Effective_Writes,
3894      --  Extensions_Visible and Volatile_Function. Ensure that expression Expr
3895      --  is an OK static boolean expression. Emit an error if this is not the
3896      --  case.
3897
3898      procedure Check_Static_Constraint (Constr : Node_Id);
3899      --  Constr is a constraint from an N_Subtype_Indication node from a
3900      --  component constraint in an Unchecked_Union type. This routine checks
3901      --  that the constraint is static as required by the restrictions for
3902      --  Unchecked_Union.
3903
3904      procedure Check_Valid_Configuration_Pragma;
3905      --  Legality checks for placement of a configuration pragma
3906
3907      procedure Check_Valid_Library_Unit_Pragma;
3908      --  Legality checks for library unit pragmas. A special case arises for
3909      --  pragmas in generic instances that come from copies of the original
3910      --  library unit pragmas in the generic templates. In the case of other
3911      --  than library level instantiations these can appear in contexts which
3912      --  would normally be invalid (they only apply to the original template
3913      --  and to library level instantiations), and they are simply ignored,
3914      --  which is implemented by rewriting them as null statements.
3915
3916      procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id);
3917      --  Check an Unchecked_Union variant for lack of nested variants and
3918      --  presence of at least one component. UU_Typ is the related Unchecked_
3919      --  Union type.
3920
3921      procedure Ensure_Aggregate_Form (Arg : Node_Id);
3922      --  Subsidiary routine to the processing of pragmas Abstract_State,
3923      --  Contract_Cases, Depends, Global, Initializes, Refined_Depends,
3924      --  Refined_Global and Refined_State. Transform argument Arg into
3925      --  an aggregate if not one already. N_Null is never transformed.
3926      --  Arg may denote an aspect specification or a pragma argument
3927      --  association.
3928
3929      procedure Error_Pragma (Msg : String);
3930      pragma No_Return (Error_Pragma);
3931      --  Outputs error message for current pragma. The message contains a %
3932      --  that will be replaced with the pragma name, and the flag is placed
3933      --  on the pragma itself. Pragma_Exit is then raised. Note: this routine
3934      --  calls Fix_Error (see spec of that procedure for details).
3935
3936      procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id);
3937      pragma No_Return (Error_Pragma_Arg);
3938      --  Outputs error message for current pragma. The message may contain
3939      --  a % that will be replaced with the pragma name. The parameter Arg
3940      --  may either be a pragma argument association, in which case the flag
3941      --  is placed on the expression of this association, or an expression,
3942      --  in which case the flag is placed directly on the expression. The
3943      --  message is placed using Error_Msg_N, so the message may also contain
3944      --  an & insertion character which will reference the given Arg value.
3945      --  After placing the message, Pragma_Exit is raised. Note: this routine
3946      --  calls Fix_Error (see spec of that procedure for details).
3947
3948      procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id);
3949      pragma No_Return (Error_Pragma_Arg);
3950      --  Similar to above form of Error_Pragma_Arg except that two messages
3951      --  are provided, the second is a continuation comment starting with \.
3952
3953      procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id);
3954      pragma No_Return (Error_Pragma_Arg_Ident);
3955      --  Outputs error message for current pragma. The message may contain a %
3956      --  that will be replaced with the pragma name. The parameter Arg must be
3957      --  a pragma argument association with a non-empty identifier (i.e. its
3958      --  Chars field must be set), and the error message is placed on the
3959      --  identifier. The message is placed using Error_Msg_N so the message
3960      --  may also contain an & insertion character which will reference
3961      --  the identifier. After placing the message, Pragma_Exit is raised.
3962      --  Note: this routine calls Fix_Error (see spec of that procedure for
3963      --  details).
3964
3965      procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id);
3966      pragma No_Return (Error_Pragma_Ref);
3967      --  Outputs error message for current pragma. The message may contain
3968      --  a % that will be replaced with the pragma name. The parameter Ref
3969      --  must be an entity whose name can be referenced by & and sloc by #.
3970      --  After placing the message, Pragma_Exit is raised. Note: this routine
3971      --  calls Fix_Error (see spec of that procedure for details).
3972
3973      function Find_Lib_Unit_Name return Entity_Id;
3974      --  Used for a library unit pragma to find the entity to which the
3975      --  library unit pragma applies, returns the entity found.
3976
3977      procedure Find_Program_Unit_Name (Id : Node_Id);
3978      --  If the pragma is a compilation unit pragma, the id must denote the
3979      --  compilation unit in the same compilation, and the pragma must appear
3980      --  in the list of preceding or trailing pragmas. If it is a program
3981      --  unit pragma that is not a compilation unit pragma, then the
3982      --  identifier must be visible.
3983
3984      function Find_Unique_Parameterless_Procedure
3985        (Name : Entity_Id;
3986         Arg  : Node_Id) return Entity_Id;
3987      --  Used for a procedure pragma to find the unique parameterless
3988      --  procedure identified by Name, returns it if it exists, otherwise
3989      --  errors out and uses Arg as the pragma argument for the message.
3990
3991      function Fix_Error (Msg : String) return String;
3992      --  This is called prior to issuing an error message. Msg is the normal
3993      --  error message issued in the pragma case. This routine checks for the
3994      --  case of a pragma coming from an aspect in the source, and returns a
3995      --  message suitable for the aspect case as follows:
3996      --
3997      --    Each substring "pragma" is replaced by "aspect"
3998      --
3999      --    If "argument of" is at the start of the error message text, it is
4000      --    replaced by "entity for".
4001      --
4002      --    If "argument" is at the start of the error message text, it is
4003      --    replaced by "entity".
4004      --
4005      --  So for example, "argument of pragma X must be discrete type"
4006      --  returns "entity for aspect X must be a discrete type".
4007
4008      --  Finally Error_Msg_Name_1 is set to the name of the aspect (which may
4009      --  be different from the pragma name). If the current pragma results
4010      --  from rewriting another pragma, then Error_Msg_Name_1 is set to the
4011      --  original pragma name.
4012
4013      procedure Gather_Associations
4014        (Names : Name_List;
4015         Args  : out Args_List);
4016      --  This procedure is used to gather the arguments for a pragma that
4017      --  permits arbitrary ordering of parameters using the normal rules
4018      --  for named and positional parameters. The Names argument is a list
4019      --  of Name_Id values that corresponds to the allowed pragma argument
4020      --  association identifiers in order. The result returned in Args is
4021      --  a list of corresponding expressions that are the pragma arguments.
4022      --  Note that this is a list of expressions, not of pragma argument
4023      --  associations (Gather_Associations has completely checked all the
4024      --  optional identifiers when it returns). An entry in Args is Empty
4025      --  on return if the corresponding argument is not present.
4026
4027      procedure GNAT_Pragma;
4028      --  Called for all GNAT defined pragmas to check the relevant restriction
4029      --  (No_Implementation_Pragmas).
4030
4031      function Is_Before_First_Decl
4032        (Pragma_Node : Node_Id;
4033         Decls       : List_Id) return Boolean;
4034      --  Return True if Pragma_Node is before the first declarative item in
4035      --  Decls where Decls is the list of declarative items.
4036
4037      function Is_Configuration_Pragma return Boolean;
4038      --  Determines if the placement of the current pragma is appropriate
4039      --  for a configuration pragma.
4040
4041      function Is_In_Context_Clause return Boolean;
4042      --  Returns True if pragma appears within the context clause of a unit,
4043      --  and False for any other placement (does not generate any messages).
4044
4045      function Is_Static_String_Expression (Arg : Node_Id) return Boolean;
4046      --  Analyzes the argument, and determines if it is a static string
4047      --  expression, returns True if so, False if non-static or not String.
4048      --  A special case is that a string literal returns True in Ada 83 mode
4049      --  (which has no such thing as static string expressions). Note that
4050      --  the call analyzes its argument, so this cannot be used for the case
4051      --  where an identifier might not be declared.
4052
4053      procedure Pragma_Misplaced;
4054      pragma No_Return (Pragma_Misplaced);
4055      --  Issue fatal error message for misplaced pragma
4056
4057      procedure Process_Atomic_Independent_Shared_Volatile;
4058      --  Common processing for pragmas Atomic, Independent, Shared, Volatile,
4059      --  Volatile_Full_Access. Note that Shared is an obsolete Ada 83 pragma
4060      --  and treated as being identical in effect to pragma Atomic.
4061
4062      procedure Process_Compile_Time_Warning_Or_Error;
4063      --  Common processing for Compile_Time_Error and Compile_Time_Warning
4064
4065      procedure Process_Convention
4066        (C   : out Convention_Id;
4067         Ent : out Entity_Id);
4068      --  Common processing for Convention, Interface, Import and Export.
4069      --  Checks first two arguments of pragma, and sets the appropriate
4070      --  convention value in the specified entity or entities. On return
4071      --  C is the convention, Ent is the referenced entity.
4072
4073      procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id);
4074      --  Common processing for Disable/Enable_Atomic_Synchronization. Nam is
4075      --  Name_Suppress for Disable and Name_Unsuppress for Enable.
4076
4077      procedure Process_Extended_Import_Export_Object_Pragma
4078        (Arg_Internal : Node_Id;
4079         Arg_External : Node_Id;
4080         Arg_Size     : Node_Id);
4081      --  Common processing for the pragmas Import/Export_Object. The three
4082      --  arguments correspond to the three named parameters of the pragmas. An
4083      --  argument is empty if the corresponding parameter is not present in
4084      --  the pragma.
4085
4086      procedure Process_Extended_Import_Export_Internal_Arg
4087        (Arg_Internal : Node_Id := Empty);
4088      --  Common processing for all extended Import and Export pragmas. The
4089      --  argument is the pragma parameter for the Internal argument. If
4090      --  Arg_Internal is empty or inappropriate, an error message is posted.
4091      --  Otherwise, on normal return, the Entity_Field of Arg_Internal is
4092      --  set to identify the referenced entity.
4093
4094      procedure Process_Extended_Import_Export_Subprogram_Pragma
4095        (Arg_Internal                 : Node_Id;
4096         Arg_External                 : Node_Id;
4097         Arg_Parameter_Types          : Node_Id;
4098         Arg_Result_Type              : Node_Id := Empty;
4099         Arg_Mechanism                : Node_Id;
4100         Arg_Result_Mechanism         : Node_Id := Empty);
4101      --  Common processing for all extended Import and Export pragmas applying
4102      --  to subprograms. The caller omits any arguments that do not apply to
4103      --  the pragma in question (for example, Arg_Result_Type can be non-Empty
4104      --  only in the Import_Function and Export_Function cases). The argument
4105      --  names correspond to the allowed pragma association identifiers.
4106
4107      procedure Process_Generic_List;
4108      --  Common processing for Share_Generic and Inline_Generic
4109
4110      procedure Process_Import_Or_Interface;
4111      --  Common processing for Import or Interface
4112
4113      procedure Process_Import_Predefined_Type;
4114      --  Processing for completing a type with pragma Import. This is used
4115      --  to declare types that match predefined C types, especially for cases
4116      --  without corresponding Ada predefined type.
4117
4118      type Inline_Status is (Suppressed, Disabled, Enabled);
4119      --  Inline status of a subprogram, indicated as follows:
4120      --    Suppressed: inlining is suppressed for the subprogram
4121      --    Disabled:   no inlining is requested for the subprogram
4122      --    Enabled:    inlining is requested/required for the subprogram
4123
4124      procedure Process_Inline (Status : Inline_Status);
4125      --  Common processing for No_Inline, Inline and Inline_Always. Parameter
4126      --  indicates the inline status specified by the pragma.
4127
4128      procedure Process_Interface_Name
4129        (Subprogram_Def : Entity_Id;
4130         Ext_Arg        : Node_Id;
4131         Link_Arg       : Node_Id;
4132         Prag           : Node_Id);
4133      --  Given the last two arguments of pragma Import, pragma Export, or
4134      --  pragma Interface_Name, performs validity checks and sets the
4135      --  Interface_Name field of the given subprogram entity to the
4136      --  appropriate external or link name, depending on the arguments given.
4137      --  Ext_Arg is always present, but Link_Arg may be missing. Note that
4138      --  Ext_Arg may represent the Link_Name if Link_Arg is missing, and
4139      --  appropriate named notation is used for Ext_Arg. If neither Ext_Arg
4140      --  nor Link_Arg is present, the interface name is set to the default
4141      --  from the subprogram name. In addition, the pragma itself is passed
4142      --  to analyze any expressions in the case the pragma came from an aspect
4143      --  specification.
4144
4145      procedure Process_Interrupt_Or_Attach_Handler;
4146      --  Common processing for Interrupt and Attach_Handler pragmas
4147
4148      procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
4149      --  Common processing for Restrictions and Restriction_Warnings pragmas.
4150      --  Warn is True for Restriction_Warnings, or for Restrictions if the
4151      --  flag Treat_Restrictions_As_Warnings is set, and False if this flag
4152      --  is not set in the Restrictions case.
4153
4154      procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
4155      --  Common processing for Suppress and Unsuppress. The boolean parameter
4156      --  Suppress_Case is True for the Suppress case, and False for the
4157      --  Unsuppress case.
4158
4159      procedure Record_Independence_Check (N : Node_Id; E : Entity_Id);
4160      --  Subsidiary to the analysis of pragmas Independent[_Components].
4161      --  Record such a pragma N applied to entity E for future checks.
4162
4163      procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
4164      --  This procedure sets the Is_Exported flag for the given entity,
4165      --  checking that the entity was not previously imported. Arg is
4166      --  the argument that specified the entity. A check is also made
4167      --  for exporting inappropriate entities.
4168
4169      procedure Set_Extended_Import_Export_External_Name
4170        (Internal_Ent : Entity_Id;
4171         Arg_External : Node_Id);
4172      --  Common processing for all extended import export pragmas. The first
4173      --  argument, Internal_Ent, is the internal entity, which has already
4174      --  been checked for validity by the caller. Arg_External is from the
4175      --  Import or Export pragma, and may be null if no External parameter
4176      --  was present. If Arg_External is present and is a non-null string
4177      --  (a null string is treated as the default), then the Interface_Name
4178      --  field of Internal_Ent is set appropriately.
4179
4180      procedure Set_Imported (E : Entity_Id);
4181      --  This procedure sets the Is_Imported flag for the given entity,
4182      --  checking that it is not previously exported or imported.
4183
4184      procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
4185      --  Mech is a parameter passing mechanism (see Import_Function syntax
4186      --  for MECHANISM_NAME). This routine checks that the mechanism argument
4187      --  has the right form, and if not issues an error message. If the
4188      --  argument has the right form then the Mechanism field of Ent is
4189      --  set appropriately.
4190
4191      procedure Set_Rational_Profile;
4192      --  Activate the set of configuration pragmas and permissions that make
4193      --  up the Rational profile.
4194
4195      procedure Set_Ravenscar_Profile (Profile : Profile_Name; N : Node_Id);
4196      --  Activate the set of configuration pragmas and restrictions that make
4197      --  up the Profile. Profile must be either GNAT_Extended_Ravenscar,
4198      --  GNAT_Ravenscar_EDF, or Ravenscar. N is the corresponding pragma node,
4199      --  which is used for error messages on any constructs violating the
4200      --  profile.
4201
4202      ----------------------------------
4203      -- Acquire_Warning_Match_String --
4204      ----------------------------------
4205
4206      procedure Acquire_Warning_Match_String (Arg : Node_Id) is
4207      begin
4208         String_To_Name_Buffer
4209           (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
4210
4211         --  Add asterisk at start if not already there
4212
4213         if Name_Len > 0 and then Name_Buffer (1) /= '*' then
4214            Name_Buffer (2 .. Name_Len + 1) :=
4215              Name_Buffer (1 .. Name_Len);
4216            Name_Buffer (1) := '*';
4217            Name_Len := Name_Len + 1;
4218         end if;
4219
4220         --  Add asterisk at end if not already there
4221
4222         if Name_Buffer (Name_Len) /= '*' then
4223            Name_Len := Name_Len + 1;
4224            Name_Buffer (Name_Len) := '*';
4225         end if;
4226      end Acquire_Warning_Match_String;
4227
4228      ---------------------
4229      -- Ada_2005_Pragma --
4230      ---------------------
4231
4232      procedure Ada_2005_Pragma is
4233      begin
4234         if Ada_Version <= Ada_95 then
4235            Check_Restriction (No_Implementation_Pragmas, N);
4236         end if;
4237      end Ada_2005_Pragma;
4238
4239      ---------------------
4240      -- Ada_2012_Pragma --
4241      ---------------------
4242
4243      procedure Ada_2012_Pragma is
4244      begin
4245         if Ada_Version <= Ada_2005 then
4246            Check_Restriction (No_Implementation_Pragmas, N);
4247         end if;
4248      end Ada_2012_Pragma;
4249
4250      ----------------------------
4251      -- Analyze_Depends_Global --
4252      ----------------------------
4253
4254      procedure Analyze_Depends_Global
4255        (Spec_Id   : out Entity_Id;
4256         Subp_Decl : out Node_Id;
4257         Legal     : out Boolean)
4258      is
4259      begin
4260         --  Assume that the pragma is illegal
4261
4262         Spec_Id   := Empty;
4263         Subp_Decl := Empty;
4264         Legal     := False;
4265
4266         GNAT_Pragma;
4267         Check_Arg_Count (1);
4268
4269         --  Ensure the proper placement of the pragma. Depends/Global must be
4270         --  associated with a subprogram declaration or a body that acts as a
4271         --  spec.
4272
4273         Subp_Decl := Find_Related_Declaration_Or_Body (N, Do_Checks => True);
4274
4275         --  Entry
4276
4277         if Nkind (Subp_Decl) = N_Entry_Declaration then
4278            null;
4279
4280         --  Generic subprogram
4281
4282         elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
4283            null;
4284
4285         --  Object declaration of a single concurrent type
4286
4287         elsif Nkind (Subp_Decl) = N_Object_Declaration
4288           and then Is_Single_Concurrent_Object
4289                      (Unique_Defining_Entity (Subp_Decl))
4290         then
4291            null;
4292
4293         --  Single task type
4294
4295         elsif Nkind (Subp_Decl) = N_Single_Task_Declaration then
4296            null;
4297
4298         --  Subprogram body acts as spec
4299
4300         elsif Nkind (Subp_Decl) = N_Subprogram_Body
4301           and then No (Corresponding_Spec (Subp_Decl))
4302         then
4303            null;
4304
4305         --  Subprogram body stub acts as spec
4306
4307         elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
4308           and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
4309         then
4310            null;
4311
4312         --  Subprogram declaration
4313
4314         elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
4315            null;
4316
4317         --  Task type
4318
4319         elsif Nkind (Subp_Decl) = N_Task_Type_Declaration then
4320            null;
4321
4322         else
4323            Pragma_Misplaced;
4324            return;
4325         end if;
4326
4327         --  If we get here, then the pragma is legal
4328
4329         Legal   := True;
4330         Spec_Id := Unique_Defining_Entity (Subp_Decl);
4331
4332         --  When the related context is an entry, the entry must belong to a
4333         --  protected unit (SPARK RM 6.1.4(6)).
4334
4335         if Is_Entry_Declaration (Spec_Id)
4336           and then Ekind (Scope (Spec_Id)) /= E_Protected_Type
4337         then
4338            Pragma_Misplaced;
4339            return;
4340
4341         --  When the related context is an anonymous object created for a
4342         --  simple concurrent type, the type must be a task
4343         --  (SPARK RM 6.1.4(6)).
4344
4345         elsif Is_Single_Concurrent_Object (Spec_Id)
4346           and then Ekind (Etype (Spec_Id)) /= E_Task_Type
4347         then
4348            Pragma_Misplaced;
4349            return;
4350         end if;
4351
4352         --  A pragma that applies to a Ghost entity becomes Ghost for the
4353         --  purposes of legality checks and removal of ignored Ghost code.
4354
4355         Mark_Ghost_Pragma (N, Spec_Id);
4356         Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
4357      end Analyze_Depends_Global;
4358
4359      ------------------------
4360      -- Analyze_If_Present --
4361      ------------------------
4362
4363      procedure Analyze_If_Present (Id : Pragma_Id) is
4364         Stmt : Node_Id;
4365
4366      begin
4367         pragma Assert (Is_List_Member (N));
4368
4369         --  Inspect the declarations or statements following pragma N looking
4370         --  for another pragma whose Id matches the caller's request. If it is
4371         --  available, analyze it.
4372
4373         Stmt := Next (N);
4374         while Present (Stmt) loop
4375            if Nkind (Stmt) = N_Pragma and then Get_Pragma_Id (Stmt) = Id then
4376               Analyze_Pragma (Stmt);
4377               exit;
4378
4379            --  The first source declaration or statement immediately following
4380            --  N ends the region where a pragma may appear.
4381
4382            elsif Comes_From_Source (Stmt) then
4383               exit;
4384            end if;
4385
4386            Next (Stmt);
4387         end loop;
4388      end Analyze_If_Present;
4389
4390      --------------------------------
4391      -- Analyze_Pre_Post_Condition --
4392      --------------------------------
4393
4394      procedure Analyze_Pre_Post_Condition is
4395         Prag_Iden : constant Node_Id := Pragma_Identifier (N);
4396         Subp_Decl : Node_Id;
4397         Subp_Id   : Entity_Id;
4398
4399         Duplicates_OK : Boolean := False;
4400         --  Flag set when a pre/postcondition allows multiple pragmas of the
4401         --  same kind.
4402
4403         In_Body_OK : Boolean := False;
4404         --  Flag set when a pre/postcondition is allowed to appear on a body
4405         --  even though the subprogram may have a spec.
4406
4407         Is_Pre_Post : Boolean := False;
4408         --  Flag set when the pragma is one of Pre, Pre_Class, Post or
4409         --  Post_Class.
4410
4411         function Inherits_Class_Wide_Pre (E : Entity_Id) return Boolean;
4412         --  Implement rules in AI12-0131: an overriding operation can have
4413         --  a class-wide precondition only if one of its ancestors has an
4414         --  explicit class-wide precondition.
4415
4416         -----------------------------
4417         -- Inherits_Class_Wide_Pre --
4418         -----------------------------
4419
4420         function Inherits_Class_Wide_Pre (E : Entity_Id) return Boolean is
4421            Typ  : constant Entity_Id := Find_Dispatching_Type (E);
4422            Cont : Node_Id;
4423            Prag : Node_Id;
4424            Prev : Entity_Id := Overridden_Operation (E);
4425
4426         begin
4427            --  Check ancestors on the overriding operation to examine the
4428            --  preconditions that may apply to them.
4429
4430            while Present (Prev) loop
4431               Cont := Contract (Prev);
4432               if Present (Cont) then
4433                  Prag := Pre_Post_Conditions (Cont);
4434                  while Present (Prag) loop
4435                     if Class_Present (Prag) then
4436                        return True;
4437                     end if;
4438
4439                     Prag := Next_Pragma (Prag);
4440                  end loop;
4441               end if;
4442
4443               --  For a type derived from a generic formal type, the operation
4444               --  inheriting the condition is a renaming, not an overriding of
4445               --  the operation of the formal. Ditto for an inherited
4446               --  operation which has no explicit contracts.
4447
4448               if Is_Generic_Type (Find_Dispatching_Type (Prev))
4449                 or else not Comes_From_Source (Prev)
4450               then
4451                  Prev := Alias (Prev);
4452               else
4453                  Prev := Overridden_Operation (Prev);
4454               end if;
4455            end loop;
4456
4457            --  If the controlling type of the subprogram has progenitors, an
4458            --  interface operation implemented by the current operation may
4459            --  have a class-wide precondition.
4460
4461            if Has_Interfaces (Typ) then
4462               declare
4463                  Elmt      : Elmt_Id;
4464                  Ints      : Elist_Id;
4465                  Prim      : Entity_Id;
4466                  Prim_Elmt : Elmt_Id;
4467                  Prim_List : Elist_Id;
4468
4469               begin
4470                  Collect_Interfaces (Typ, Ints);
4471                  Elmt := First_Elmt (Ints);
4472
4473                  --  Iterate over the primitive operations of each interface
4474
4475                  while Present (Elmt) loop
4476                     Prim_List := Direct_Primitive_Operations (Node (Elmt));
4477                     Prim_Elmt := First_Elmt (Prim_List);
4478                     while Present (Prim_Elmt) loop
4479                        Prim := Node (Prim_Elmt);
4480                        if Chars (Prim) = Chars (E)
4481                          and then Present (Contract (Prim))
4482                          and then Class_Present
4483                                     (Pre_Post_Conditions (Contract (Prim)))
4484                        then
4485                           return True;
4486                        end if;
4487
4488                        Next_Elmt (Prim_Elmt);
4489                     end loop;
4490
4491                     Next_Elmt (Elmt);
4492                  end loop;
4493               end;
4494            end if;
4495
4496            return False;
4497         end Inherits_Class_Wide_Pre;
4498
4499      --  Start of processing for Analyze_Pre_Post_Condition
4500
4501      begin
4502         --  Change the name of pragmas Pre, Pre_Class, Post and Post_Class to
4503         --  offer uniformity among the various kinds of pre/postconditions by
4504         --  rewriting the pragma identifier. This allows the retrieval of the
4505         --  original pragma name by routine Original_Aspect_Pragma_Name.
4506
4507         if Comes_From_Source (N) then
4508            if Nam_In (Pname, Name_Pre, Name_Pre_Class) then
4509               Is_Pre_Post := True;
4510               Set_Class_Present (N, Pname = Name_Pre_Class);
4511               Rewrite (Prag_Iden, Make_Identifier (Loc, Name_Precondition));
4512
4513            elsif Nam_In (Pname, Name_Post, Name_Post_Class) then
4514               Is_Pre_Post := True;
4515               Set_Class_Present (N, Pname = Name_Post_Class);
4516               Rewrite (Prag_Iden, Make_Identifier (Loc, Name_Postcondition));
4517            end if;
4518         end if;
4519
4520         --  Determine the semantics with respect to duplicates and placement
4521         --  in a body. Pragmas Precondition and Postcondition were introduced
4522         --  before aspects and are not subject to the same aspect-like rules.
4523
4524         if Nam_In (Pname, Name_Precondition, Name_Postcondition) then
4525            Duplicates_OK := True;
4526            In_Body_OK    := True;
4527         end if;
4528
4529         GNAT_Pragma;
4530
4531         --  Pragmas Pre, Pre_Class, Post and Post_Class allow for a single
4532         --  argument without an identifier.
4533
4534         if Is_Pre_Post then
4535            Check_Arg_Count (1);
4536            Check_No_Identifiers;
4537
4538         --  Pragmas Precondition and Postcondition have complex argument
4539         --  profile.
4540
4541         else
4542            Check_At_Least_N_Arguments (1);
4543            Check_At_Most_N_Arguments  (2);
4544            Check_Optional_Identifier (Arg1, Name_Check);
4545
4546            if Present (Arg2) then
4547               Check_Optional_Identifier (Arg2, Name_Message);
4548               Preanalyze_Spec_Expression
4549                 (Get_Pragma_Arg (Arg2), Standard_String);
4550            end if;
4551         end if;
4552
4553         --  For a pragma PPC in the extended main source unit, record enabled
4554         --  status in SCO.
4555         --  ??? nothing checks that the pragma is in the main source unit
4556
4557         if Is_Checked (N) and then not Split_PPC (N) then
4558            Set_SCO_Pragma_Enabled (Loc);
4559         end if;
4560
4561         --  Ensure the proper placement of the pragma
4562
4563         Subp_Decl :=
4564           Find_Related_Declaration_Or_Body
4565             (N, Do_Checks => not Duplicates_OK);
4566
4567         --  When a pre/postcondition pragma applies to an abstract subprogram,
4568         --  its original form must be an aspect with 'Class.
4569
4570         if Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
4571            if not From_Aspect_Specification (N) then
4572               Error_Pragma
4573                 ("pragma % cannot be applied to abstract subprogram");
4574
4575            elsif not Class_Present (N) then
4576               Error_Pragma
4577                 ("aspect % requires ''Class for abstract subprogram");
4578            end if;
4579
4580         --  Entry declaration
4581
4582         elsif Nkind (Subp_Decl) = N_Entry_Declaration then
4583            null;
4584
4585         --  Generic subprogram declaration
4586
4587         elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
4588            null;
4589
4590         --  Subprogram body
4591
4592         elsif Nkind (Subp_Decl) = N_Subprogram_Body
4593           and then (No (Corresponding_Spec (Subp_Decl)) or In_Body_OK)
4594         then
4595            null;
4596
4597         --  Subprogram body stub
4598
4599         elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
4600           and then (No (Corresponding_Spec_Of_Stub (Subp_Decl)) or In_Body_OK)
4601         then
4602            null;
4603
4604         --  Subprogram declaration
4605
4606         elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
4607
4608            --  AI05-0230: When a pre/postcondition pragma applies to a null
4609            --  procedure, its original form must be an aspect with 'Class.
4610
4611            if Nkind (Specification (Subp_Decl)) = N_Procedure_Specification
4612              and then Null_Present (Specification (Subp_Decl))
4613              and then From_Aspect_Specification (N)
4614              and then not Class_Present (N)
4615            then
4616               Error_Pragma ("aspect % requires ''Class for null procedure");
4617            end if;
4618
4619            --  Implement the legality checks mandated by AI12-0131:
4620            --    Pre'Class shall not be specified for an overriding primitive
4621            --    subprogram of a tagged type T unless the Pre'Class aspect is
4622            --    specified for the corresponding primitive subprogram of some
4623            --    ancestor of T.
4624
4625            declare
4626               E : constant Entity_Id := Defining_Entity (Subp_Decl);
4627
4628            begin
4629               if Class_Present (N)
4630                 and then Pragma_Name (N) = Name_Precondition
4631                 and then Present (Overridden_Operation (E))
4632                 and then not Inherits_Class_Wide_Pre (E)
4633               then
4634                  Error_Msg_N
4635                    ("illegal class-wide precondition on overriding operation",
4636                     Corresponding_Aspect (N));
4637               end if;
4638            end;
4639
4640         --  A renaming declaration may inherit a generated pragma, its
4641         --  placement comes from expansion, not from source.
4642
4643         elsif Nkind (Subp_Decl) = N_Subprogram_Renaming_Declaration
4644           and then not Comes_From_Source (N)
4645         then
4646            null;
4647
4648         --  Otherwise the placement is illegal
4649
4650         else
4651            Pragma_Misplaced;
4652            return;
4653         end if;
4654
4655         Subp_Id := Defining_Entity (Subp_Decl);
4656
4657         --  A pragma that applies to a Ghost entity becomes Ghost for the
4658         --  purposes of legality checks and removal of ignored Ghost code.
4659
4660         Mark_Ghost_Pragma (N, Subp_Id);
4661
4662         --  Chain the pragma on the contract for further processing by
4663         --  Analyze_Pre_Post_Condition_In_Decl_Part.
4664
4665         Add_Contract_Item (N, Defining_Entity (Subp_Decl));
4666
4667         --  Fully analyze the pragma when it appears inside an entry or
4668         --  subprogram body because it cannot benefit from forward references.
4669
4670         if Nkind_In (Subp_Decl, N_Entry_Body,
4671                                 N_Subprogram_Body,
4672                                 N_Subprogram_Body_Stub)
4673         then
4674            --  The legality checks of pragmas Precondition and Postcondition
4675            --  are affected by the SPARK mode in effect and the volatility of
4676            --  the context. Analyze all pragmas in a specific order.
4677
4678            Analyze_If_Present (Pragma_SPARK_Mode);
4679            Analyze_If_Present (Pragma_Volatile_Function);
4680            Analyze_Pre_Post_Condition_In_Decl_Part (N);
4681         end if;
4682      end Analyze_Pre_Post_Condition;
4683
4684      -----------------------------------------
4685      -- Analyze_Refined_Depends_Global_Post --
4686      -----------------------------------------
4687
4688      procedure Analyze_Refined_Depends_Global_Post
4689        (Spec_Id : out Entity_Id;
4690         Body_Id : out Entity_Id;
4691         Legal   : out Boolean)
4692      is
4693         Body_Decl : Node_Id;
4694         Spec_Decl : Node_Id;
4695
4696      begin
4697         --  Assume that the pragma is illegal
4698
4699         Spec_Id := Empty;
4700         Body_Id := Empty;
4701         Legal   := False;
4702
4703         GNAT_Pragma;
4704         Check_Arg_Count (1);
4705         Check_No_Identifiers;
4706
4707         --  Verify the placement of the pragma and check for duplicates. The
4708         --  pragma must apply to a subprogram body [stub].
4709
4710         Body_Decl := Find_Related_Declaration_Or_Body (N, Do_Checks => True);
4711
4712         --  Entry body
4713
4714         if Nkind (Body_Decl) = N_Entry_Body then
4715            null;
4716
4717         --  Subprogram body
4718
4719         elsif Nkind (Body_Decl) = N_Subprogram_Body then
4720            null;
4721
4722         --  Subprogram body stub
4723
4724         elsif Nkind (Body_Decl) = N_Subprogram_Body_Stub then
4725            null;
4726
4727         --  Task body
4728
4729         elsif Nkind (Body_Decl) = N_Task_Body then
4730            null;
4731
4732         else
4733            Pragma_Misplaced;
4734            return;
4735         end if;
4736
4737         Body_Id := Defining_Entity (Body_Decl);
4738         Spec_Id := Unique_Defining_Entity (Body_Decl);
4739
4740         --  The pragma must apply to the second declaration of a subprogram.
4741         --  In other words, the body [stub] cannot acts as a spec.
4742
4743         if No (Spec_Id) then
4744            Error_Pragma ("pragma % cannot apply to a stand alone body");
4745            return;
4746
4747         --  Catch the case where the subprogram body is a subunit and acts as
4748         --  the third declaration of the subprogram.
4749
4750         elsif Nkind (Parent (Body_Decl)) = N_Subunit then
4751            Error_Pragma ("pragma % cannot apply to a subunit");
4752            return;
4753         end if;
4754
4755         --  A refined pragma can only apply to the body [stub] of a subprogram
4756         --  declared in the visible part of a package. Retrieve the context of
4757         --  the subprogram declaration.
4758
4759         Spec_Decl := Unit_Declaration_Node (Spec_Id);
4760
4761         --  When dealing with protected entries or protected subprograms, use
4762         --  the enclosing protected type as the proper context.
4763
4764         if Ekind_In (Spec_Id, E_Entry,
4765                               E_Entry_Family,
4766                               E_Function,
4767                               E_Procedure)
4768           and then Ekind (Scope (Spec_Id)) = E_Protected_Type
4769         then
4770            Spec_Decl := Declaration_Node (Scope (Spec_Id));
4771         end if;
4772
4773         if Nkind (Parent (Spec_Decl)) /= N_Package_Specification then
4774            Error_Pragma
4775              (Fix_Msg (Spec_Id, "pragma % must apply to the body of "
4776               & "subprogram declared in a package specification"));
4777            return;
4778         end if;
4779
4780         --  If we get here, then the pragma is legal
4781
4782         Legal := True;
4783
4784         --  A pragma that applies to a Ghost entity becomes Ghost for the
4785         --  purposes of legality checks and removal of ignored Ghost code.
4786
4787         Mark_Ghost_Pragma (N, Spec_Id);
4788
4789         if Nam_In (Pname, Name_Refined_Depends, Name_Refined_Global) then
4790            Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
4791         end if;
4792      end Analyze_Refined_Depends_Global_Post;
4793
4794      ----------------------------------
4795      -- Analyze_Unmodified_Or_Unused --
4796      ----------------------------------
4797
4798      procedure Analyze_Unmodified_Or_Unused (Is_Unused : Boolean := False) is
4799         Arg      : Node_Id;
4800         Arg_Expr : Node_Id;
4801         Arg_Id   : Entity_Id;
4802
4803         Ghost_Error_Posted : Boolean := False;
4804         --  Flag set when an error concerning the illegal mix of Ghost and
4805         --  non-Ghost variables is emitted.
4806
4807         Ghost_Id : Entity_Id := Empty;
4808         --  The entity of the first Ghost variable encountered while
4809         --  processing the arguments of the pragma.
4810
4811      begin
4812         GNAT_Pragma;
4813         Check_At_Least_N_Arguments (1);
4814
4815         --  Loop through arguments
4816
4817         Arg := Arg1;
4818         while Present (Arg) loop
4819            Check_No_Identifier (Arg);
4820
4821            --  Note: the analyze call done by Check_Arg_Is_Local_Name will
4822            --  in fact generate reference, so that the entity will have a
4823            --  reference, which will inhibit any warnings about it not
4824            --  being referenced, and also properly show up in the ali file
4825            --  as a reference. But this reference is recorded before the
4826            --  Has_Pragma_Unreferenced flag is set, so that no warning is
4827            --  generated for this reference.
4828
4829            Check_Arg_Is_Local_Name (Arg);
4830            Arg_Expr := Get_Pragma_Arg (Arg);
4831
4832            if Is_Entity_Name (Arg_Expr) then
4833               Arg_Id := Entity (Arg_Expr);
4834
4835               --  Skip processing the argument if already flagged
4836
4837               if Is_Assignable (Arg_Id)
4838                 and then not Has_Pragma_Unmodified (Arg_Id)
4839                 and then not Has_Pragma_Unused (Arg_Id)
4840               then
4841                  Set_Has_Pragma_Unmodified (Arg_Id);
4842
4843                  if Is_Unused then
4844                     Set_Has_Pragma_Unused (Arg_Id);
4845                  end if;
4846
4847                  --  A pragma that applies to a Ghost entity becomes Ghost for
4848                  --  the purposes of legality checks and removal of ignored
4849                  --  Ghost code.
4850
4851                  Mark_Ghost_Pragma (N, Arg_Id);
4852
4853                  --  Capture the entity of the first Ghost variable being
4854                  --  processed for error detection purposes.
4855
4856                  if Is_Ghost_Entity (Arg_Id) then
4857                     if No (Ghost_Id) then
4858                        Ghost_Id := Arg_Id;
4859                     end if;
4860
4861                  --  Otherwise the variable is non-Ghost. It is illegal to mix
4862                  --  references to Ghost and non-Ghost entities
4863                  --  (SPARK RM 6.9).
4864
4865                  elsif Present (Ghost_Id)
4866                    and then not Ghost_Error_Posted
4867                  then
4868                     Ghost_Error_Posted := True;
4869
4870                     Error_Msg_Name_1 := Pname;
4871                     Error_Msg_N
4872                       ("pragma % cannot mention ghost and non-ghost "
4873                        & "variables", N);
4874
4875                     Error_Msg_Sloc := Sloc (Ghost_Id);
4876                     Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
4877
4878                     Error_Msg_Sloc := Sloc (Arg_Id);
4879                     Error_Msg_NE ("\& # declared as non-ghost", N, Arg_Id);
4880                  end if;
4881
4882               --  Warn if already flagged as Unused or Unmodified
4883
4884               elsif Has_Pragma_Unmodified (Arg_Id) then
4885                  if Has_Pragma_Unused (Arg_Id) then
4886                     Error_Msg_NE
4887                       ("??pragma Unused already given for &!", Arg_Expr,
4888                         Arg_Id);
4889                  else
4890                     Error_Msg_NE
4891                       ("??pragma Unmodified already given for &!", Arg_Expr,
4892                         Arg_Id);
4893                  end if;
4894
4895               --  Otherwise the pragma referenced an illegal entity
4896
4897               else
4898                  Error_Pragma_Arg
4899                    ("pragma% can only be applied to a variable", Arg_Expr);
4900               end if;
4901            end if;
4902
4903            Next (Arg);
4904         end loop;
4905      end Analyze_Unmodified_Or_Unused;
4906
4907      -----------------------------------
4908      -- Analyze_Unreference_Or_Unused --
4909      -----------------------------------
4910
4911      procedure Analyze_Unreferenced_Or_Unused
4912        (Is_Unused : Boolean := False)
4913      is
4914         Arg      : Node_Id;
4915         Arg_Expr : Node_Id;
4916         Arg_Id   : Entity_Id;
4917         Citem    : Node_Id;
4918
4919         Ghost_Error_Posted : Boolean := False;
4920         --  Flag set when an error concerning the illegal mix of Ghost and
4921         --  non-Ghost names is emitted.
4922
4923         Ghost_Id : Entity_Id := Empty;
4924         --  The entity of the first Ghost name encountered while processing
4925         --  the arguments of the pragma.
4926
4927      begin
4928         GNAT_Pragma;
4929         Check_At_Least_N_Arguments (1);
4930
4931         --  Check case of appearing within context clause
4932
4933         if not Is_Unused and then Is_In_Context_Clause then
4934
4935            --  The arguments must all be units mentioned in a with clause in
4936            --  the same context clause. Note that Par.Prag already checked
4937            --  that the arguments are either identifiers or selected
4938            --  components.
4939
4940            Arg := Arg1;
4941            while Present (Arg) loop
4942               Citem := First (List_Containing (N));
4943               while Citem /= N loop
4944                  Arg_Expr := Get_Pragma_Arg (Arg);
4945
4946                  if Nkind (Citem) = N_With_Clause
4947                    and then Same_Name (Name (Citem), Arg_Expr)
4948                  then
4949                     Set_Has_Pragma_Unreferenced
4950                       (Cunit_Entity
4951                         (Get_Source_Unit
4952                           (Library_Unit (Citem))));
4953                     Set_Elab_Unit_Name (Arg_Expr, Name (Citem));
4954                     exit;
4955                  end if;
4956
4957                  Next (Citem);
4958               end loop;
4959
4960               if Citem = N then
4961                  Error_Pragma_Arg
4962                    ("argument of pragma% is not withed unit", Arg);
4963               end if;
4964
4965               Next (Arg);
4966            end loop;
4967
4968         --  Case of not in list of context items
4969
4970         else
4971            Arg := Arg1;
4972            while Present (Arg) loop
4973               Check_No_Identifier (Arg);
4974
4975               --  Note: the analyze call done by Check_Arg_Is_Local_Name will
4976               --  in fact generate reference, so that the entity will have a
4977               --  reference, which will inhibit any warnings about it not
4978               --  being referenced, and also properly show up in the ali file
4979               --  as a reference. But this reference is recorded before the
4980               --  Has_Pragma_Unreferenced flag is set, so that no warning is
4981               --  generated for this reference.
4982
4983               Check_Arg_Is_Local_Name (Arg);
4984               Arg_Expr := Get_Pragma_Arg (Arg);
4985
4986               if Is_Entity_Name (Arg_Expr) then
4987                  Arg_Id := Entity (Arg_Expr);
4988
4989                  --  Warn if already flagged as Unused or Unreferenced and
4990                  --  skip processing the argument.
4991
4992                  if Has_Pragma_Unreferenced (Arg_Id) then
4993                     if Has_Pragma_Unused (Arg_Id) then
4994                        Error_Msg_NE
4995                          ("??pragma Unused already given for &!", Arg_Expr,
4996                            Arg_Id);
4997                     else
4998                        Error_Msg_NE
4999                          ("??pragma Unreferenced already given for &!",
5000                            Arg_Expr, Arg_Id);
5001                     end if;
5002
5003                  --  Apply Unreferenced to the entity
5004
5005                  else
5006                     --  If the entity is overloaded, the pragma applies to the
5007                     --  most recent overloading, as documented. In this case,
5008                     --  name resolution does not generate a reference, so it
5009                     --  must be done here explicitly.
5010
5011                     if Is_Overloaded (Arg_Expr) then
5012                        Generate_Reference (Arg_Id, N);
5013                     end if;
5014
5015                     Set_Has_Pragma_Unreferenced (Arg_Id);
5016
5017                     if Is_Unused then
5018                        Set_Has_Pragma_Unused (Arg_Id);
5019                     end if;
5020
5021                     --  A pragma that applies to a Ghost entity becomes Ghost
5022                     --  for the purposes of legality checks and removal of
5023                     --  ignored Ghost code.
5024
5025                     Mark_Ghost_Pragma (N, Arg_Id);
5026
5027                     --  Capture the entity of the first Ghost name being
5028                     --  processed for error detection purposes.
5029
5030                     if Is_Ghost_Entity (Arg_Id) then
5031                        if No (Ghost_Id) then
5032                           Ghost_Id := Arg_Id;
5033                        end if;
5034
5035                     --  Otherwise the name is non-Ghost. It is illegal to mix
5036                     --  references to Ghost and non-Ghost entities
5037                     --  (SPARK RM 6.9).
5038
5039                     elsif Present (Ghost_Id)
5040                       and then not Ghost_Error_Posted
5041                     then
5042                        Ghost_Error_Posted := True;
5043
5044                        Error_Msg_Name_1 := Pname;
5045                        Error_Msg_N
5046                          ("pragma % cannot mention ghost and non-ghost "
5047                           & "names", N);
5048
5049                        Error_Msg_Sloc := Sloc (Ghost_Id);
5050                        Error_Msg_NE
5051                          ("\& # declared as ghost", N, Ghost_Id);
5052
5053                        Error_Msg_Sloc := Sloc (Arg_Id);
5054                        Error_Msg_NE
5055                          ("\& # declared as non-ghost", N, Arg_Id);
5056                     end if;
5057                  end if;
5058               end if;
5059
5060               Next (Arg);
5061            end loop;
5062         end if;
5063      end Analyze_Unreferenced_Or_Unused;
5064
5065      --------------------------
5066      -- Check_Ada_83_Warning --
5067      --------------------------
5068
5069      procedure Check_Ada_83_Warning is
5070      begin
5071         if Ada_Version = Ada_83 and then Comes_From_Source (N) then
5072            Error_Msg_N ("(Ada 83) pragma& is non-standard??", N);
5073         end if;
5074      end Check_Ada_83_Warning;
5075
5076      ---------------------
5077      -- Check_Arg_Count --
5078      ---------------------
5079
5080      procedure Check_Arg_Count (Required : Nat) is
5081      begin
5082         if Arg_Count /= Required then
5083            Error_Pragma ("wrong number of arguments for pragma%");
5084         end if;
5085      end Check_Arg_Count;
5086
5087      --------------------------------
5088      -- Check_Arg_Is_External_Name --
5089      --------------------------------
5090
5091      procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
5092         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5093
5094      begin
5095         if Nkind (Argx) = N_Identifier then
5096            return;
5097
5098         else
5099            Analyze_And_Resolve (Argx, Standard_String);
5100
5101            if Is_OK_Static_Expression (Argx) then
5102               return;
5103
5104            elsif Etype (Argx) = Any_Type then
5105               raise Pragma_Exit;
5106
5107            --  An interesting special case, if we have a string literal and
5108            --  we are in Ada 83 mode, then we allow it even though it will
5109            --  not be flagged as static. This allows expected Ada 83 mode
5110            --  use of external names which are string literals, even though
5111            --  technically these are not static in Ada 83.
5112
5113            elsif Ada_Version = Ada_83
5114              and then Nkind (Argx) = N_String_Literal
5115            then
5116               return;
5117
5118            --  Here we have a real error (non-static expression)
5119
5120            else
5121               Error_Msg_Name_1 := Pname;
5122               Flag_Non_Static_Expr
5123                 (Fix_Error ("argument for pragma% must be a identifier or "
5124                  & "static string expression!"), Argx);
5125
5126               raise Pragma_Exit;
5127            end if;
5128         end if;
5129      end Check_Arg_Is_External_Name;
5130
5131      -----------------------------
5132      -- Check_Arg_Is_Identifier --
5133      -----------------------------
5134
5135      procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
5136         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5137      begin
5138         if Nkind (Argx) /= N_Identifier then
5139            Error_Pragma_Arg ("argument for pragma% must be identifier", Argx);
5140         end if;
5141      end Check_Arg_Is_Identifier;
5142
5143      ----------------------------------
5144      -- Check_Arg_Is_Integer_Literal --
5145      ----------------------------------
5146
5147      procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
5148         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5149      begin
5150         if Nkind (Argx) /= N_Integer_Literal then
5151            Error_Pragma_Arg
5152              ("argument for pragma% must be integer literal", Argx);
5153         end if;
5154      end Check_Arg_Is_Integer_Literal;
5155
5156      -------------------------------------------
5157      -- Check_Arg_Is_Library_Level_Local_Name --
5158      -------------------------------------------
5159
5160      --  LOCAL_NAME ::=
5161      --    DIRECT_NAME
5162      --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
5163      --  | library_unit_NAME
5164
5165      procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
5166      begin
5167         Check_Arg_Is_Local_Name (Arg);
5168
5169         --  If it came from an aspect, we want to give the error just as if it
5170         --  came from source.
5171
5172         if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
5173           and then (Comes_From_Source (N)
5174                       or else Present (Corresponding_Aspect (Parent (Arg))))
5175         then
5176            Error_Pragma_Arg
5177              ("argument for pragma% must be library level entity", Arg);
5178         end if;
5179      end Check_Arg_Is_Library_Level_Local_Name;
5180
5181      -----------------------------
5182      -- Check_Arg_Is_Local_Name --
5183      -----------------------------
5184
5185      --  LOCAL_NAME ::=
5186      --    DIRECT_NAME
5187      --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
5188      --  | library_unit_NAME
5189
5190      procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
5191         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5192
5193      begin
5194         --  If this pragma came from an aspect specification, we don't want to
5195         --  check for this error, because that would cause spurious errors, in
5196         --  case a type is frozen in a scope more nested than the type. The
5197         --  aspect itself of course can't be anywhere but on the declaration
5198         --  itself.
5199
5200         if Nkind (Arg) = N_Pragma_Argument_Association then
5201            if From_Aspect_Specification (Parent (Arg)) then
5202               return;
5203            end if;
5204
5205         --  Arg is the Expression of an N_Pragma_Argument_Association
5206
5207         else
5208            if From_Aspect_Specification (Parent (Parent (Arg))) then
5209               return;
5210            end if;
5211         end if;
5212
5213         Analyze (Argx);
5214
5215         if Nkind (Argx) not in N_Direct_Name
5216           and then (Nkind (Argx) /= N_Attribute_Reference
5217                      or else Present (Expressions (Argx))
5218                      or else Nkind (Prefix (Argx)) /= N_Identifier)
5219           and then (not Is_Entity_Name (Argx)
5220                      or else not Is_Compilation_Unit (Entity (Argx)))
5221         then
5222            Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
5223         end if;
5224
5225         --  No further check required if not an entity name
5226
5227         if not Is_Entity_Name (Argx) then
5228            null;
5229
5230         else
5231            declare
5232               OK   : Boolean;
5233               Ent  : constant Entity_Id := Entity (Argx);
5234               Scop : constant Entity_Id := Scope (Ent);
5235
5236            begin
5237               --  Case of a pragma applied to a compilation unit: pragma must
5238               --  occur immediately after the program unit in the compilation.
5239
5240               if Is_Compilation_Unit (Ent) then
5241                  declare
5242                     Decl : constant Node_Id := Unit_Declaration_Node (Ent);
5243
5244                  begin
5245                     --  Case of pragma placed immediately after spec
5246
5247                     if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
5248                        OK := True;
5249
5250                     --  Case of pragma placed immediately after body
5251
5252                     elsif Nkind (Decl) = N_Subprogram_Declaration
5253                             and then Present (Corresponding_Body (Decl))
5254                     then
5255                        OK := Parent (N) =
5256                                Aux_Decls_Node
5257                                  (Parent (Unit_Declaration_Node
5258                                             (Corresponding_Body (Decl))));
5259
5260                     --  All other cases are illegal
5261
5262                     else
5263                        OK := False;
5264                     end if;
5265                  end;
5266
5267               --  Special restricted placement rule from 10.2.1(11.8/2)
5268
5269               elsif Is_Generic_Formal (Ent)
5270                       and then Prag_Id = Pragma_Preelaborable_Initialization
5271               then
5272                  OK := List_Containing (N) =
5273                          Generic_Formal_Declarations
5274                            (Unit_Declaration_Node (Scop));
5275
5276               --  If this is an aspect applied to a subprogram body, the
5277               --  pragma is inserted in its declarative part.
5278
5279               elsif From_Aspect_Specification (N)
5280                 and then Ent = Current_Scope
5281                 and then
5282                   Nkind (Unit_Declaration_Node (Ent)) = N_Subprogram_Body
5283               then
5284                  OK := True;
5285
5286               --  If the aspect is a predicate (possibly others ???) and the
5287               --  context is a record type, this is a discriminant expression
5288               --  within a type declaration, that freezes the predicated
5289               --  subtype.
5290
5291               elsif From_Aspect_Specification (N)
5292                 and then Prag_Id = Pragma_Predicate
5293                 and then Ekind (Current_Scope) = E_Record_Type
5294                 and then Scop = Scope (Current_Scope)
5295               then
5296                  OK := True;
5297
5298               --  Default case, just check that the pragma occurs in the scope
5299               --  of the entity denoted by the name.
5300
5301               else
5302                  OK := Current_Scope = Scop;
5303               end if;
5304
5305               if not OK then
5306                  Error_Pragma_Arg
5307                    ("pragma% argument must be in same declarative part", Arg);
5308               end if;
5309            end;
5310         end if;
5311      end Check_Arg_Is_Local_Name;
5312
5313      ---------------------------------
5314      -- Check_Arg_Is_Locking_Policy --
5315      ---------------------------------
5316
5317      procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
5318         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5319
5320      begin
5321         Check_Arg_Is_Identifier (Argx);
5322
5323         if not Is_Locking_Policy_Name (Chars (Argx)) then
5324            Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
5325         end if;
5326      end Check_Arg_Is_Locking_Policy;
5327
5328      -----------------------------------------------
5329      -- Check_Arg_Is_Partition_Elaboration_Policy --
5330      -----------------------------------------------
5331
5332      procedure Check_Arg_Is_Partition_Elaboration_Policy (Arg : Node_Id) is
5333         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5334
5335      begin
5336         Check_Arg_Is_Identifier (Argx);
5337
5338         if not Is_Partition_Elaboration_Policy_Name (Chars (Argx)) then
5339            Error_Pragma_Arg
5340              ("& is not a valid partition elaboration policy name", Argx);
5341         end if;
5342      end Check_Arg_Is_Partition_Elaboration_Policy;
5343
5344      -------------------------
5345      -- Check_Arg_Is_One_Of --
5346      -------------------------
5347
5348      procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
5349         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5350
5351      begin
5352         Check_Arg_Is_Identifier (Argx);
5353
5354         if not Nam_In (Chars (Argx), N1, N2) then
5355            Error_Msg_Name_2 := N1;
5356            Error_Msg_Name_3 := N2;
5357            Error_Pragma_Arg ("argument for pragma% must be% or%", Argx);
5358         end if;
5359      end Check_Arg_Is_One_Of;
5360
5361      procedure Check_Arg_Is_One_Of
5362        (Arg        : Node_Id;
5363         N1, N2, N3 : Name_Id)
5364      is
5365         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5366
5367      begin
5368         Check_Arg_Is_Identifier (Argx);
5369
5370         if not Nam_In (Chars (Argx), N1, N2, N3) then
5371            Error_Pragma_Arg ("invalid argument for pragma%", Argx);
5372         end if;
5373      end Check_Arg_Is_One_Of;
5374
5375      procedure Check_Arg_Is_One_Of
5376        (Arg                : Node_Id;
5377         N1, N2, N3, N4     : Name_Id)
5378      is
5379         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5380
5381      begin
5382         Check_Arg_Is_Identifier (Argx);
5383
5384         if not Nam_In (Chars (Argx), N1, N2, N3, N4) then
5385            Error_Pragma_Arg ("invalid argument for pragma%", Argx);
5386         end if;
5387      end Check_Arg_Is_One_Of;
5388
5389      procedure Check_Arg_Is_One_Of
5390        (Arg                : Node_Id;
5391         N1, N2, N3, N4, N5 : Name_Id)
5392      is
5393         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5394
5395      begin
5396         Check_Arg_Is_Identifier (Argx);
5397
5398         if not Nam_In (Chars (Argx), N1, N2, N3, N4, N5) then
5399            Error_Pragma_Arg ("invalid argument for pragma%", Argx);
5400         end if;
5401      end Check_Arg_Is_One_Of;
5402
5403      ---------------------------------
5404      -- Check_Arg_Is_Queuing_Policy --
5405      ---------------------------------
5406
5407      procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
5408         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5409
5410      begin
5411         Check_Arg_Is_Identifier (Argx);
5412
5413         if not Is_Queuing_Policy_Name (Chars (Argx)) then
5414            Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
5415         end if;
5416      end Check_Arg_Is_Queuing_Policy;
5417
5418      ---------------------------------------
5419      -- Check_Arg_Is_OK_Static_Expression --
5420      ---------------------------------------
5421
5422      procedure Check_Arg_Is_OK_Static_Expression
5423        (Arg : Node_Id;
5424         Typ : Entity_Id := Empty)
5425      is
5426      begin
5427         Check_Expr_Is_OK_Static_Expression (Get_Pragma_Arg (Arg), Typ);
5428      end Check_Arg_Is_OK_Static_Expression;
5429
5430      ------------------------------------------
5431      -- Check_Arg_Is_Task_Dispatching_Policy --
5432      ------------------------------------------
5433
5434      procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
5435         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5436
5437      begin
5438         Check_Arg_Is_Identifier (Argx);
5439
5440         if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
5441            Error_Pragma_Arg
5442              ("& is not an allowed task dispatching policy name", Argx);
5443         end if;
5444      end Check_Arg_Is_Task_Dispatching_Policy;
5445
5446      ---------------------
5447      -- Check_Arg_Order --
5448      ---------------------
5449
5450      procedure Check_Arg_Order (Names : Name_List) is
5451         Arg : Node_Id;
5452
5453         Highest_So_Far : Natural := 0;
5454         --  Highest index in Names seen do far
5455
5456      begin
5457         Arg := Arg1;
5458         for J in 1 .. Arg_Count loop
5459            if Chars (Arg) /= No_Name then
5460               for K in Names'Range loop
5461                  if Chars (Arg) = Names (K) then
5462                     if K < Highest_So_Far then
5463                        Error_Msg_Name_1 := Pname;
5464                        Error_Msg_N
5465                          ("parameters out of order for pragma%", Arg);
5466                        Error_Msg_Name_1 := Names (K);
5467                        Error_Msg_Name_2 := Names (Highest_So_Far);
5468                        Error_Msg_N ("\% must appear before %", Arg);
5469                        raise Pragma_Exit;
5470
5471                     else
5472                        Highest_So_Far := K;
5473                     end if;
5474                  end if;
5475               end loop;
5476            end if;
5477
5478            Arg := Next (Arg);
5479         end loop;
5480      end Check_Arg_Order;
5481
5482      --------------------------------
5483      -- Check_At_Least_N_Arguments --
5484      --------------------------------
5485
5486      procedure Check_At_Least_N_Arguments (N : Nat) is
5487      begin
5488         if Arg_Count < N then
5489            Error_Pragma ("too few arguments for pragma%");
5490         end if;
5491      end Check_At_Least_N_Arguments;
5492
5493      -------------------------------
5494      -- Check_At_Most_N_Arguments --
5495      -------------------------------
5496
5497      procedure Check_At_Most_N_Arguments (N : Nat) is
5498         Arg : Node_Id;
5499      begin
5500         if Arg_Count > N then
5501            Arg := Arg1;
5502            for J in 1 .. N loop
5503               Next (Arg);
5504               Error_Pragma_Arg ("too many arguments for pragma%", Arg);
5505            end loop;
5506         end if;
5507      end Check_At_Most_N_Arguments;
5508
5509      ---------------------
5510      -- Check_Component --
5511      ---------------------
5512
5513      procedure Check_Component
5514        (Comp            : Node_Id;
5515         UU_Typ          : Entity_Id;
5516         In_Variant_Part : Boolean := False)
5517      is
5518         Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
5519         Sindic  : constant Node_Id :=
5520                     Subtype_Indication (Component_Definition (Comp));
5521         Typ     : constant Entity_Id := Etype (Comp_Id);
5522
5523      begin
5524         --  Ada 2005 (AI-216): If a component subtype is subject to a per-
5525         --  object constraint, then the component type shall be an Unchecked_
5526         --  Union.
5527
5528         if Nkind (Sindic) = N_Subtype_Indication
5529           and then Has_Per_Object_Constraint (Comp_Id)
5530           and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
5531         then
5532            Error_Msg_N
5533              ("component subtype subject to per-object constraint "
5534               & "must be an Unchecked_Union", Comp);
5535
5536         --  Ada 2012 (AI05-0026): For an unchecked union type declared within
5537         --  the body of a generic unit, or within the body of any of its
5538         --  descendant library units, no part of the type of a component
5539         --  declared in a variant_part of the unchecked union type shall be of
5540         --  a formal private type or formal private extension declared within
5541         --  the formal part of the generic unit.
5542
5543         elsif Ada_Version >= Ada_2012
5544           and then In_Generic_Body (UU_Typ)
5545           and then In_Variant_Part
5546           and then Is_Private_Type (Typ)
5547           and then Is_Generic_Type (Typ)
5548         then
5549            Error_Msg_N
5550              ("component of unchecked union cannot be of generic type", Comp);
5551
5552         elsif Needs_Finalization (Typ) then
5553            Error_Msg_N
5554              ("component of unchecked union cannot be controlled", Comp);
5555
5556         elsif Has_Task (Typ) then
5557            Error_Msg_N
5558              ("component of unchecked union cannot have tasks", Comp);
5559         end if;
5560      end Check_Component;
5561
5562      ----------------------------
5563      -- Check_Duplicate_Pragma --
5564      ----------------------------
5565
5566      procedure Check_Duplicate_Pragma (E : Entity_Id) is
5567         Id : Entity_Id := E;
5568         P  : Node_Id;
5569
5570      begin
5571         --  Nothing to do if this pragma comes from an aspect specification,
5572         --  since we could not be duplicating a pragma, and we dealt with the
5573         --  case of duplicated aspects in Analyze_Aspect_Specifications.
5574
5575         if From_Aspect_Specification (N) then
5576            return;
5577         end if;
5578
5579         --  Otherwise current pragma may duplicate previous pragma or a
5580         --  previously given aspect specification or attribute definition
5581         --  clause for the same pragma.
5582
5583         P := Get_Rep_Item (E, Pragma_Name (N), Check_Parents => False);
5584
5585         if Present (P) then
5586
5587            --  If the entity is a type, then we have to make sure that the
5588            --  ostensible duplicate is not for a parent type from which this
5589            --  type is derived.
5590
5591            if Is_Type (E) then
5592               if Nkind (P) = N_Pragma then
5593                  declare
5594                     Args : constant List_Id :=
5595                              Pragma_Argument_Associations (P);
5596                  begin
5597                     if Present (Args)
5598                       and then Is_Entity_Name (Expression (First (Args)))
5599                       and then Is_Type (Entity (Expression (First (Args))))
5600                       and then Entity (Expression (First (Args))) /= E
5601                     then
5602                        return;
5603                     end if;
5604                  end;
5605
5606               elsif Nkind (P) = N_Aspect_Specification
5607                 and then Is_Type (Entity (P))
5608                 and then Entity (P) /= E
5609               then
5610                  return;
5611               end if;
5612            end if;
5613
5614            --  Here we have a definite duplicate
5615
5616            Error_Msg_Name_1 := Pragma_Name (N);
5617            Error_Msg_Sloc := Sloc (P);
5618
5619            --  For a single protected or a single task object, the error is
5620            --  issued on the original entity.
5621
5622            if Ekind_In (Id, E_Task_Type, E_Protected_Type) then
5623               Id := Defining_Identifier (Original_Node (Parent (Id)));
5624            end if;
5625
5626            if Nkind (P) = N_Aspect_Specification
5627              or else From_Aspect_Specification (P)
5628            then
5629               Error_Msg_NE ("aspect% for & previously given#", N, Id);
5630            else
5631               Error_Msg_NE ("pragma% for & duplicates pragma#", N, Id);
5632            end if;
5633
5634            raise Pragma_Exit;
5635         end if;
5636      end Check_Duplicate_Pragma;
5637
5638      ----------------------------------
5639      -- Check_Duplicated_Export_Name --
5640      ----------------------------------
5641
5642      procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
5643         String_Val : constant String_Id := Strval (Nam);
5644
5645      begin
5646         --  We are only interested in the export case, and in the case of
5647         --  generics, it is the instance, not the template, that is the
5648         --  problem (the template will generate a warning in any case).
5649
5650         if not Inside_A_Generic
5651           and then (Prag_Id = Pragma_Export
5652                       or else
5653                     Prag_Id = Pragma_Export_Procedure
5654                       or else
5655                     Prag_Id = Pragma_Export_Valued_Procedure
5656                       or else
5657                     Prag_Id = Pragma_Export_Function)
5658         then
5659            for J in Externals.First .. Externals.Last loop
5660               if String_Equal (String_Val, Strval (Externals.Table (J))) then
5661                  Error_Msg_Sloc := Sloc (Externals.Table (J));
5662                  Error_Msg_N ("external name duplicates name given#", Nam);
5663                  exit;
5664               end if;
5665            end loop;
5666
5667            Externals.Append (Nam);
5668         end if;
5669      end Check_Duplicated_Export_Name;
5670
5671      ----------------------------------------
5672      -- Check_Expr_Is_OK_Static_Expression --
5673      ----------------------------------------
5674
5675      procedure Check_Expr_Is_OK_Static_Expression
5676        (Expr : Node_Id;
5677         Typ  : Entity_Id := Empty)
5678      is
5679      begin
5680         if Present (Typ) then
5681            Analyze_And_Resolve (Expr, Typ);
5682         else
5683            Analyze_And_Resolve (Expr);
5684         end if;
5685
5686         --  An expression cannot be considered static if its resolution failed
5687         --  or if it's erroneous. Stop the analysis of the related pragma.
5688
5689         if Etype (Expr) = Any_Type or else Error_Posted (Expr) then
5690            raise Pragma_Exit;
5691
5692         elsif Is_OK_Static_Expression (Expr) then
5693            return;
5694
5695         --  An interesting special case, if we have a string literal and we
5696         --  are in Ada 83 mode, then we allow it even though it will not be
5697         --  flagged as static. This allows the use of Ada 95 pragmas like
5698         --  Import in Ada 83 mode. They will of course be flagged with
5699         --  warnings as usual, but will not cause errors.
5700
5701         elsif Ada_Version = Ada_83
5702           and then Nkind (Expr) = N_String_Literal
5703         then
5704            return;
5705
5706         --  Finally, we have a real error
5707
5708         else
5709            Error_Msg_Name_1 := Pname;
5710            Flag_Non_Static_Expr
5711              (Fix_Error ("argument for pragma% must be a static expression!"),
5712               Expr);
5713            raise Pragma_Exit;
5714         end if;
5715      end Check_Expr_Is_OK_Static_Expression;
5716
5717      -------------------------
5718      -- Check_First_Subtype --
5719      -------------------------
5720
5721      procedure Check_First_Subtype (Arg : Node_Id) is
5722         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
5723         Ent  : constant Entity_Id := Entity (Argx);
5724
5725      begin
5726         if Is_First_Subtype (Ent) then
5727            null;
5728
5729         elsif Is_Type (Ent) then
5730            Error_Pragma_Arg
5731              ("pragma% cannot apply to subtype", Argx);
5732
5733         elsif Is_Object (Ent) then
5734            Error_Pragma_Arg
5735              ("pragma% cannot apply to object, requires a type", Argx);
5736
5737         else
5738            Error_Pragma_Arg
5739              ("pragma% cannot apply to&, requires a type", Argx);
5740         end if;
5741      end Check_First_Subtype;
5742
5743      ----------------------
5744      -- Check_Identifier --
5745      ----------------------
5746
5747      procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
5748      begin
5749         if Present (Arg)
5750           and then Nkind (Arg) = N_Pragma_Argument_Association
5751         then
5752            if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
5753               Error_Msg_Name_1 := Pname;
5754               Error_Msg_Name_2 := Id;
5755               Error_Msg_N ("pragma% argument expects identifier%", Arg);
5756               raise Pragma_Exit;
5757            end if;
5758         end if;
5759      end Check_Identifier;
5760
5761      --------------------------------
5762      -- Check_Identifier_Is_One_Of --
5763      --------------------------------
5764
5765      procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
5766      begin
5767         if Present (Arg)
5768           and then Nkind (Arg) = N_Pragma_Argument_Association
5769         then
5770            if Chars (Arg) = No_Name then
5771               Error_Msg_Name_1 := Pname;
5772               Error_Msg_N ("pragma% argument expects an identifier", Arg);
5773               raise Pragma_Exit;
5774
5775            elsif Chars (Arg) /= N1
5776              and then Chars (Arg) /= N2
5777            then
5778               Error_Msg_Name_1 := Pname;
5779               Error_Msg_N ("invalid identifier for pragma% argument", Arg);
5780               raise Pragma_Exit;
5781            end if;
5782         end if;
5783      end Check_Identifier_Is_One_Of;
5784
5785      ---------------------------
5786      -- Check_In_Main_Program --
5787      ---------------------------
5788
5789      procedure Check_In_Main_Program is
5790         P : constant Node_Id := Parent (N);
5791
5792      begin
5793         --  Must be in subprogram body
5794
5795         if Nkind (P) /= N_Subprogram_Body then
5796            Error_Pragma ("% pragma allowed only in subprogram");
5797
5798         --  Otherwise warn if obviously not main program
5799
5800         elsif Present (Parameter_Specifications (Specification (P)))
5801           or else not Is_Compilation_Unit (Defining_Entity (P))
5802         then
5803            Error_Msg_Name_1 := Pname;
5804            Error_Msg_N
5805              ("??pragma% is only effective in main program", N);
5806         end if;
5807      end Check_In_Main_Program;
5808
5809      ---------------------------------------
5810      -- Check_Interrupt_Or_Attach_Handler --
5811      ---------------------------------------
5812
5813      procedure Check_Interrupt_Or_Attach_Handler is
5814         Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
5815         Handler_Proc, Proc_Scope : Entity_Id;
5816
5817      begin
5818         Analyze (Arg1_X);
5819
5820         if Prag_Id = Pragma_Interrupt_Handler then
5821            Check_Restriction (No_Dynamic_Attachment, N);
5822         end if;
5823
5824         Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
5825         Proc_Scope := Scope (Handler_Proc);
5826
5827         if Ekind (Proc_Scope) /= E_Protected_Type then
5828            Error_Pragma_Arg
5829              ("argument of pragma% must be protected procedure", Arg1);
5830         end if;
5831
5832         --  For pragma case (as opposed to access case), check placement.
5833         --  We don't need to do that for aspects, because we have the
5834         --  check that they aspect applies an appropriate procedure.
5835
5836         if not From_Aspect_Specification (N)
5837           and then Parent (N) /= Protected_Definition (Parent (Proc_Scope))
5838         then
5839            Error_Pragma ("pragma% must be in protected definition");
5840         end if;
5841
5842         if not Is_Library_Level_Entity (Proc_Scope) then
5843            Error_Pragma_Arg
5844              ("argument for pragma% must be library level entity", Arg1);
5845         end if;
5846
5847         --  AI05-0033: A pragma cannot appear within a generic body, because
5848         --  instance can be in a nested scope. The check that protected type
5849         --  is itself a library-level declaration is done elsewhere.
5850
5851         --  Note: we omit this check in Relaxed_RM_Semantics mode to properly
5852         --  handle code prior to AI-0033. Analysis tools typically are not
5853         --  interested in this pragma in any case, so no need to worry too
5854         --  much about its placement.
5855
5856         if Inside_A_Generic then
5857            if Ekind (Scope (Current_Scope)) = E_Generic_Package
5858              and then In_Package_Body (Scope (Current_Scope))
5859              and then not Relaxed_RM_Semantics
5860            then
5861               Error_Pragma ("pragma% cannot be used inside a generic");
5862            end if;
5863         end if;
5864      end Check_Interrupt_Or_Attach_Handler;
5865
5866      ---------------------------------
5867      -- Check_Loop_Pragma_Placement --
5868      ---------------------------------
5869
5870      procedure Check_Loop_Pragma_Placement is
5871         procedure Check_Loop_Pragma_Grouping (Loop_Stmt : Node_Id);
5872         --  Verify whether the current pragma is properly grouped with other
5873         --  pragma Loop_Invariant and/or Loop_Variant. Node Loop_Stmt is the
5874         --  related loop where the pragma appears.
5875
5876         function Is_Loop_Pragma (Stmt : Node_Id) return Boolean;
5877         --  Determine whether an arbitrary statement Stmt denotes pragma
5878         --  Loop_Invariant or Loop_Variant.
5879
5880         procedure Placement_Error (Constr : Node_Id);
5881         pragma No_Return (Placement_Error);
5882         --  Node Constr denotes the last loop restricted construct before we
5883         --  encountered an illegal relation between enclosing constructs. Emit
5884         --  an error depending on what Constr was.
5885
5886         --------------------------------
5887         -- Check_Loop_Pragma_Grouping --
5888         --------------------------------
5889
5890         procedure Check_Loop_Pragma_Grouping (Loop_Stmt : Node_Id) is
5891            Stop_Search : exception;
5892            --  This exception is used to terminate the recursive descent of
5893            --  routine Check_Grouping.
5894
5895            procedure Check_Grouping (L : List_Id);
5896            --  Find the first group of pragmas in list L and if successful,
5897            --  ensure that the current pragma is part of that group. The
5898            --  routine raises Stop_Search once such a check is performed to
5899            --  halt the recursive descent.
5900
5901            procedure Grouping_Error (Prag : Node_Id);
5902            pragma No_Return (Grouping_Error);
5903            --  Emit an error concerning the current pragma indicating that it
5904            --  should be placed after pragma Prag.
5905
5906            --------------------
5907            -- Check_Grouping --
5908            --------------------
5909
5910            procedure Check_Grouping (L : List_Id) is
5911               HSS  : Node_Id;
5912               Stmt : Node_Id;
5913               Prag : Node_Id := Empty; -- init to avoid warning
5914
5915            begin
5916               --  Inspect the list of declarations or statements looking for
5917               --  the first grouping of pragmas:
5918
5919               --    loop
5920               --       pragma Loop_Invariant ...;
5921               --       pragma Loop_Variant ...;
5922               --       . . .                     -- (1)
5923               --       pragma Loop_Variant ...;  --  current pragma
5924
5925               --  If the current pragma is not in the grouping, then it must
5926               --  either appear in a different declarative or statement list
5927               --  or the construct at (1) is separating the pragma from the
5928               --  grouping.
5929
5930               Stmt := First (L);
5931               while Present (Stmt) loop
5932
5933                  --  Pragmas Loop_Invariant and Loop_Variant may only appear
5934                  --  inside a loop or a block housed inside a loop. Inspect
5935                  --  the declarations and statements of the block as they may
5936                  --  contain the first grouping.
5937
5938                  if Nkind (Stmt) = N_Block_Statement then
5939                     HSS := Handled_Statement_Sequence (Stmt);
5940
5941                     Check_Grouping (Declarations (Stmt));
5942
5943                     if Present (HSS) then
5944                        Check_Grouping (Statements (HSS));
5945                     end if;
5946
5947                  --  First pragma of the first topmost grouping has been found
5948
5949                  elsif Is_Loop_Pragma (Stmt) then
5950
5951                     --  The group and the current pragma are not in the same
5952                     --  declarative or statement list.
5953
5954                     if List_Containing (Stmt) /= List_Containing (N) then
5955                        Grouping_Error (Stmt);
5956
5957                     --  Try to reach the current pragma from the first pragma
5958                     --  of the grouping while skipping other members:
5959
5960                     --    pragma Loop_Invariant ...;  --  first pragma
5961                     --    pragma Loop_Variant ...;    --  member
5962                     --    . . .
5963                     --    pragma Loop_Variant ...;    --  current pragma
5964
5965                     else
5966                        while Present (Stmt) loop
5967                           --  The current pragma is either the first pragma
5968                           --  of the group or is a member of the group.
5969                           --  Stop the search as the placement is legal.
5970
5971                           if Stmt = N then
5972                              raise Stop_Search;
5973
5974                           --  Skip group members, but keep track of the
5975                           --  last pragma in the group.
5976
5977                           elsif Is_Loop_Pragma (Stmt) then
5978                              Prag := Stmt;
5979
5980                           --  Skip declarations and statements generated by
5981                           --  the compiler during expansion.
5982
5983                           elsif not Comes_From_Source (Stmt) then
5984                              null;
5985
5986                           --  A non-pragma is separating the group from the
5987                           --  current pragma, the placement is illegal.
5988
5989                           else
5990                              Grouping_Error (Prag);
5991                           end if;
5992
5993                           Next (Stmt);
5994                        end loop;
5995
5996                        --  If the traversal did not reach the current pragma,
5997                        --  then the list must be malformed.
5998
5999                        raise Program_Error;
6000                     end if;
6001                  end if;
6002
6003                  Next (Stmt);
6004               end loop;
6005            end Check_Grouping;
6006
6007            --------------------
6008            -- Grouping_Error --
6009            --------------------
6010
6011            procedure Grouping_Error (Prag : Node_Id) is
6012            begin
6013               Error_Msg_Sloc := Sloc (Prag);
6014               Error_Pragma ("pragma% must appear next to pragma#");
6015            end Grouping_Error;
6016
6017         --  Start of processing for Check_Loop_Pragma_Grouping
6018
6019         begin
6020            --  Inspect the statements of the loop or nested blocks housed
6021            --  within to determine whether the current pragma is part of the
6022            --  first topmost grouping of Loop_Invariant and Loop_Variant.
6023
6024            Check_Grouping (Statements (Loop_Stmt));
6025
6026         exception
6027            when Stop_Search => null;
6028         end Check_Loop_Pragma_Grouping;
6029
6030         --------------------
6031         -- Is_Loop_Pragma --
6032         --------------------
6033
6034         function Is_Loop_Pragma (Stmt : Node_Id) return Boolean is
6035         begin
6036            --  Inspect the original node as Loop_Invariant and Loop_Variant
6037            --  pragmas are rewritten to null when assertions are disabled.
6038
6039            if Nkind (Original_Node (Stmt)) = N_Pragma then
6040               return
6041                 Nam_In (Pragma_Name_Unmapped (Original_Node (Stmt)),
6042                         Name_Loop_Invariant,
6043                         Name_Loop_Variant);
6044            else
6045               return False;
6046            end if;
6047         end Is_Loop_Pragma;
6048
6049         ---------------------
6050         -- Placement_Error --
6051         ---------------------
6052
6053         procedure Placement_Error (Constr : Node_Id) is
6054            LA : constant String := " with Loop_Entry";
6055
6056         begin
6057            if Prag_Id = Pragma_Assert then
6058               Error_Msg_String (1 .. LA'Length) := LA;
6059               Error_Msg_Strlen := LA'Length;
6060            else
6061               Error_Msg_Strlen := 0;
6062            end if;
6063
6064            if Nkind (Constr) = N_Pragma then
6065               Error_Pragma
6066                 ("pragma %~ must appear immediately within the statements "
6067                  & "of a loop");
6068            else
6069               Error_Pragma_Arg
6070                 ("block containing pragma %~ must appear immediately within "
6071                  & "the statements of a loop", Constr);
6072            end if;
6073         end Placement_Error;
6074
6075         --  Local declarations
6076
6077         Prev : Node_Id;
6078         Stmt : Node_Id;
6079
6080      --  Start of processing for Check_Loop_Pragma_Placement
6081
6082      begin
6083         --  Check that pragma appears immediately within a loop statement,
6084         --  ignoring intervening block statements.
6085
6086         Prev := N;
6087         Stmt := Parent (N);
6088         while Present (Stmt) loop
6089
6090            --  The pragma or previous block must appear immediately within the
6091            --  current block's declarative or statement part.
6092
6093            if Nkind (Stmt) = N_Block_Statement then
6094               if (No (Declarations (Stmt))
6095                    or else List_Containing (Prev) /= Declarations (Stmt))
6096                 and then
6097                   List_Containing (Prev) /=
6098                     Statements (Handled_Statement_Sequence (Stmt))
6099               then
6100                  Placement_Error (Prev);
6101                  return;
6102
6103               --  Keep inspecting the parents because we are now within a
6104               --  chain of nested blocks.
6105
6106               else
6107                  Prev := Stmt;
6108                  Stmt := Parent (Stmt);
6109               end if;
6110
6111            --  The pragma or previous block must appear immediately within the
6112            --  statements of the loop.
6113
6114            elsif Nkind (Stmt) = N_Loop_Statement then
6115               if List_Containing (Prev) /= Statements (Stmt) then
6116                  Placement_Error (Prev);
6117               end if;
6118
6119               --  Stop the traversal because we reached the innermost loop
6120               --  regardless of whether we encountered an error or not.
6121
6122               exit;
6123
6124            --  Ignore a handled statement sequence. Note that this node may
6125            --  be related to a subprogram body in which case we will emit an
6126            --  error on the next iteration of the search.
6127
6128            elsif Nkind (Stmt) = N_Handled_Sequence_Of_Statements then
6129               Stmt := Parent (Stmt);
6130
6131            --  Any other statement breaks the chain from the pragma to the
6132            --  loop.
6133
6134            else
6135               Placement_Error (Prev);
6136               return;
6137            end if;
6138         end loop;
6139
6140         --  Check that the current pragma Loop_Invariant or Loop_Variant is
6141         --  grouped together with other such pragmas.
6142
6143         if Is_Loop_Pragma (N) then
6144
6145            --  The previous check should have located the related loop
6146
6147            pragma Assert (Nkind (Stmt) = N_Loop_Statement);
6148            Check_Loop_Pragma_Grouping (Stmt);
6149         end if;
6150      end Check_Loop_Pragma_Placement;
6151
6152      -------------------------------------------
6153      -- Check_Is_In_Decl_Part_Or_Package_Spec --
6154      -------------------------------------------
6155
6156      procedure Check_Is_In_Decl_Part_Or_Package_Spec is
6157         P : Node_Id;
6158
6159      begin
6160         P := Parent (N);
6161         loop
6162            if No (P) then
6163               exit;
6164
6165            elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
6166               exit;
6167
6168            elsif Nkind_In (P, N_Package_Specification,
6169                               N_Block_Statement)
6170            then
6171               return;
6172
6173            --  Note: the following tests seem a little peculiar, because
6174            --  they test for bodies, but if we were in the statement part
6175            --  of the body, we would already have hit the handled statement
6176            --  sequence, so the only way we get here is by being in the
6177            --  declarative part of the body.
6178
6179            elsif Nkind_In (P, N_Subprogram_Body,
6180                               N_Package_Body,
6181                               N_Task_Body,
6182                               N_Entry_Body)
6183            then
6184               return;
6185            end if;
6186
6187            P := Parent (P);
6188         end loop;
6189
6190         Error_Pragma ("pragma% is not in declarative part or package spec");
6191      end Check_Is_In_Decl_Part_Or_Package_Spec;
6192
6193      -------------------------
6194      -- Check_No_Identifier --
6195      -------------------------
6196
6197      procedure Check_No_Identifier (Arg : Node_Id) is
6198      begin
6199         if Nkind (Arg) = N_Pragma_Argument_Association
6200           and then Chars (Arg) /= No_Name
6201         then
6202            Error_Pragma_Arg_Ident
6203              ("pragma% does not permit identifier& here", Arg);
6204         end if;
6205      end Check_No_Identifier;
6206
6207      --------------------------
6208      -- Check_No_Identifiers --
6209      --------------------------
6210
6211      procedure Check_No_Identifiers is
6212         Arg_Node : Node_Id;
6213      begin
6214         Arg_Node := Arg1;
6215         for J in 1 .. Arg_Count loop
6216            Check_No_Identifier (Arg_Node);
6217            Next (Arg_Node);
6218         end loop;
6219      end Check_No_Identifiers;
6220
6221      ------------------------
6222      -- Check_No_Link_Name --
6223      ------------------------
6224
6225      procedure Check_No_Link_Name is
6226      begin
6227         if Present (Arg3) and then Chars (Arg3) = Name_Link_Name then
6228            Arg4 := Arg3;
6229         end if;
6230
6231         if Present (Arg4) then
6232            Error_Pragma_Arg
6233              ("Link_Name argument not allowed for Import Intrinsic", Arg4);
6234         end if;
6235      end Check_No_Link_Name;
6236
6237      -------------------------------
6238      -- Check_Optional_Identifier --
6239      -------------------------------
6240
6241      procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
6242      begin
6243         if Present (Arg)
6244           and then Nkind (Arg) = N_Pragma_Argument_Association
6245           and then Chars (Arg) /= No_Name
6246         then
6247            if Chars (Arg) /= Id then
6248               Error_Msg_Name_1 := Pname;
6249               Error_Msg_Name_2 := Id;
6250               Error_Msg_N ("pragma% argument expects identifier%", Arg);
6251               raise Pragma_Exit;
6252            end if;
6253         end if;
6254      end Check_Optional_Identifier;
6255
6256      procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
6257      begin
6258         Check_Optional_Identifier (Arg, Name_Find (Id));
6259      end Check_Optional_Identifier;
6260
6261      -------------------------------------
6262      -- Check_Static_Boolean_Expression --
6263      -------------------------------------
6264
6265      procedure Check_Static_Boolean_Expression (Expr : Node_Id) is
6266      begin
6267         if Present (Expr) then
6268            Analyze_And_Resolve (Expr, Standard_Boolean);
6269
6270            if not Is_OK_Static_Expression (Expr) then
6271               Error_Pragma_Arg
6272                 ("expression of pragma % must be static", Expr);
6273            end if;
6274         end if;
6275      end Check_Static_Boolean_Expression;
6276
6277      -----------------------------
6278      -- Check_Static_Constraint --
6279      -----------------------------
6280
6281      --  Note: for convenience in writing this procedure, in addition to
6282      --  the officially (i.e. by spec) allowed argument which is always a
6283      --  constraint, it also allows ranges and discriminant associations.
6284      --  Above is not clear ???
6285
6286      procedure Check_Static_Constraint (Constr : Node_Id) is
6287
6288         procedure Require_Static (E : Node_Id);
6289         --  Require given expression to be static expression
6290
6291         --------------------
6292         -- Require_Static --
6293         --------------------
6294
6295         procedure Require_Static (E : Node_Id) is
6296         begin
6297            if not Is_OK_Static_Expression (E) then
6298               Flag_Non_Static_Expr
6299                 ("non-static constraint not allowed in Unchecked_Union!", E);
6300               raise Pragma_Exit;
6301            end if;
6302         end Require_Static;
6303
6304      --  Start of processing for Check_Static_Constraint
6305
6306      begin
6307         case Nkind (Constr) is
6308            when N_Discriminant_Association =>
6309               Require_Static (Expression (Constr));
6310
6311            when N_Range =>
6312               Require_Static (Low_Bound (Constr));
6313               Require_Static (High_Bound (Constr));
6314
6315            when N_Attribute_Reference =>
6316               Require_Static (Type_Low_Bound  (Etype (Prefix (Constr))));
6317               Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
6318
6319            when N_Range_Constraint =>
6320               Check_Static_Constraint (Range_Expression (Constr));
6321
6322            when N_Index_Or_Discriminant_Constraint =>
6323               declare
6324                  IDC : Entity_Id;
6325               begin
6326                  IDC := First (Constraints (Constr));
6327                  while Present (IDC) loop
6328                     Check_Static_Constraint (IDC);
6329                     Next (IDC);
6330                  end loop;
6331               end;
6332
6333            when others =>
6334               null;
6335         end case;
6336      end Check_Static_Constraint;
6337
6338      --------------------------------------
6339      -- Check_Valid_Configuration_Pragma --
6340      --------------------------------------
6341
6342      --  A configuration pragma must appear in the context clause of a
6343      --  compilation unit, and only other pragmas may precede it. Note that
6344      --  the test also allows use in a configuration pragma file.
6345
6346      procedure Check_Valid_Configuration_Pragma is
6347      begin
6348         if not Is_Configuration_Pragma then
6349            Error_Pragma ("incorrect placement for configuration pragma%");
6350         end if;
6351      end Check_Valid_Configuration_Pragma;
6352
6353      -------------------------------------
6354      -- Check_Valid_Library_Unit_Pragma --
6355      -------------------------------------
6356
6357      procedure Check_Valid_Library_Unit_Pragma is
6358         Plist       : List_Id;
6359         Parent_Node : Node_Id;
6360         Unit_Name   : Entity_Id;
6361         Unit_Kind   : Node_Kind;
6362         Unit_Node   : Node_Id;
6363         Sindex      : Source_File_Index;
6364
6365      begin
6366         if not Is_List_Member (N) then
6367            Pragma_Misplaced;
6368
6369         else
6370            Plist := List_Containing (N);
6371            Parent_Node := Parent (Plist);
6372
6373            if Parent_Node = Empty then
6374               Pragma_Misplaced;
6375
6376            --  Case of pragma appearing after a compilation unit. In this case
6377            --  it must have an argument with the corresponding name and must
6378            --  be part of the following pragmas of its parent.
6379
6380            elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
6381               if Plist /= Pragmas_After (Parent_Node) then
6382                  Pragma_Misplaced;
6383
6384               elsif Arg_Count = 0 then
6385                  Error_Pragma
6386                    ("argument required if outside compilation unit");
6387
6388               else
6389                  Check_No_Identifiers;
6390                  Check_Arg_Count (1);
6391                  Unit_Node := Unit (Parent (Parent_Node));
6392                  Unit_Kind := Nkind (Unit_Node);
6393
6394                  Analyze (Get_Pragma_Arg (Arg1));
6395
6396                  if Unit_Kind = N_Generic_Subprogram_Declaration
6397                    or else Unit_Kind = N_Subprogram_Declaration
6398                  then
6399                     Unit_Name := Defining_Entity (Unit_Node);
6400
6401                  elsif Unit_Kind in N_Generic_Instantiation then
6402                     Unit_Name := Defining_Entity (Unit_Node);
6403
6404                  else
6405                     Unit_Name := Cunit_Entity (Current_Sem_Unit);
6406                  end if;
6407
6408                  if Chars (Unit_Name) /=
6409                     Chars (Entity (Get_Pragma_Arg (Arg1)))
6410                  then
6411                     Error_Pragma_Arg
6412                       ("pragma% argument is not current unit name", Arg1);
6413                  end if;
6414
6415                  if Ekind (Unit_Name) = E_Package
6416                    and then Present (Renamed_Entity (Unit_Name))
6417                  then
6418                     Error_Pragma ("pragma% not allowed for renamed package");
6419                  end if;
6420               end if;
6421
6422            --  Pragma appears other than after a compilation unit
6423
6424            else
6425               --  Here we check for the generic instantiation case and also
6426               --  for the case of processing a generic formal package. We
6427               --  detect these cases by noting that the Sloc on the node
6428               --  does not belong to the current compilation unit.
6429
6430               Sindex := Source_Index (Current_Sem_Unit);
6431
6432               if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
6433                  Rewrite (N, Make_Null_Statement (Loc));
6434                  return;
6435
6436               --  If before first declaration, the pragma applies to the
6437               --  enclosing unit, and the name if present must be this name.
6438
6439               elsif Is_Before_First_Decl (N, Plist) then
6440                  Unit_Node := Unit_Declaration_Node (Current_Scope);
6441                  Unit_Kind := Nkind (Unit_Node);
6442
6443                  if Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
6444                     Pragma_Misplaced;
6445
6446                  elsif Unit_Kind = N_Subprogram_Body
6447                    and then not Acts_As_Spec (Unit_Node)
6448                  then
6449                     Pragma_Misplaced;
6450
6451                  elsif Nkind (Parent_Node) = N_Package_Body then
6452                     Pragma_Misplaced;
6453
6454                  elsif Nkind (Parent_Node) = N_Package_Specification
6455                    and then Plist = Private_Declarations (Parent_Node)
6456                  then
6457                     Pragma_Misplaced;
6458
6459                  elsif (Nkind (Parent_Node) = N_Generic_Package_Declaration
6460                          or else Nkind (Parent_Node) =
6461                                             N_Generic_Subprogram_Declaration)
6462                    and then Plist = Generic_Formal_Declarations (Parent_Node)
6463                  then
6464                     Pragma_Misplaced;
6465
6466                  elsif Arg_Count > 0 then
6467                     Analyze (Get_Pragma_Arg (Arg1));
6468
6469                     if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
6470                        Error_Pragma_Arg
6471                          ("name in pragma% must be enclosing unit", Arg1);
6472                     end if;
6473
6474                  --  It is legal to have no argument in this context
6475
6476                  else
6477                     return;
6478                  end if;
6479
6480               --  Error if not before first declaration. This is because a
6481               --  library unit pragma argument must be the name of a library
6482               --  unit (RM 10.1.5(7)), but the only names permitted in this
6483               --  context are (RM 10.1.5(6)) names of subprogram declarations,
6484               --  generic subprogram declarations or generic instantiations.
6485
6486               else
6487                  Error_Pragma
6488                    ("pragma% misplaced, must be before first declaration");
6489               end if;
6490            end if;
6491         end if;
6492      end Check_Valid_Library_Unit_Pragma;
6493
6494      -------------------
6495      -- Check_Variant --
6496      -------------------
6497
6498      procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
6499         Clist : constant Node_Id := Component_List (Variant);
6500         Comp  : Node_Id;
6501
6502      begin
6503         Comp := First_Non_Pragma (Component_Items (Clist));
6504         while Present (Comp) loop
6505            Check_Component (Comp, UU_Typ, In_Variant_Part => True);
6506            Next_Non_Pragma (Comp);
6507         end loop;
6508      end Check_Variant;
6509
6510      ---------------------------
6511      -- Ensure_Aggregate_Form --
6512      ---------------------------
6513
6514      procedure Ensure_Aggregate_Form (Arg : Node_Id) is
6515         CFSD    : constant Boolean    := Get_Comes_From_Source_Default;
6516         Expr    : constant Node_Id    := Expression (Arg);
6517         Loc     : constant Source_Ptr := Sloc (Expr);
6518         Comps   : List_Id := No_List;
6519         Exprs   : List_Id := No_List;
6520         Nam     : Name_Id := No_Name;
6521         Nam_Loc : Source_Ptr;
6522
6523      begin
6524         --  The pragma argument is in positional form:
6525
6526         --    pragma Depends (Nam => ...)
6527         --                    ^
6528         --                    Chars field
6529
6530         --  Note that the Sloc of the Chars field is the Sloc of the pragma
6531         --  argument association.
6532
6533         if Nkind (Arg) = N_Pragma_Argument_Association then
6534            Nam     := Chars (Arg);
6535            Nam_Loc := Sloc (Arg);
6536
6537            --  Remove the pragma argument name as this will be captured in the
6538            --  aggregate.
6539
6540            Set_Chars (Arg, No_Name);
6541         end if;
6542
6543         --  The argument is already in aggregate form, but the presence of a
6544         --  name causes this to be interpreted as named association which in
6545         --  turn must be converted into an aggregate.
6546
6547         --    pragma Global (In_Out => (A, B, C))
6548         --                   ^         ^
6549         --                   name      aggregate
6550
6551         --    pragma Global ((In_Out => (A, B, C)))
6552         --                   ^          ^
6553         --                   aggregate  aggregate
6554
6555         if Nkind (Expr) = N_Aggregate then
6556            if Nam = No_Name then
6557               return;
6558            end if;
6559
6560         --  Do not transform a null argument into an aggregate as N_Null has
6561         --  special meaning in formal verification pragmas.
6562
6563         elsif Nkind (Expr) = N_Null then
6564            return;
6565         end if;
6566
6567         --  Everything comes from source if the original comes from source
6568
6569         Set_Comes_From_Source_Default (Comes_From_Source (Arg));
6570
6571         --  Positional argument is transformed into an aggregate with an
6572         --  Expressions list.
6573
6574         if Nam = No_Name then
6575            Exprs := New_List (Relocate_Node (Expr));
6576
6577         --  An associative argument is transformed into an aggregate with
6578         --  Component_Associations.
6579
6580         else
6581            Comps := New_List (
6582              Make_Component_Association (Loc,
6583                Choices    => New_List (Make_Identifier (Nam_Loc, Nam)),
6584                Expression => Relocate_Node (Expr)));
6585         end if;
6586
6587         Set_Expression (Arg,
6588           Make_Aggregate (Loc,
6589             Component_Associations => Comps,
6590             Expressions            => Exprs));
6591
6592         --  Restore Comes_From_Source default
6593
6594         Set_Comes_From_Source_Default (CFSD);
6595      end Ensure_Aggregate_Form;
6596
6597      ------------------
6598      -- Error_Pragma --
6599      ------------------
6600
6601      procedure Error_Pragma (Msg : String) is
6602      begin
6603         Error_Msg_Name_1 := Pname;
6604         Error_Msg_N (Fix_Error (Msg), N);
6605         raise Pragma_Exit;
6606      end Error_Pragma;
6607
6608      ----------------------
6609      -- Error_Pragma_Arg --
6610      ----------------------
6611
6612      procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
6613      begin
6614         Error_Msg_Name_1 := Pname;
6615         Error_Msg_N (Fix_Error (Msg), Get_Pragma_Arg (Arg));
6616         raise Pragma_Exit;
6617      end Error_Pragma_Arg;
6618
6619      procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
6620      begin
6621         Error_Msg_Name_1 := Pname;
6622         Error_Msg_N (Fix_Error (Msg1), Get_Pragma_Arg (Arg));
6623         Error_Pragma_Arg (Msg2, Arg);
6624      end Error_Pragma_Arg;
6625
6626      ----------------------------
6627      -- Error_Pragma_Arg_Ident --
6628      ----------------------------
6629
6630      procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
6631      begin
6632         Error_Msg_Name_1 := Pname;
6633         Error_Msg_N (Fix_Error (Msg), Arg);
6634         raise Pragma_Exit;
6635      end Error_Pragma_Arg_Ident;
6636
6637      ----------------------
6638      -- Error_Pragma_Ref --
6639      ----------------------
6640
6641      procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
6642      begin
6643         Error_Msg_Name_1 := Pname;
6644         Error_Msg_Sloc := Sloc (Ref);
6645         Error_Msg_NE (Fix_Error (Msg), N, Ref);
6646         raise Pragma_Exit;
6647      end Error_Pragma_Ref;
6648
6649      ------------------------
6650      -- Find_Lib_Unit_Name --
6651      ------------------------
6652
6653      function Find_Lib_Unit_Name return Entity_Id is
6654      begin
6655         --  Return inner compilation unit entity, for case of nested
6656         --  categorization pragmas. This happens in generic unit.
6657
6658         if Nkind (Parent (N)) = N_Package_Specification
6659           and then Defining_Entity (Parent (N)) /= Current_Scope
6660         then
6661            return Defining_Entity (Parent (N));
6662         else
6663            return Current_Scope;
6664         end if;
6665      end Find_Lib_Unit_Name;
6666
6667      ----------------------------
6668      -- Find_Program_Unit_Name --
6669      ----------------------------
6670
6671      procedure Find_Program_Unit_Name (Id : Node_Id) is
6672         Unit_Name : Entity_Id;
6673         Unit_Kind : Node_Kind;
6674         P         : constant Node_Id := Parent (N);
6675
6676      begin
6677         if Nkind (P) = N_Compilation_Unit then
6678            Unit_Kind := Nkind (Unit (P));
6679
6680            if Nkind_In (Unit_Kind, N_Subprogram_Declaration,
6681                                    N_Package_Declaration)
6682              or else Unit_Kind in N_Generic_Declaration
6683            then
6684               Unit_Name := Defining_Entity (Unit (P));
6685
6686               if Chars (Id) = Chars (Unit_Name) then
6687                  Set_Entity (Id, Unit_Name);
6688                  Set_Etype (Id, Etype (Unit_Name));
6689               else
6690                  Set_Etype (Id, Any_Type);
6691                  Error_Pragma
6692                    ("cannot find program unit referenced by pragma%");
6693               end if;
6694
6695            else
6696               Set_Etype (Id, Any_Type);
6697               Error_Pragma ("pragma% inapplicable to this unit");
6698            end if;
6699
6700         else
6701            Analyze (Id);
6702         end if;
6703      end Find_Program_Unit_Name;
6704
6705      -----------------------------------------
6706      -- Find_Unique_Parameterless_Procedure --
6707      -----------------------------------------
6708
6709      function Find_Unique_Parameterless_Procedure
6710        (Name : Entity_Id;
6711         Arg  : Node_Id) return Entity_Id
6712      is
6713         Proc : Entity_Id := Empty;
6714
6715      begin
6716         --  The body of this procedure needs some comments ???
6717
6718         if not Is_Entity_Name (Name) then
6719            Error_Pragma_Arg
6720              ("argument of pragma% must be entity name", Arg);
6721
6722         elsif not Is_Overloaded (Name) then
6723            Proc := Entity (Name);
6724
6725            if Ekind (Proc) /= E_Procedure
6726              or else Present (First_Formal (Proc))
6727            then
6728               Error_Pragma_Arg
6729                 ("argument of pragma% must be parameterless procedure", Arg);
6730            end if;
6731
6732         else
6733            declare
6734               Found : Boolean := False;
6735               It    : Interp;
6736               Index : Interp_Index;
6737
6738            begin
6739               Get_First_Interp (Name, Index, It);
6740               while Present (It.Nam) loop
6741                  Proc := It.Nam;
6742
6743                  if Ekind (Proc) = E_Procedure
6744                    and then No (First_Formal (Proc))
6745                  then
6746                     if not Found then
6747                        Found := True;
6748                        Set_Entity (Name, Proc);
6749                        Set_Is_Overloaded (Name, False);
6750                     else
6751                        Error_Pragma_Arg
6752                          ("ambiguous handler name for pragma% ", Arg);
6753                     end if;
6754                  end if;
6755
6756                  Get_Next_Interp (Index, It);
6757               end loop;
6758
6759               if not Found then
6760                  Error_Pragma_Arg
6761                    ("argument of pragma% must be parameterless procedure",
6762                     Arg);
6763               else
6764                  Proc := Entity (Name);
6765               end if;
6766            end;
6767         end if;
6768
6769         return Proc;
6770      end Find_Unique_Parameterless_Procedure;
6771
6772      ---------------
6773      -- Fix_Error --
6774      ---------------
6775
6776      function Fix_Error (Msg : String) return String is
6777         Res      : String (Msg'Range) := Msg;
6778         Res_Last : Natural            := Msg'Last;
6779         J        : Natural;
6780
6781      begin
6782         --  If we have a rewriting of another pragma, go to that pragma
6783
6784         if Is_Rewrite_Substitution (N)
6785           and then Nkind (Original_Node (N)) = N_Pragma
6786         then
6787            Error_Msg_Name_1 := Pragma_Name (Original_Node (N));
6788         end if;
6789
6790         --  Case where pragma comes from an aspect specification
6791
6792         if From_Aspect_Specification (N) then
6793
6794            --  Change appearence of "pragma" in message to "aspect"
6795
6796            J := Res'First;
6797            while J <= Res_Last - 5 loop
6798               if Res (J .. J + 5) = "pragma" then
6799                  Res (J .. J + 5) := "aspect";
6800                  J := J + 6;
6801
6802               else
6803                  J := J + 1;
6804               end if;
6805            end loop;
6806
6807            --  Change "argument of" at start of message to "entity for"
6808
6809            if Res'Length > 11
6810              and then Res (Res'First .. Res'First + 10) = "argument of"
6811            then
6812               Res (Res'First .. Res'First + 9) := "entity for";
6813               Res (Res'First + 10 .. Res_Last - 1) :=
6814                 Res (Res'First + 11 .. Res_Last);
6815               Res_Last := Res_Last - 1;
6816            end if;
6817
6818            --  Change "argument" at start of message to "entity"
6819
6820            if Res'Length > 8
6821              and then Res (Res'First .. Res'First + 7) = "argument"
6822            then
6823               Res (Res'First .. Res'First + 5) := "entity";
6824               Res (Res'First + 6 .. Res_Last - 2) :=
6825                 Res (Res'First + 8 .. Res_Last);
6826               Res_Last := Res_Last - 2;
6827            end if;
6828
6829            --  Get name from corresponding aspect
6830
6831            Error_Msg_Name_1 := Original_Aspect_Pragma_Name (N);
6832         end if;
6833
6834         --  Return possibly modified message
6835
6836         return Res (Res'First .. Res_Last);
6837      end Fix_Error;
6838
6839      -------------------------
6840      -- Gather_Associations --
6841      -------------------------
6842
6843      procedure Gather_Associations
6844        (Names : Name_List;
6845         Args  : out Args_List)
6846      is
6847         Arg : Node_Id;
6848
6849      begin
6850         --  Initialize all parameters to Empty
6851
6852         for J in Args'Range loop
6853            Args (J) := Empty;
6854         end loop;
6855
6856         --  That's all we have to do if there are no argument associations
6857
6858         if No (Pragma_Argument_Associations (N)) then
6859            return;
6860         end if;
6861
6862         --  Otherwise first deal with any positional parameters present
6863
6864         Arg := First (Pragma_Argument_Associations (N));
6865         for Index in Args'Range loop
6866            exit when No (Arg) or else Chars (Arg) /= No_Name;
6867            Args (Index) := Get_Pragma_Arg (Arg);
6868            Next (Arg);
6869         end loop;
6870
6871         --  Positional parameters all processed, if any left, then we
6872         --  have too many positional parameters.
6873
6874         if Present (Arg) and then Chars (Arg) = No_Name then
6875            Error_Pragma_Arg
6876              ("too many positional associations for pragma%", Arg);
6877         end if;
6878
6879         --  Process named parameters if any are present
6880
6881         while Present (Arg) loop
6882            if Chars (Arg) = No_Name then
6883               Error_Pragma_Arg
6884                 ("positional association cannot follow named association",
6885                  Arg);
6886
6887            else
6888               for Index in Names'Range loop
6889                  if Names (Index) = Chars (Arg) then
6890                     if Present (Args (Index)) then
6891                        Error_Pragma_Arg
6892                          ("duplicate argument association for pragma%", Arg);
6893                     else
6894                        Args (Index) := Get_Pragma_Arg (Arg);
6895                        exit;
6896                     end if;
6897                  end if;
6898
6899                  if Index = Names'Last then
6900                     Error_Msg_Name_1 := Pname;
6901                     Error_Msg_N ("pragma% does not allow & argument", Arg);
6902
6903                     --  Check for possible misspelling
6904
6905                     for Index1 in Names'Range loop
6906                        if Is_Bad_Spelling_Of
6907                             (Chars (Arg), Names (Index1))
6908                        then
6909                           Error_Msg_Name_1 := Names (Index1);
6910                           Error_Msg_N -- CODEFIX
6911                             ("\possible misspelling of%", Arg);
6912                           exit;
6913                        end if;
6914                     end loop;
6915
6916                     raise Pragma_Exit;
6917                  end if;
6918               end loop;
6919            end if;
6920
6921            Next (Arg);
6922         end loop;
6923      end Gather_Associations;
6924
6925      -----------------
6926      -- GNAT_Pragma --
6927      -----------------
6928
6929      procedure GNAT_Pragma is
6930      begin
6931         --  We need to check the No_Implementation_Pragmas restriction for
6932         --  the case of a pragma from source. Note that the case of aspects
6933         --  generating corresponding pragmas marks these pragmas as not being
6934         --  from source, so this test also catches that case.
6935
6936         if Comes_From_Source (N) then
6937            Check_Restriction (No_Implementation_Pragmas, N);
6938         end if;
6939      end GNAT_Pragma;
6940
6941      --------------------------
6942      -- Is_Before_First_Decl --
6943      --------------------------
6944
6945      function Is_Before_First_Decl
6946        (Pragma_Node : Node_Id;
6947         Decls       : List_Id) return Boolean
6948      is
6949         Item : Node_Id := First (Decls);
6950
6951      begin
6952         --  Only other pragmas can come before this pragma
6953
6954         loop
6955            if No (Item) or else Nkind (Item) /= N_Pragma then
6956               return False;
6957
6958            elsif Item = Pragma_Node then
6959               return True;
6960            end if;
6961
6962            Next (Item);
6963         end loop;
6964      end Is_Before_First_Decl;
6965
6966      -----------------------------
6967      -- Is_Configuration_Pragma --
6968      -----------------------------
6969
6970      --  A configuration pragma must appear in the context clause of a
6971      --  compilation unit, and only other pragmas may precede it. Note that
6972      --  the test below also permits use in a configuration pragma file.
6973
6974      function Is_Configuration_Pragma return Boolean is
6975         Lis : constant List_Id := List_Containing (N);
6976         Par : constant Node_Id := Parent (N);
6977         Prg : Node_Id;
6978
6979      begin
6980         --  If no parent, then we are in the configuration pragma file,
6981         --  so the placement is definitely appropriate.
6982
6983         if No (Par) then
6984            return True;
6985
6986         --  Otherwise we must be in the context clause of a compilation unit
6987         --  and the only thing allowed before us in the context list is more
6988         --  configuration pragmas.
6989
6990         elsif Nkind (Par) = N_Compilation_Unit
6991           and then Context_Items (Par) = Lis
6992         then
6993            Prg := First (Lis);
6994
6995            loop
6996               if Prg = N then
6997                  return True;
6998               elsif Nkind (Prg) /= N_Pragma then
6999                  return False;
7000               end if;
7001
7002               Next (Prg);
7003            end loop;
7004
7005         else
7006            return False;
7007         end if;
7008      end Is_Configuration_Pragma;
7009
7010      --------------------------
7011      -- Is_In_Context_Clause --
7012      --------------------------
7013
7014      function Is_In_Context_Clause return Boolean is
7015         Plist       : List_Id;
7016         Parent_Node : Node_Id;
7017
7018      begin
7019         if not Is_List_Member (N) then
7020            return False;
7021
7022         else
7023            Plist := List_Containing (N);
7024            Parent_Node := Parent (Plist);
7025
7026            if Parent_Node = Empty
7027              or else Nkind (Parent_Node) /= N_Compilation_Unit
7028              or else Context_Items (Parent_Node) /= Plist
7029            then
7030               return False;
7031            end if;
7032         end if;
7033
7034         return True;
7035      end Is_In_Context_Clause;
7036
7037      ---------------------------------
7038      -- Is_Static_String_Expression --
7039      ---------------------------------
7040
7041      function Is_Static_String_Expression (Arg : Node_Id) return Boolean is
7042         Argx : constant Node_Id := Get_Pragma_Arg (Arg);
7043         Lit  : constant Boolean := Nkind (Argx) = N_String_Literal;
7044
7045      begin
7046         Analyze_And_Resolve (Argx);
7047
7048         --  Special case Ada 83, where the expression will never be static,
7049         --  but we will return true if we had a string literal to start with.
7050
7051         if Ada_Version = Ada_83 then
7052            return Lit;
7053
7054         --  Normal case, true only if we end up with a string literal that
7055         --  is marked as being the result of evaluating a static expression.
7056
7057         else
7058            return Is_OK_Static_Expression (Argx)
7059              and then Nkind (Argx) = N_String_Literal;
7060         end if;
7061
7062      end Is_Static_String_Expression;
7063
7064      ----------------------
7065      -- Pragma_Misplaced --
7066      ----------------------
7067
7068      procedure Pragma_Misplaced is
7069      begin
7070         Error_Pragma ("incorrect placement of pragma%");
7071      end Pragma_Misplaced;
7072
7073      ------------------------------------------------
7074      -- Process_Atomic_Independent_Shared_Volatile --
7075      ------------------------------------------------
7076
7077      procedure Process_Atomic_Independent_Shared_Volatile is
7078         procedure Check_VFA_Conflicts (Ent : Entity_Id);
7079         --  Apply additional checks for the GNAT pragma Volatile_Full_Access
7080
7081         procedure Mark_Component_Or_Object (Ent : Entity_Id);
7082         --  Appropriately set flags on the given entity (either an array or
7083         --  record component, or an object declaration) according to the
7084         --  current pragma.
7085
7086         procedure Set_Atomic_VFA (Ent : Entity_Id);
7087         --  Set given type as Is_Atomic or Is_Volatile_Full_Access. Also, if
7088         --  no explicit alignment was given, set alignment to unknown, since
7089         --  back end knows what the alignment requirements are for atomic and
7090         --  full access arrays. Note: this is necessary for derived types.
7091
7092         -------------------------
7093         -- Check_VFA_Conflicts --
7094         -------------------------
7095
7096         procedure Check_VFA_Conflicts (Ent : Entity_Id) is
7097            Comp : Entity_Id;
7098            Typ  : Entity_Id;
7099
7100            VFA_And_Atomic : Boolean := False;
7101            --  Set True if atomic component present
7102
7103            VFA_And_Aliased : Boolean := False;
7104            --  Set True if aliased component present
7105
7106         begin
7107            --  Fetch the type in case we are dealing with an object or
7108            --  component.
7109
7110            if Is_Type (Ent) then
7111               Typ := Ent;
7112            else
7113               pragma Assert (Is_Object (Ent)
7114                 or else
7115                   Nkind (Declaration_Node (Ent)) = N_Component_Declaration);
7116
7117               Typ := Etype (Ent);
7118            end if;
7119
7120            --  Check Atomic and VFA used together
7121
7122            if Prag_Id = Pragma_Volatile_Full_Access
7123              or else Is_Volatile_Full_Access (Ent)
7124            then
7125               if Prag_Id = Pragma_Atomic
7126                 or else Prag_Id = Pragma_Shared
7127                 or else Is_Atomic (Ent)
7128               then
7129                  VFA_And_Atomic := True;
7130
7131               elsif Is_Array_Type (Typ) then
7132                  VFA_And_Atomic := Has_Atomic_Components (Typ);
7133
7134               --  Note: Has_Atomic_Components is not used below, as this flag
7135               --  represents the pragma of the same name, Atomic_Components,
7136               --  which only applies to arrays.
7137
7138               elsif Is_Record_Type (Typ) then
7139                  --  Attributes cannot be applied to discriminants, only
7140                  --  regular record components.
7141
7142                  Comp := First_Component (Typ);
7143                  while Present (Comp) loop
7144                     if Is_Atomic (Comp)
7145                       or else Is_Atomic (Typ)
7146                     then
7147                        VFA_And_Atomic := True;
7148
7149                        exit;
7150                     end if;
7151
7152                     Next_Component (Comp);
7153                  end loop;
7154               end if;
7155
7156               if VFA_And_Atomic then
7157                  Error_Pragma
7158                    ("cannot have Volatile_Full_Access and Atomic for same "
7159                     & "entity");
7160               end if;
7161            end if;
7162
7163            --  Check for the application of VFA to an entity that has aliased
7164            --  components.
7165
7166            if Prag_Id = Pragma_Volatile_Full_Access then
7167               if Is_Array_Type (Typ)
7168                 and then Has_Aliased_Components (Typ)
7169               then
7170                  VFA_And_Aliased := True;
7171
7172               --  Note: Has_Aliased_Components, like Has_Atomic_Components,
7173               --  and Has_Independent_Components, applies only to arrays.
7174               --  However, this flag does not have a corresponding pragma, so
7175               --  perhaps it should be possible to apply it to record types as
7176               --  well. Should this be done ???
7177
7178               elsif Is_Record_Type (Typ) then
7179                  --  It is possible to have an aliased discriminant, so they
7180                  --  must be checked along with normal components.
7181
7182                  Comp := First_Component_Or_Discriminant (Typ);
7183                  while Present (Comp) loop
7184                     if Is_Aliased (Comp)
7185                       or else Is_Aliased (Etype (Comp))
7186                     then
7187                        VFA_And_Aliased := True;
7188                        Check_SPARK_05_Restriction
7189                          ("aliased is not allowed", Comp);
7190
7191                        exit;
7192                     end if;
7193
7194                     Next_Component_Or_Discriminant (Comp);
7195                  end loop;
7196               end if;
7197
7198               if VFA_And_Aliased then
7199                  Error_Pragma
7200                    ("cannot apply Volatile_Full_Access (aliased component "
7201                     & "present)");
7202               end if;
7203            end if;
7204         end Check_VFA_Conflicts;
7205
7206         ------------------------------
7207         -- Mark_Component_Or_Object --
7208         ------------------------------
7209
7210         procedure Mark_Component_Or_Object (Ent : Entity_Id) is
7211         begin
7212            if Prag_Id = Pragma_Atomic
7213              or else Prag_Id = Pragma_Shared
7214              or else Prag_Id = Pragma_Volatile_Full_Access
7215            then
7216               if Prag_Id = Pragma_Volatile_Full_Access then
7217                  Set_Is_Volatile_Full_Access (Ent);
7218               else
7219                  Set_Is_Atomic (Ent);
7220               end if;
7221
7222               --  If the object declaration has an explicit initialization, a
7223               --  temporary may have to be created to hold the expression, to
7224               --  ensure that access to the object remains atomic.
7225
7226               if Nkind (Parent (Ent)) = N_Object_Declaration
7227                 and then Present (Expression (Parent (Ent)))
7228               then
7229                  Set_Has_Delayed_Freeze (Ent);
7230               end if;
7231            end if;
7232
7233            --  Atomic/Shared/Volatile_Full_Access imply Independent
7234
7235            if Prag_Id /= Pragma_Volatile then
7236               Set_Is_Independent (Ent);
7237
7238               if Prag_Id = Pragma_Independent then
7239                  Record_Independence_Check (N, Ent);
7240               end if;
7241            end if;
7242
7243            --  Atomic/Shared/Volatile_Full_Access imply Volatile
7244
7245            if Prag_Id /= Pragma_Independent then
7246               Set_Is_Volatile (Ent);
7247               Set_Treat_As_Volatile (Ent);
7248            end if;
7249         end Mark_Component_Or_Object;
7250
7251         --------------------
7252         -- Set_Atomic_VFA --
7253         --------------------
7254
7255         procedure Set_Atomic_VFA (Ent : Entity_Id) is
7256         begin
7257            if Prag_Id = Pragma_Volatile_Full_Access then
7258               Set_Is_Volatile_Full_Access (Ent);
7259            else
7260               Set_Is_Atomic (Ent);
7261            end if;
7262
7263            if not Has_Alignment_Clause (Ent) then
7264               Set_Alignment (Ent, Uint_0);
7265            end if;
7266         end Set_Atomic_VFA;
7267
7268         --  Local variables
7269
7270         Decl  : Node_Id;
7271         E     : Entity_Id;
7272         E_Arg : Node_Id;
7273
7274      --  Start of processing for Process_Atomic_Independent_Shared_Volatile
7275
7276      begin
7277         Check_Ada_83_Warning;
7278         Check_No_Identifiers;
7279         Check_Arg_Count (1);
7280         Check_Arg_Is_Local_Name (Arg1);
7281         E_Arg := Get_Pragma_Arg (Arg1);
7282
7283         if Etype (E_Arg) = Any_Type then
7284            return;
7285         end if;
7286
7287         E := Entity (E_Arg);
7288
7289         --  A pragma that applies to a Ghost entity becomes Ghost for the
7290         --  purposes of legality checks and removal of ignored Ghost code.
7291
7292         Mark_Ghost_Pragma (N, E);
7293
7294         --  Check duplicate before we chain ourselves
7295
7296         Check_Duplicate_Pragma (E);
7297
7298         --  Check appropriateness of the entity
7299
7300         Decl := Declaration_Node (E);
7301
7302         --  Deal with the case where the pragma/attribute is applied to a type
7303
7304         if Is_Type (E) then
7305            if Rep_Item_Too_Early (E, N)
7306              or else Rep_Item_Too_Late (E, N)
7307            then
7308               return;
7309            else
7310               Check_First_Subtype (Arg1);
7311            end if;
7312
7313            --  Attribute belongs on the base type. If the view of the type is
7314            --  currently private, it also belongs on the underlying type.
7315
7316            if Prag_Id = Pragma_Atomic
7317              or else Prag_Id = Pragma_Shared
7318              or else Prag_Id = Pragma_Volatile_Full_Access
7319            then
7320               Set_Atomic_VFA (E);
7321               Set_Atomic_VFA (Base_Type (E));
7322               Set_Atomic_VFA (Underlying_Type (E));
7323            end if;
7324
7325            --  Atomic/Shared/Volatile_Full_Access imply Independent
7326
7327            if Prag_Id /= Pragma_Volatile then
7328               Set_Is_Independent (E);
7329               Set_Is_Independent (Base_Type (E));
7330               Set_Is_Independent (Underlying_Type (E));
7331
7332               if Prag_Id = Pragma_Independent then
7333                  Record_Independence_Check (N, Base_Type (E));
7334               end if;
7335            end if;
7336
7337            --  Atomic/Shared/Volatile_Full_Access imply Volatile
7338
7339            if Prag_Id /= Pragma_Independent then
7340               Set_Is_Volatile (E);
7341               Set_Is_Volatile (Base_Type (E));
7342               Set_Is_Volatile (Underlying_Type (E));
7343
7344               Set_Treat_As_Volatile (E);
7345               Set_Treat_As_Volatile (Underlying_Type (E));
7346            end if;
7347
7348            --  Apply Volatile to the composite type's individual components,
7349            --  (RM C.6(8/3)).
7350
7351            if Prag_Id = Pragma_Volatile
7352              and then Is_Record_Type (Etype (E))
7353            then
7354               declare
7355                  Comp : Entity_Id;
7356               begin
7357                  Comp := First_Component (E);
7358                  while Present (Comp) loop
7359                     Mark_Component_Or_Object (Comp);
7360
7361                     Next_Component (Comp);
7362                  end loop;
7363               end;
7364            end if;
7365
7366         --  Deal with the case where the pragma/attribute applies to a
7367         --  component or object declaration.
7368
7369         elsif Nkind (Decl) = N_Object_Declaration
7370           or else (Nkind (Decl) = N_Component_Declaration
7371                     and then Original_Record_Component (E) = E)
7372         then
7373            if Rep_Item_Too_Late (E, N) then
7374               return;
7375            end if;
7376
7377            Mark_Component_Or_Object (E);
7378         else
7379            Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
7380         end if;
7381
7382         --  Perform the checks needed to assure the proper use of the GNAT
7383         --  pragma Volatile_Full_Access.
7384
7385         Check_VFA_Conflicts (E);
7386
7387         --  The following check is only relevant when SPARK_Mode is on as
7388         --  this is not a standard Ada legality rule. Pragma Volatile can
7389         --  only apply to a full type declaration or an object declaration
7390         --  (SPARK RM 7.1.3(2)). Original_Node is necessary to account for
7391         --  untagged derived types that are rewritten as subtypes of their
7392         --  respective root types.
7393
7394         if SPARK_Mode = On
7395           and then Prag_Id = Pragma_Volatile
7396           and then
7397             not Nkind_In (Original_Node (Decl), N_Full_Type_Declaration,
7398                                                 N_Object_Declaration)
7399         then
7400            Error_Pragma_Arg
7401              ("argument of pragma % must denote a full type or object "
7402               & "declaration", Arg1);
7403         end if;
7404      end Process_Atomic_Independent_Shared_Volatile;
7405
7406      -------------------------------------------
7407      -- Process_Compile_Time_Warning_Or_Error --
7408      -------------------------------------------
7409
7410      procedure Process_Compile_Time_Warning_Or_Error is
7411         Validation_Needed : Boolean := False;
7412
7413         function Check_Node (N : Node_Id) return Traverse_Result;
7414         --  Tree visitor that checks if N is an attribute reference that can
7415         --  be statically computed by the back end. Validation_Needed is set
7416         --  to True if found.
7417
7418         ----------------
7419         -- Check_Node --
7420         ----------------
7421
7422         function Check_Node (N : Node_Id) return Traverse_Result is
7423         begin
7424            if Nkind (N) = N_Attribute_Reference
7425              and then Is_Entity_Name (Prefix (N))
7426            then
7427               declare
7428                  Attr_Id : constant Attribute_Id :=
7429                              Get_Attribute_Id (Attribute_Name (N));
7430               begin
7431                  if Attr_Id = Attribute_Alignment
7432                    or else Attr_Id = Attribute_Size
7433                  then
7434                     Validation_Needed := True;
7435                  end if;
7436               end;
7437            end if;
7438
7439            return OK;
7440         end Check_Node;
7441
7442         procedure Check_Expression is new Traverse_Proc (Check_Node);
7443
7444         --  Local variables
7445
7446         Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
7447
7448      --  Start of processing for Process_Compile_Time_Warning_Or_Error
7449
7450      begin
7451         Check_Arg_Count (2);
7452         Check_No_Identifiers;
7453         Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
7454         Analyze_And_Resolve (Arg1x, Standard_Boolean);
7455
7456         if Compile_Time_Known_Value (Arg1x) then
7457            Process_Compile_Time_Warning_Or_Error (N, Sloc (Arg1));
7458
7459         --  Register the expression for its validation after the back end has
7460         --  been called if it has occurrences of attributes Size or Alignment
7461         --  (because they may be statically computed by the back end and hence
7462         --  the whole expression needs to be reevaluated).
7463
7464         else
7465            Check_Expression (Arg1x);
7466
7467            if Validation_Needed then
7468               Sem_Ch13.Validate_Compile_Time_Warning_Error (N);
7469            end if;
7470         end if;
7471      end Process_Compile_Time_Warning_Or_Error;
7472
7473      ------------------------
7474      -- Process_Convention --
7475      ------------------------
7476
7477      procedure Process_Convention
7478        (C   : out Convention_Id;
7479         Ent : out Entity_Id)
7480      is
7481         Cname : Name_Id;
7482
7483         procedure Diagnose_Multiple_Pragmas (S : Entity_Id);
7484         --  Called if we have more than one Export/Import/Convention pragma.
7485         --  This is generally illegal, but we have a special case of allowing
7486         --  Import and Interface to coexist if they specify the convention in
7487         --  a consistent manner. We are allowed to do this, since Interface is
7488         --  an implementation defined pragma, and we choose to do it since we
7489         --  know Rational allows this combination. S is the entity id of the
7490         --  subprogram in question. This procedure also sets the special flag
7491         --  Import_Interface_Present in both pragmas in the case where we do
7492         --  have matching Import and Interface pragmas.
7493
7494         procedure Set_Convention_From_Pragma (E : Entity_Id);
7495         --  Set convention in entity E, and also flag that the entity has a
7496         --  convention pragma. If entity is for a private or incomplete type,
7497         --  also set convention and flag on underlying type. This procedure
7498         --  also deals with the special case of C_Pass_By_Copy convention,
7499         --  and error checks for inappropriate convention specification.
7500
7501         -------------------------------
7502         -- Diagnose_Multiple_Pragmas --
7503         -------------------------------
7504
7505         procedure Diagnose_Multiple_Pragmas (S : Entity_Id) is
7506            Pdec : constant Node_Id := Declaration_Node (S);
7507            Decl : Node_Id;
7508            Err  : Boolean;
7509
7510            function Same_Convention (Decl : Node_Id) return Boolean;
7511            --  Decl is a pragma node. This function returns True if this
7512            --  pragma has a first argument that is an identifier with a
7513            --  Chars field corresponding to the Convention_Id C.
7514
7515            function Same_Name (Decl : Node_Id) return Boolean;
7516            --  Decl is a pragma node. This function returns True if this
7517            --  pragma has a second argument that is an identifier with a
7518            --  Chars field that matches the Chars of the current subprogram.
7519
7520            ---------------------
7521            -- Same_Convention --
7522            ---------------------
7523
7524            function Same_Convention (Decl : Node_Id) return Boolean is
7525               Arg1 : constant Node_Id :=
7526                        First (Pragma_Argument_Associations (Decl));
7527
7528            begin
7529               if Present (Arg1) then
7530                  declare
7531                     Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
7532                  begin
7533                     if Nkind (Arg) = N_Identifier
7534                       and then Is_Convention_Name (Chars (Arg))
7535                       and then Get_Convention_Id (Chars (Arg)) = C
7536                     then
7537                        return True;
7538                     end if;
7539                  end;
7540               end if;
7541
7542               return False;
7543            end Same_Convention;
7544
7545            ---------------
7546            -- Same_Name --
7547            ---------------
7548
7549            function Same_Name (Decl : Node_Id) return Boolean is
7550               Arg1 : constant Node_Id :=
7551                        First (Pragma_Argument_Associations (Decl));
7552               Arg2 : Node_Id;
7553
7554            begin
7555               if No (Arg1) then
7556                  return False;
7557               end if;
7558
7559               Arg2 := Next (Arg1);
7560
7561               if No (Arg2) then
7562                  return False;
7563               end if;
7564
7565               declare
7566                  Arg : constant Node_Id := Get_Pragma_Arg (Arg2);
7567               begin
7568                  if Nkind (Arg) = N_Identifier
7569                    and then Chars (Arg) = Chars (S)
7570                  then
7571                     return True;
7572                  end if;
7573               end;
7574
7575               return False;
7576            end Same_Name;
7577
7578         --  Start of processing for Diagnose_Multiple_Pragmas
7579
7580         begin
7581            Err := True;
7582
7583            --  Definitely give message if we have Convention/Export here
7584
7585            if Prag_Id = Pragma_Convention or else Prag_Id = Pragma_Export then
7586               null;
7587
7588               --  If we have an Import or Export, scan back from pragma to
7589               --  find any previous pragma applying to the same procedure.
7590               --  The scan will be terminated by the start of the list, or
7591               --  hitting the subprogram declaration. This won't allow one
7592               --  pragma to appear in the public part and one in the private
7593               --  part, but that seems very unlikely in practice.
7594
7595            else
7596               Decl := Prev (N);
7597               while Present (Decl) and then Decl /= Pdec loop
7598
7599                  --  Look for pragma with same name as us
7600
7601                  if Nkind (Decl) = N_Pragma
7602                    and then Same_Name (Decl)
7603                  then
7604                     --  Give error if same as our pragma or Export/Convention
7605
7606                     if Nam_In (Pragma_Name_Unmapped (Decl),
7607                                Name_Export,
7608                                Name_Convention,
7609                                Pragma_Name_Unmapped (N))
7610                     then
7611                        exit;
7612
7613                     --  Case of Import/Interface or the other way round
7614
7615                     elsif Nam_In (Pragma_Name_Unmapped (Decl),
7616                                   Name_Interface, Name_Import)
7617                     then
7618                        --  Here we know that we have Import and Interface. It
7619                        --  doesn't matter which way round they are. See if
7620                        --  they specify the same convention. If so, all OK,
7621                        --  and set special flags to stop other messages
7622
7623                        if Same_Convention (Decl) then
7624                           Set_Import_Interface_Present (N);
7625                           Set_Import_Interface_Present (Decl);
7626                           Err := False;
7627
7628                        --  If different conventions, special message
7629
7630                        else
7631                           Error_Msg_Sloc := Sloc (Decl);
7632                           Error_Pragma_Arg
7633                             ("convention differs from that given#", Arg1);
7634                           return;
7635                        end if;
7636                     end if;
7637                  end if;
7638
7639                  Next (Decl);
7640               end loop;
7641            end if;
7642
7643            --  Give message if needed if we fall through those tests
7644            --  except on Relaxed_RM_Semantics where we let go: either this
7645            --  is a case accepted/ignored by other Ada compilers (e.g.
7646            --  a mix of Convention and Import), or another error will be
7647            --  generated later (e.g. using both Import and Export).
7648
7649            if Err and not Relaxed_RM_Semantics then
7650               Error_Pragma_Arg
7651                 ("at most one Convention/Export/Import pragma is allowed",
7652                  Arg2);
7653            end if;
7654         end Diagnose_Multiple_Pragmas;
7655
7656         --------------------------------
7657         -- Set_Convention_From_Pragma --
7658         --------------------------------
7659
7660         procedure Set_Convention_From_Pragma (E : Entity_Id) is
7661         begin
7662            --  Ada 2005 (AI-430): Check invalid attempt to change convention
7663            --  for an overridden dispatching operation. Technically this is
7664            --  an amendment and should only be done in Ada 2005 mode. However,
7665            --  this is clearly a mistake, since the problem that is addressed
7666            --  by this AI is that there is a clear gap in the RM.
7667
7668            if Is_Dispatching_Operation (E)
7669              and then Present (Overridden_Operation (E))
7670              and then C /= Convention (Overridden_Operation (E))
7671            then
7672               Error_Pragma_Arg
7673                 ("cannot change convention for overridden dispatching "
7674                  & "operation", Arg1);
7675            end if;
7676
7677            --  Special checks for Convention_Stdcall
7678
7679            if C = Convention_Stdcall then
7680
7681               --  A dispatching call is not allowed. A dispatching subprogram
7682               --  cannot be used to interface to the Win32 API, so in fact
7683               --  this check does not impose any effective restriction.
7684
7685               if Is_Dispatching_Operation (E) then
7686                  Error_Msg_Sloc := Sloc (E);
7687
7688                  --  Note: make this unconditional so that if there is more
7689                  --  than one call to which the pragma applies, we get a
7690                  --  message for each call. Also don't use Error_Pragma,
7691                  --  so that we get multiple messages.
7692
7693                  Error_Msg_N
7694                    ("dispatching subprogram# cannot use Stdcall convention!",
7695                     Arg1);
7696
7697               --  Several allowed cases
7698
7699               elsif Is_Subprogram_Or_Generic_Subprogram (E)
7700
7701                 --  A variable is OK
7702
7703                 or else Ekind (E) = E_Variable
7704
7705                 --  A component as well. The entity does not have its Ekind
7706                 --  set until the enclosing record declaration is fully
7707                 --  analyzed.
7708
7709                 or else Nkind (Parent (E)) = N_Component_Declaration
7710
7711                 --  An access to subprogram is also allowed
7712
7713                 or else
7714                   (Is_Access_Type (E)
7715                     and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
7716
7717                 --  Allow internal call to set convention of subprogram type
7718
7719                 or else Ekind (E) = E_Subprogram_Type
7720               then
7721                  null;
7722
7723               else
7724                  Error_Pragma_Arg
7725                    ("second argument of pragma% must be subprogram (type)",
7726                     Arg2);
7727               end if;
7728            end if;
7729
7730            --  Set the convention
7731
7732            Set_Convention (E, C);
7733            Set_Has_Convention_Pragma (E);
7734
7735            --  For the case of a record base type, also set the convention of
7736            --  any anonymous access types declared in the record which do not
7737            --  currently have a specified convention.
7738
7739            if Is_Record_Type (E) and then Is_Base_Type (E) then
7740               declare
7741                  Comp : Node_Id;
7742
7743               begin
7744                  Comp := First_Component (E);
7745                  while Present (Comp) loop
7746                     if Present (Etype (Comp))
7747                       and then Ekind_In (Etype (Comp),
7748                                          E_Anonymous_Access_Type,
7749                                          E_Anonymous_Access_Subprogram_Type)
7750                       and then not Has_Convention_Pragma (Comp)
7751                     then
7752                        Set_Convention (Comp, C);
7753                     end if;
7754
7755                     Next_Component (Comp);
7756                  end loop;
7757               end;
7758            end if;
7759
7760            --  Deal with incomplete/private type case, where underlying type
7761            --  is available, so set convention of that underlying type.
7762
7763            if Is_Incomplete_Or_Private_Type (E)
7764              and then Present (Underlying_Type (E))
7765            then
7766               Set_Convention            (Underlying_Type (E), C);
7767               Set_Has_Convention_Pragma (Underlying_Type (E), True);
7768            end if;
7769
7770            --  A class-wide type should inherit the convention of the specific
7771            --  root type (although this isn't specified clearly by the RM).
7772
7773            if Is_Type (E) and then Present (Class_Wide_Type (E)) then
7774               Set_Convention (Class_Wide_Type (E), C);
7775            end if;
7776
7777            --  If the entity is a record type, then check for special case of
7778            --  C_Pass_By_Copy, which is treated the same as C except that the
7779            --  special record flag is set. This convention is only permitted
7780            --  on record types (see AI95-00131).
7781
7782            if Cname = Name_C_Pass_By_Copy then
7783               if Is_Record_Type (E) then
7784                  Set_C_Pass_By_Copy (Base_Type (E));
7785               elsif Is_Incomplete_Or_Private_Type (E)
7786                 and then Is_Record_Type (Underlying_Type (E))
7787               then
7788                  Set_C_Pass_By_Copy (Base_Type (Underlying_Type (E)));
7789               else
7790                  Error_Pragma_Arg
7791                    ("C_Pass_By_Copy convention allowed only for record type",
7792                     Arg2);
7793               end if;
7794            end if;
7795
7796            --  If the entity is a derived boolean type, check for the special
7797            --  case of convention C, C++, or Fortran, where we consider any
7798            --  nonzero value to represent true.
7799
7800            if Is_Discrete_Type (E)
7801              and then Root_Type (Etype (E)) = Standard_Boolean
7802              and then
7803                (C = Convention_C
7804                   or else
7805                 C = Convention_CPP
7806                   or else
7807                 C = Convention_Fortran)
7808            then
7809               Set_Nonzero_Is_True (Base_Type (E));
7810            end if;
7811         end Set_Convention_From_Pragma;
7812
7813         --  Local variables
7814
7815         Comp_Unit : Unit_Number_Type;
7816         E         : Entity_Id;
7817         E1        : Entity_Id;
7818         Id        : Node_Id;
7819
7820      --  Start of processing for Process_Convention
7821
7822      begin
7823         Check_At_Least_N_Arguments (2);
7824         Check_Optional_Identifier (Arg1, Name_Convention);
7825         Check_Arg_Is_Identifier (Arg1);
7826         Cname := Chars (Get_Pragma_Arg (Arg1));
7827
7828         --  C_Pass_By_Copy is treated as a synonym for convention C (this is
7829         --  tested again below to set the critical flag).
7830
7831         if Cname = Name_C_Pass_By_Copy then
7832            C := Convention_C;
7833
7834         --  Otherwise we must have something in the standard convention list
7835
7836         elsif Is_Convention_Name (Cname) then
7837            C := Get_Convention_Id (Chars (Get_Pragma_Arg (Arg1)));
7838
7839         --  Otherwise warn on unrecognized convention
7840
7841         else
7842            if Warn_On_Export_Import then
7843               Error_Msg_N
7844                 ("??unrecognized convention name, C assumed",
7845                  Get_Pragma_Arg (Arg1));
7846            end if;
7847
7848            C := Convention_C;
7849         end if;
7850
7851         Check_Optional_Identifier (Arg2, Name_Entity);
7852         Check_Arg_Is_Local_Name (Arg2);
7853
7854         Id := Get_Pragma_Arg (Arg2);
7855         Analyze (Id);
7856
7857         if not Is_Entity_Name (Id) then
7858            Error_Pragma_Arg ("entity name required", Arg2);
7859         end if;
7860
7861         E := Entity (Id);
7862
7863         --  Set entity to return
7864
7865         Ent := E;
7866
7867         --  Ada_Pass_By_Copy special checking
7868
7869         if C = Convention_Ada_Pass_By_Copy then
7870            if not Is_First_Subtype (E) then
7871               Error_Pragma_Arg
7872                 ("convention `Ada_Pass_By_Copy` only allowed for types",
7873                  Arg2);
7874            end if;
7875
7876            if Is_By_Reference_Type (E) then
7877               Error_Pragma_Arg
7878                 ("convention `Ada_Pass_By_Copy` not allowed for by-reference "
7879                  & "type", Arg1);
7880            end if;
7881
7882         --  Ada_Pass_By_Reference special checking
7883
7884         elsif C = Convention_Ada_Pass_By_Reference then
7885            if not Is_First_Subtype (E) then
7886               Error_Pragma_Arg
7887                 ("convention `Ada_Pass_By_Reference` only allowed for types",
7888                  Arg2);
7889            end if;
7890
7891            if Is_By_Copy_Type (E) then
7892               Error_Pragma_Arg
7893                 ("convention `Ada_Pass_By_Reference` not allowed for by-copy "
7894                  & "type", Arg1);
7895            end if;
7896         end if;
7897
7898         --  Go to renamed subprogram if present, since convention applies to
7899         --  the actual renamed entity, not to the renaming entity. If the
7900         --  subprogram is inherited, go to parent subprogram.
7901
7902         if Is_Subprogram (E)
7903           and then Present (Alias (E))
7904         then
7905            if Nkind (Parent (Declaration_Node (E))) =
7906                                       N_Subprogram_Renaming_Declaration
7907            then
7908               if Scope (E) /= Scope (Alias (E)) then
7909                  Error_Pragma_Ref
7910                    ("cannot apply pragma% to non-local entity&#", E);
7911               end if;
7912
7913               E := Alias (E);
7914
7915            elsif Nkind_In (Parent (E), N_Full_Type_Declaration,
7916                                        N_Private_Extension_Declaration)
7917              and then Scope (E) = Scope (Alias (E))
7918            then
7919               E := Alias (E);
7920
7921               --  Return the parent subprogram the entity was inherited from
7922
7923               Ent := E;
7924            end if;
7925         end if;
7926
7927         --  Check that we are not applying this to a specless body. Relax this
7928         --  check if Relaxed_RM_Semantics to accommodate other Ada compilers.
7929
7930         if Is_Subprogram (E)
7931           and then Nkind (Parent (Declaration_Node (E))) = N_Subprogram_Body
7932           and then not Relaxed_RM_Semantics
7933         then
7934            Error_Pragma
7935              ("pragma% requires separate spec and must come before body");
7936         end if;
7937
7938         --  Check that we are not applying this to a named constant
7939
7940         if Ekind_In (E, E_Named_Integer, E_Named_Real) then
7941            Error_Msg_Name_1 := Pname;
7942            Error_Msg_N
7943              ("cannot apply pragma% to named constant!",
7944               Get_Pragma_Arg (Arg2));
7945            Error_Pragma_Arg
7946              ("\supply appropriate type for&!", Arg2);
7947         end if;
7948
7949         if Ekind (E) = E_Enumeration_Literal then
7950            Error_Pragma ("enumeration literal not allowed for pragma%");
7951         end if;
7952
7953         --  Check for rep item appearing too early or too late
7954
7955         if Etype (E) = Any_Type
7956           or else Rep_Item_Too_Early (E, N)
7957         then
7958            raise Pragma_Exit;
7959
7960         elsif Present (Underlying_Type (E)) then
7961            E := Underlying_Type (E);
7962         end if;
7963
7964         if Rep_Item_Too_Late (E, N) then
7965            raise Pragma_Exit;
7966         end if;
7967
7968         if Has_Convention_Pragma (E) then
7969            Diagnose_Multiple_Pragmas (E);
7970
7971         elsif Convention (E) = Convention_Protected
7972           or else Ekind (Scope (E)) = E_Protected_Type
7973         then
7974            Error_Pragma_Arg
7975              ("a protected operation cannot be given a different convention",
7976                Arg2);
7977         end if;
7978
7979         --  For Intrinsic, a subprogram is required
7980
7981         if C = Convention_Intrinsic
7982           and then not Is_Subprogram_Or_Generic_Subprogram (E)
7983         then
7984            --  Accept Intrinsic Export on types if Relaxed_RM_Semantics
7985
7986            if not (Is_Type (E) and then Relaxed_RM_Semantics) then
7987               Error_Pragma_Arg
7988                 ("second argument of pragma% must be a subprogram", Arg2);
7989            end if;
7990         end if;
7991
7992         --  Deal with non-subprogram cases
7993
7994         if not Is_Subprogram_Or_Generic_Subprogram (E) then
7995            Set_Convention_From_Pragma (E);
7996
7997            if Is_Type (E) then
7998
7999               --  The pragma must apply to a first subtype, but it can also
8000               --  apply to a generic type in a generic formal part, in which
8001               --  case it will also appear in the corresponding instance.
8002
8003               if Is_Generic_Type (E) or else In_Instance then
8004                  null;
8005               else
8006                  Check_First_Subtype (Arg2);
8007               end if;
8008
8009               Set_Convention_From_Pragma (Base_Type (E));
8010
8011               --  For access subprograms, we must set the convention on the
8012               --  internally generated directly designated type as well.
8013
8014               if Ekind (E) = E_Access_Subprogram_Type then
8015                  Set_Convention_From_Pragma (Directly_Designated_Type (E));
8016               end if;
8017            end if;
8018
8019         --  For the subprogram case, set proper convention for all homonyms
8020         --  in same scope and the same declarative part, i.e. the same
8021         --  compilation unit.
8022
8023         else
8024            Comp_Unit := Get_Source_Unit (E);
8025            Set_Convention_From_Pragma (E);
8026
8027            --  Treat a pragma Import as an implicit body, and pragma import
8028            --  as implicit reference (for navigation in GPS).
8029
8030            if Prag_Id = Pragma_Import then
8031               Generate_Reference (E, Id, 'b');
8032
8033            --  For exported entities we restrict the generation of references
8034            --  to entities exported to foreign languages since entities
8035            --  exported to Ada do not provide further information to GPS and
8036            --  add undesired references to the output of the gnatxref tool.
8037
8038            elsif Prag_Id = Pragma_Export
8039              and then Convention (E) /= Convention_Ada
8040            then
8041               Generate_Reference (E, Id, 'i');
8042            end if;
8043
8044            --  If the pragma comes from an aspect, it only applies to the
8045            --  given entity, not its homonyms.
8046
8047            if From_Aspect_Specification (N) then
8048               if C = Convention_Intrinsic
8049                 and then Nkind (Ent) = N_Defining_Operator_Symbol
8050               then
8051                  if Is_Fixed_Point_Type (Etype (Ent))
8052                    or else Is_Fixed_Point_Type (Etype (First_Entity (Ent)))
8053                    or else Is_Fixed_Point_Type (Etype (Last_Entity (Ent)))
8054                  then
8055                     Error_Msg_N
8056                       ("no intrinsic operator available for this fixed-point "
8057                        & "operation", N);
8058                     Error_Msg_N
8059                       ("\use expression functions with the desired "
8060                        & "conversions made explicit", N);
8061                  end if;
8062               end if;
8063
8064               return;
8065            end if;
8066
8067            --  Otherwise Loop through the homonyms of the pragma argument's
8068            --  entity, an apply convention to those in the current scope.
8069
8070            E1 := Ent;
8071
8072            loop
8073               E1 := Homonym (E1);
8074               exit when No (E1) or else Scope (E1) /= Current_Scope;
8075
8076               --  Ignore entry for which convention is already set
8077
8078               if Has_Convention_Pragma (E1) then
8079                  goto Continue;
8080               end if;
8081
8082               if Is_Subprogram (E1)
8083                 and then Nkind (Parent (Declaration_Node (E1))) =
8084                            N_Subprogram_Body
8085                 and then not Relaxed_RM_Semantics
8086               then
8087                  Set_Has_Completion (E);  --  to prevent cascaded error
8088                  Error_Pragma_Ref
8089                    ("pragma% requires separate spec and must come before "
8090                     & "body#", E1);
8091               end if;
8092
8093               --  Do not set the pragma on inherited operations or on formal
8094               --  subprograms.
8095
8096               if Comes_From_Source (E1)
8097                 and then Comp_Unit = Get_Source_Unit (E1)
8098                 and then not Is_Formal_Subprogram (E1)
8099                 and then Nkind (Original_Node (Parent (E1))) /=
8100                                                    N_Full_Type_Declaration
8101               then
8102                  if Present (Alias (E1))
8103                    and then Scope (E1) /= Scope (Alias (E1))
8104                  then
8105                     Error_Pragma_Ref
8106                       ("cannot apply pragma% to non-local entity& declared#",
8107                        E1);
8108                  end if;
8109
8110                  Set_Convention_From_Pragma (E1);
8111
8112                  if Prag_Id = Pragma_Import then
8113                     Generate_Reference (E1, Id, 'b');
8114                  end if;
8115               end if;
8116
8117            <<Continue>>
8118               null;
8119            end loop;
8120         end if;
8121      end Process_Convention;
8122
8123      ----------------------------------------
8124      -- Process_Disable_Enable_Atomic_Sync --
8125      ----------------------------------------
8126
8127      procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id) is
8128      begin
8129         Check_No_Identifiers;
8130         Check_At_Most_N_Arguments (1);
8131
8132         --  Modeled internally as
8133         --    pragma Suppress/Unsuppress (Atomic_Synchronization [,Entity])
8134
8135         Rewrite (N,
8136           Make_Pragma (Loc,
8137             Chars                        => Nam,
8138             Pragma_Argument_Associations => New_List (
8139               Make_Pragma_Argument_Association (Loc,
8140                 Expression =>
8141                   Make_Identifier (Loc, Name_Atomic_Synchronization)))));
8142
8143         if Present (Arg1) then
8144            Append_To (Pragma_Argument_Associations (N), New_Copy (Arg1));
8145         end if;
8146
8147         Analyze (N);
8148      end Process_Disable_Enable_Atomic_Sync;
8149
8150      -------------------------------------------------
8151      -- Process_Extended_Import_Export_Internal_Arg --
8152      -------------------------------------------------
8153
8154      procedure Process_Extended_Import_Export_Internal_Arg
8155        (Arg_Internal : Node_Id := Empty)
8156      is
8157      begin
8158         if No (Arg_Internal) then
8159            Error_Pragma ("Internal parameter required for pragma%");
8160         end if;
8161
8162         if Nkind (Arg_Internal) = N_Identifier then
8163            null;
8164
8165         elsif Nkind (Arg_Internal) = N_Operator_Symbol
8166           and then (Prag_Id = Pragma_Import_Function
8167                       or else
8168                     Prag_Id = Pragma_Export_Function)
8169         then
8170            null;
8171
8172         else
8173            Error_Pragma_Arg
8174              ("wrong form for Internal parameter for pragma%", Arg_Internal);
8175         end if;
8176
8177         Check_Arg_Is_Local_Name (Arg_Internal);
8178      end Process_Extended_Import_Export_Internal_Arg;
8179
8180      --------------------------------------------------
8181      -- Process_Extended_Import_Export_Object_Pragma --
8182      --------------------------------------------------
8183
8184      procedure Process_Extended_Import_Export_Object_Pragma
8185        (Arg_Internal : Node_Id;
8186         Arg_External : Node_Id;
8187         Arg_Size     : Node_Id)
8188      is
8189         Def_Id : Entity_Id;
8190
8191      begin
8192         Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
8193         Def_Id := Entity (Arg_Internal);
8194
8195         if not Ekind_In (Def_Id, E_Constant, E_Variable) then
8196            Error_Pragma_Arg
8197              ("pragma% must designate an object", Arg_Internal);
8198         end if;
8199
8200         if Has_Rep_Pragma (Def_Id, Name_Common_Object)
8201              or else
8202            Has_Rep_Pragma (Def_Id, Name_Psect_Object)
8203         then
8204            Error_Pragma_Arg
8205              ("previous Common/Psect_Object applies, pragma % not permitted",
8206               Arg_Internal);
8207         end if;
8208
8209         if Rep_Item_Too_Late (Def_Id, N) then
8210            raise Pragma_Exit;
8211         end if;
8212
8213         Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
8214
8215         if Present (Arg_Size) then
8216            Check_Arg_Is_External_Name (Arg_Size);
8217         end if;
8218
8219         --  Export_Object case
8220
8221         if Prag_Id = Pragma_Export_Object then
8222            if not Is_Library_Level_Entity (Def_Id) then
8223               Error_Pragma_Arg
8224                 ("argument for pragma% must be library level entity",
8225                  Arg_Internal);
8226            end if;
8227
8228            if Ekind (Current_Scope) = E_Generic_Package then
8229               Error_Pragma ("pragma& cannot appear in a generic unit");
8230            end if;
8231
8232            if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
8233               Error_Pragma_Arg
8234                 ("exported object must have compile time known size",
8235                  Arg_Internal);
8236            end if;
8237
8238            if Warn_On_Export_Import and then Is_Exported (Def_Id) then
8239               Error_Msg_N ("??duplicate Export_Object pragma", N);
8240            else
8241               Set_Exported (Def_Id, Arg_Internal);
8242            end if;
8243
8244         --  Import_Object case
8245
8246         else
8247            if Is_Concurrent_Type (Etype (Def_Id)) then
8248               Error_Pragma_Arg
8249                 ("cannot use pragma% for task/protected object",
8250                  Arg_Internal);
8251            end if;
8252
8253            if Ekind (Def_Id) = E_Constant then
8254               Error_Pragma_Arg
8255                 ("cannot import a constant", Arg_Internal);
8256            end if;
8257
8258            if Warn_On_Export_Import
8259              and then Has_Discriminants (Etype (Def_Id))
8260            then
8261               Error_Msg_N
8262                 ("imported value must be initialized??", Arg_Internal);
8263            end if;
8264
8265            if Warn_On_Export_Import
8266              and then Is_Access_Type (Etype (Def_Id))
8267            then
8268               Error_Pragma_Arg
8269                 ("cannot import object of an access type??", Arg_Internal);
8270            end if;
8271
8272            if Warn_On_Export_Import
8273              and then Is_Imported (Def_Id)
8274            then
8275               Error_Msg_N ("??duplicate Import_Object pragma", N);
8276
8277            --  Check for explicit initialization present. Note that an
8278            --  initialization generated by the code generator, e.g. for an
8279            --  access type, does not count here.
8280
8281            elsif Present (Expression (Parent (Def_Id)))
8282               and then
8283                 Comes_From_Source
8284                   (Original_Node (Expression (Parent (Def_Id))))
8285            then
8286               Error_Msg_Sloc := Sloc (Def_Id);
8287               Error_Pragma_Arg
8288                 ("imported entities cannot be initialized (RM B.1(24))",
8289                  "\no initialization allowed for & declared#", Arg1);
8290            else
8291               Set_Imported (Def_Id);
8292               Note_Possible_Modification (Arg_Internal, Sure => False);
8293            end if;
8294         end if;
8295      end Process_Extended_Import_Export_Object_Pragma;
8296
8297      ------------------------------------------------------
8298      -- Process_Extended_Import_Export_Subprogram_Pragma --
8299      ------------------------------------------------------
8300
8301      procedure Process_Extended_Import_Export_Subprogram_Pragma
8302        (Arg_Internal                 : Node_Id;
8303         Arg_External                 : Node_Id;
8304         Arg_Parameter_Types          : Node_Id;
8305         Arg_Result_Type              : Node_Id := Empty;
8306         Arg_Mechanism                : Node_Id;
8307         Arg_Result_Mechanism         : Node_Id := Empty)
8308      is
8309         Ent       : Entity_Id;
8310         Def_Id    : Entity_Id;
8311         Hom_Id    : Entity_Id;
8312         Formal    : Entity_Id;
8313         Ambiguous : Boolean;
8314         Match     : Boolean;
8315
8316         function Same_Base_Type
8317          (Ptype  : Node_Id;
8318           Formal : Entity_Id) return Boolean;
8319         --  Determines if Ptype references the type of Formal. Note that only
8320         --  the base types need to match according to the spec. Ptype here is
8321         --  the argument from the pragma, which is either a type name, or an
8322         --  access attribute.
8323
8324         --------------------
8325         -- Same_Base_Type --
8326         --------------------
8327
8328         function Same_Base_Type
8329           (Ptype  : Node_Id;
8330            Formal : Entity_Id) return Boolean
8331         is
8332            Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
8333            Pref : Node_Id;
8334
8335         begin
8336            --  Case where pragma argument is typ'Access
8337
8338            if Nkind (Ptype) = N_Attribute_Reference
8339              and then Attribute_Name (Ptype) = Name_Access
8340            then
8341               Pref := Prefix (Ptype);
8342               Find_Type (Pref);
8343
8344               if not Is_Entity_Name (Pref)
8345                 or else Entity (Pref) = Any_Type
8346               then
8347                  raise Pragma_Exit;
8348               end if;
8349
8350               --  We have a match if the corresponding argument is of an
8351               --  anonymous access type, and its designated type matches the
8352               --  type of the prefix of the access attribute
8353
8354               return Ekind (Ftyp) = E_Anonymous_Access_Type
8355                 and then Base_Type (Entity (Pref)) =
8356                            Base_Type (Etype (Designated_Type (Ftyp)));
8357
8358            --  Case where pragma argument is a type name
8359
8360            else
8361               Find_Type (Ptype);
8362
8363               if not Is_Entity_Name (Ptype)
8364                 or else Entity (Ptype) = Any_Type
8365               then
8366                  raise Pragma_Exit;
8367               end if;
8368
8369               --  We have a match if the corresponding argument is of the type
8370               --  given in the pragma (comparing base types)
8371
8372               return Base_Type (Entity (Ptype)) = Ftyp;
8373            end if;
8374         end Same_Base_Type;
8375
8376      --  Start of processing for
8377      --  Process_Extended_Import_Export_Subprogram_Pragma
8378
8379      begin
8380         Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
8381         Ent := Empty;
8382         Ambiguous := False;
8383
8384         --  Loop through homonyms (overloadings) of the entity
8385
8386         Hom_Id := Entity (Arg_Internal);
8387         while Present (Hom_Id) loop
8388            Def_Id := Get_Base_Subprogram (Hom_Id);
8389
8390            --  We need a subprogram in the current scope
8391
8392            if not Is_Subprogram (Def_Id)
8393              or else Scope (Def_Id) /= Current_Scope
8394            then
8395               null;
8396
8397            else
8398               Match := True;
8399
8400               --  Pragma cannot apply to subprogram body
8401
8402               if Is_Subprogram (Def_Id)
8403                 and then Nkind (Parent (Declaration_Node (Def_Id))) =
8404                                                             N_Subprogram_Body
8405               then
8406                  Error_Pragma
8407                    ("pragma% requires separate spec and must come before "
8408                     & "body");
8409               end if;
8410
8411               --  Test result type if given, note that the result type
8412               --  parameter can only be present for the function cases.
8413
8414               if Present (Arg_Result_Type)
8415                 and then not Same_Base_Type (Arg_Result_Type, Def_Id)
8416               then
8417                  Match := False;
8418
8419               elsif Etype (Def_Id) /= Standard_Void_Type
8420                 and then Nam_In (Pname, Name_Export_Procedure,
8421                                         Name_Import_Procedure)
8422               then
8423                  Match := False;
8424
8425               --  Test parameter types if given. Note that this parameter has
8426               --  not been analyzed (and must not be, since it is semantic
8427               --  nonsense), so we get it as the parser left it.
8428
8429               elsif Present (Arg_Parameter_Types) then
8430                  Check_Matching_Types : declare
8431                     Formal : Entity_Id;
8432                     Ptype  : Node_Id;
8433
8434                  begin
8435                     Formal := First_Formal (Def_Id);
8436
8437                     if Nkind (Arg_Parameter_Types) = N_Null then
8438                        if Present (Formal) then
8439                           Match := False;
8440                        end if;
8441
8442                     --  A list of one type, e.g. (List) is parsed as a
8443                     --  parenthesized expression.
8444
8445                     elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
8446                       and then Paren_Count (Arg_Parameter_Types) = 1
8447                     then
8448                        if No (Formal)
8449                          or else Present (Next_Formal (Formal))
8450                        then
8451                           Match := False;
8452                        else
8453                           Match :=
8454                             Same_Base_Type (Arg_Parameter_Types, Formal);
8455                        end if;
8456
8457                     --  A list of more than one type is parsed as a aggregate
8458
8459                     elsif Nkind (Arg_Parameter_Types) = N_Aggregate
8460                       and then Paren_Count (Arg_Parameter_Types) = 0
8461                     then
8462                        Ptype := First (Expressions (Arg_Parameter_Types));
8463                        while Present (Ptype) or else Present (Formal) loop
8464                           if No (Ptype)
8465                             or else No (Formal)
8466                             or else not Same_Base_Type (Ptype, Formal)
8467                           then
8468                              Match := False;
8469                              exit;
8470                           else
8471                              Next_Formal (Formal);
8472                              Next (Ptype);
8473                           end if;
8474                        end loop;
8475
8476                     --  Anything else is of the wrong form
8477
8478                     else
8479                        Error_Pragma_Arg
8480                          ("wrong form for Parameter_Types parameter",
8481                           Arg_Parameter_Types);
8482                     end if;
8483                  end Check_Matching_Types;
8484               end if;
8485
8486               --  Match is now False if the entry we found did not match
8487               --  either a supplied Parameter_Types or Result_Types argument
8488
8489               if Match then
8490                  if No (Ent) then
8491                     Ent := Def_Id;
8492
8493                  --  Ambiguous case, the flag Ambiguous shows if we already
8494                  --  detected this and output the initial messages.
8495
8496                  else
8497                     if not Ambiguous then
8498                        Ambiguous := True;
8499                        Error_Msg_Name_1 := Pname;
8500                        Error_Msg_N
8501                          ("pragma% does not uniquely identify subprogram!",
8502                           N);
8503                        Error_Msg_Sloc := Sloc (Ent);
8504                        Error_Msg_N ("matching subprogram #!", N);
8505                        Ent := Empty;
8506                     end if;
8507
8508                     Error_Msg_Sloc := Sloc (Def_Id);
8509                     Error_Msg_N ("matching subprogram #!", N);
8510                  end if;
8511               end if;
8512            end if;
8513
8514            Hom_Id := Homonym (Hom_Id);
8515         end loop;
8516
8517         --  See if we found an entry
8518
8519         if No (Ent) then
8520            if not Ambiguous then
8521               if Is_Generic_Subprogram (Entity (Arg_Internal)) then
8522                  Error_Pragma
8523                    ("pragma% cannot be given for generic subprogram");
8524               else
8525                  Error_Pragma
8526                    ("pragma% does not identify local subprogram");
8527               end if;
8528            end if;
8529
8530            return;
8531         end if;
8532
8533         --  Import pragmas must be for imported entities
8534
8535         if Prag_Id = Pragma_Import_Function
8536              or else
8537            Prag_Id = Pragma_Import_Procedure
8538              or else
8539            Prag_Id = Pragma_Import_Valued_Procedure
8540         then
8541            if not Is_Imported (Ent) then
8542               Error_Pragma
8543                 ("pragma Import or Interface must precede pragma%");
8544            end if;
8545
8546         --  Here we have the Export case which can set the entity as exported
8547
8548         --  But does not do so if the specified external name is null, since
8549         --  that is taken as a signal in DEC Ada 83 (with which we want to be
8550         --  compatible) to request no external name.
8551
8552         elsif Nkind (Arg_External) = N_String_Literal
8553           and then String_Length (Strval (Arg_External)) = 0
8554         then
8555            null;
8556
8557         --  In all other cases, set entity as exported
8558
8559         else
8560            Set_Exported (Ent, Arg_Internal);
8561         end if;
8562
8563         --  Special processing for Valued_Procedure cases
8564
8565         if Prag_Id = Pragma_Import_Valued_Procedure
8566           or else
8567            Prag_Id = Pragma_Export_Valued_Procedure
8568         then
8569            Formal := First_Formal (Ent);
8570
8571            if No (Formal) then
8572               Error_Pragma ("at least one parameter required for pragma%");
8573
8574            elsif Ekind (Formal) /= E_Out_Parameter then
8575               Error_Pragma ("first parameter must have mode out for pragma%");
8576
8577            else
8578               Set_Is_Valued_Procedure (Ent);
8579            end if;
8580         end if;
8581
8582         Set_Extended_Import_Export_External_Name (Ent, Arg_External);
8583
8584         --  Process Result_Mechanism argument if present. We have already
8585         --  checked that this is only allowed for the function case.
8586
8587         if Present (Arg_Result_Mechanism) then
8588            Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
8589         end if;
8590
8591         --  Process Mechanism parameter if present. Note that this parameter
8592         --  is not analyzed, and must not be analyzed since it is semantic
8593         --  nonsense, so we get it in exactly as the parser left it.
8594
8595         if Present (Arg_Mechanism) then
8596            declare
8597               Formal : Entity_Id;
8598               Massoc : Node_Id;
8599               Mname  : Node_Id;
8600               Choice : Node_Id;
8601
8602            begin
8603               --  A single mechanism association without a formal parameter
8604               --  name is parsed as a parenthesized expression. All other
8605               --  cases are parsed as aggregates, so we rewrite the single
8606               --  parameter case as an aggregate for consistency.
8607
8608               if Nkind (Arg_Mechanism) /= N_Aggregate
8609                 and then Paren_Count (Arg_Mechanism) = 1
8610               then
8611                  Rewrite (Arg_Mechanism,
8612                    Make_Aggregate (Sloc (Arg_Mechanism),
8613                      Expressions => New_List (
8614                        Relocate_Node (Arg_Mechanism))));
8615               end if;
8616
8617               --  Case of only mechanism name given, applies to all formals
8618
8619               if Nkind (Arg_Mechanism) /= N_Aggregate then
8620                  Formal := First_Formal (Ent);
8621                  while Present (Formal) loop
8622                     Set_Mechanism_Value (Formal, Arg_Mechanism);
8623                     Next_Formal (Formal);
8624                  end loop;
8625
8626               --  Case of list of mechanism associations given
8627
8628               else
8629                  if Null_Record_Present (Arg_Mechanism) then
8630                     Error_Pragma_Arg
8631                       ("inappropriate form for Mechanism parameter",
8632                        Arg_Mechanism);
8633                  end if;
8634
8635                  --  Deal with positional ones first
8636
8637                  Formal := First_Formal (Ent);
8638
8639                  if Present (Expressions (Arg_Mechanism)) then
8640                     Mname := First (Expressions (Arg_Mechanism));
8641                     while Present (Mname) loop
8642                        if No (Formal) then
8643                           Error_Pragma_Arg
8644                             ("too many mechanism associations", Mname);
8645                        end if;
8646
8647                        Set_Mechanism_Value (Formal, Mname);
8648                        Next_Formal (Formal);
8649                        Next (Mname);
8650                     end loop;
8651                  end if;
8652
8653                  --  Deal with named entries
8654
8655                  if Present (Component_Associations (Arg_Mechanism)) then
8656                     Massoc := First (Component_Associations (Arg_Mechanism));
8657                     while Present (Massoc) loop
8658                        Choice := First (Choices (Massoc));
8659
8660                        if Nkind (Choice) /= N_Identifier
8661                          or else Present (Next (Choice))
8662                        then
8663                           Error_Pragma_Arg
8664                             ("incorrect form for mechanism association",
8665                              Massoc);
8666                        end if;
8667
8668                        Formal := First_Formal (Ent);
8669                        loop
8670                           if No (Formal) then
8671                              Error_Pragma_Arg
8672                                ("parameter name & not present", Choice);
8673                           end if;
8674
8675                           if Chars (Choice) = Chars (Formal) then
8676                              Set_Mechanism_Value
8677                                (Formal, Expression (Massoc));
8678
8679                              --  Set entity on identifier (needed by ASIS)
8680
8681                              Set_Entity (Choice, Formal);
8682
8683                              exit;
8684                           end if;
8685
8686                           Next_Formal (Formal);
8687                        end loop;
8688
8689                        Next (Massoc);
8690                     end loop;
8691                  end if;
8692               end if;
8693            end;
8694         end if;
8695      end Process_Extended_Import_Export_Subprogram_Pragma;
8696
8697      --------------------------
8698      -- Process_Generic_List --
8699      --------------------------
8700
8701      procedure Process_Generic_List is
8702         Arg : Node_Id;
8703         Exp : Node_Id;
8704
8705      begin
8706         Check_No_Identifiers;
8707         Check_At_Least_N_Arguments (1);
8708
8709         --  Check all arguments are names of generic units or instances
8710
8711         Arg := Arg1;
8712         while Present (Arg) loop
8713            Exp := Get_Pragma_Arg (Arg);
8714            Analyze (Exp);
8715
8716            if not Is_Entity_Name (Exp)
8717              or else
8718                (not Is_Generic_Instance (Entity (Exp))
8719                  and then
8720                 not Is_Generic_Unit (Entity (Exp)))
8721            then
8722               Error_Pragma_Arg
8723                 ("pragma% argument must be name of generic unit/instance",
8724                  Arg);
8725            end if;
8726
8727            Next (Arg);
8728         end loop;
8729      end Process_Generic_List;
8730
8731      ------------------------------------
8732      -- Process_Import_Predefined_Type --
8733      ------------------------------------
8734
8735      procedure Process_Import_Predefined_Type is
8736         Loc  : constant Source_Ptr := Sloc (N);
8737         Elmt : Elmt_Id;
8738         Ftyp : Node_Id := Empty;
8739         Decl : Node_Id;
8740         Def  : Node_Id;
8741         Nam  : Name_Id;
8742
8743      begin
8744         Nam := String_To_Name (Strval (Expression (Arg3)));
8745
8746         Elmt := First_Elmt (Predefined_Float_Types);
8747         while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
8748            Next_Elmt (Elmt);
8749         end loop;
8750
8751         Ftyp := Node (Elmt);
8752
8753         if Present (Ftyp) then
8754
8755            --  Don't build a derived type declaration, because predefined C
8756            --  types have no declaration anywhere, so cannot really be named.
8757            --  Instead build a full type declaration, starting with an
8758            --  appropriate type definition is built
8759
8760            if Is_Floating_Point_Type (Ftyp) then
8761               Def := Make_Floating_Point_Definition (Loc,
8762                 Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
8763                 Make_Real_Range_Specification (Loc,
8764                   Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
8765                   Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
8766
8767            --  Should never have a predefined type we cannot handle
8768
8769            else
8770               raise Program_Error;
8771            end if;
8772
8773            --  Build and insert a Full_Type_Declaration, which will be
8774            --  analyzed as soon as this list entry has been analyzed.
8775
8776            Decl := Make_Full_Type_Declaration (Loc,
8777              Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
8778              Type_Definition => Def);
8779
8780            Insert_After (N, Decl);
8781            Mark_Rewrite_Insertion (Decl);
8782
8783         else
8784            Error_Pragma_Arg ("no matching type found for pragma%",
8785            Arg2);
8786         end if;
8787      end Process_Import_Predefined_Type;
8788
8789      ---------------------------------
8790      -- Process_Import_Or_Interface --
8791      ---------------------------------
8792
8793      procedure Process_Import_Or_Interface is
8794         C      : Convention_Id;
8795         Def_Id : Entity_Id;
8796         Hom_Id : Entity_Id;
8797
8798      begin
8799         --  In Relaxed_RM_Semantics, support old Ada 83 style:
8800         --  pragma Import (Entity, "external name");
8801
8802         if Relaxed_RM_Semantics
8803           and then Arg_Count = 2
8804           and then Prag_Id = Pragma_Import
8805           and then Nkind (Expression (Arg2)) = N_String_Literal
8806         then
8807            C := Convention_C;
8808            Def_Id := Get_Pragma_Arg (Arg1);
8809            Analyze (Def_Id);
8810
8811            if not Is_Entity_Name (Def_Id) then
8812               Error_Pragma_Arg ("entity name required", Arg1);
8813            end if;
8814
8815            Def_Id := Entity (Def_Id);
8816            Kill_Size_Check_Code (Def_Id);
8817            Note_Possible_Modification (Get_Pragma_Arg (Arg1), Sure => False);
8818
8819         else
8820            Process_Convention (C, Def_Id);
8821
8822            --  A pragma that applies to a Ghost entity becomes Ghost for the
8823            --  purposes of legality checks and removal of ignored Ghost code.
8824
8825            Mark_Ghost_Pragma (N, Def_Id);
8826            Kill_Size_Check_Code (Def_Id);
8827            Note_Possible_Modification (Get_Pragma_Arg (Arg2), Sure => False);
8828         end if;
8829
8830         --  Various error checks
8831
8832         if Ekind_In (Def_Id, E_Variable, E_Constant) then
8833
8834            --  We do not permit Import to apply to a renaming declaration
8835
8836            if Present (Renamed_Object (Def_Id)) then
8837               Error_Pragma_Arg
8838                 ("pragma% not allowed for object renaming", Arg2);
8839
8840            --  User initialization is not allowed for imported object, but
8841            --  the object declaration may contain a default initialization,
8842            --  that will be discarded. Note that an explicit initialization
8843            --  only counts if it comes from source, otherwise it is simply
8844            --  the code generator making an implicit initialization explicit.
8845
8846            elsif Present (Expression (Parent (Def_Id)))
8847              and then Comes_From_Source
8848                         (Original_Node (Expression (Parent (Def_Id))))
8849            then
8850               --  Set imported flag to prevent cascaded errors
8851
8852               Set_Is_Imported (Def_Id);
8853
8854               Error_Msg_Sloc := Sloc (Def_Id);
8855               Error_Pragma_Arg
8856                 ("no initialization allowed for declaration of& #",
8857                  "\imported entities cannot be initialized (RM B.1(24))",
8858                  Arg2);
8859
8860            else
8861               --  If the pragma comes from an aspect specification the
8862               --  Is_Imported flag has already been set.
8863
8864               if not From_Aspect_Specification (N) then
8865                  Set_Imported (Def_Id);
8866               end if;
8867
8868               Process_Interface_Name (Def_Id, Arg3, Arg4, N);
8869
8870               --  Note that we do not set Is_Public here. That's because we
8871               --  only want to set it if there is no address clause, and we
8872               --  don't know that yet, so we delay that processing till
8873               --  freeze time.
8874
8875               --  pragma Import completes deferred constants
8876
8877               if Ekind (Def_Id) = E_Constant then
8878                  Set_Has_Completion (Def_Id);
8879               end if;
8880
8881               --  It is not possible to import a constant of an unconstrained
8882               --  array type (e.g. string) because there is no simple way to
8883               --  write a meaningful subtype for it.
8884
8885               if Is_Array_Type (Etype (Def_Id))
8886                 and then not Is_Constrained (Etype (Def_Id))
8887               then
8888                  Error_Msg_NE
8889                    ("imported constant& must have a constrained subtype",
8890                      N, Def_Id);
8891               end if;
8892            end if;
8893
8894         elsif Is_Subprogram_Or_Generic_Subprogram (Def_Id) then
8895
8896            --  If the name is overloaded, pragma applies to all of the denoted
8897            --  entities in the same declarative part, unless the pragma comes
8898            --  from an aspect specification or was generated by the compiler
8899            --  (such as for pragma Provide_Shift_Operators).
8900
8901            Hom_Id := Def_Id;
8902            while Present (Hom_Id) loop
8903
8904               Def_Id := Get_Base_Subprogram (Hom_Id);
8905
8906               --  Ignore inherited subprograms because the pragma will apply
8907               --  to the parent operation, which is the one called.
8908
8909               if Is_Overloadable (Def_Id)
8910                 and then Present (Alias (Def_Id))
8911               then
8912                  null;
8913
8914               --  If it is not a subprogram, it must be in an outer scope and
8915               --  pragma does not apply.
8916
8917               elsif not Is_Subprogram_Or_Generic_Subprogram (Def_Id) then
8918                  null;
8919
8920               --  The pragma does not apply to primitives of interfaces
8921
8922               elsif Is_Dispatching_Operation (Def_Id)
8923                 and then Present (Find_Dispatching_Type (Def_Id))
8924                 and then Is_Interface (Find_Dispatching_Type (Def_Id))
8925               then
8926                  null;
8927
8928               --  Verify that the homonym is in the same declarative part (not
8929               --  just the same scope). If the pragma comes from an aspect
8930               --  specification we know that it is part of the declaration.
8931
8932               elsif Parent (Unit_Declaration_Node (Def_Id)) /= Parent (N)
8933                 and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
8934                 and then not From_Aspect_Specification (N)
8935               then
8936                  exit;
8937
8938               else
8939                  --  If the pragma comes from an aspect specification the
8940                  --  Is_Imported flag has already been set.
8941
8942                  if not From_Aspect_Specification (N) then
8943                     Set_Imported (Def_Id);
8944                  end if;
8945
8946                  --  Reject an Import applied to an abstract subprogram
8947
8948                  if Is_Subprogram (Def_Id)
8949                    and then Is_Abstract_Subprogram (Def_Id)
8950                  then
8951                     Error_Msg_Sloc := Sloc (Def_Id);
8952                     Error_Msg_NE
8953                       ("cannot import abstract subprogram& declared#",
8954                        Arg2, Def_Id);
8955                  end if;
8956
8957                  --  Special processing for Convention_Intrinsic
8958
8959                  if C = Convention_Intrinsic then
8960
8961                     --  Link_Name argument not allowed for intrinsic
8962
8963                     Check_No_Link_Name;
8964
8965                     Set_Is_Intrinsic_Subprogram (Def_Id);
8966
8967                     --  If no external name is present, then check that this
8968                     --  is a valid intrinsic subprogram. If an external name
8969                     --  is present, then this is handled by the back end.
8970
8971                     if No (Arg3) then
8972                        Check_Intrinsic_Subprogram
8973                          (Def_Id, Get_Pragma_Arg (Arg2));
8974                     end if;
8975                  end if;
8976
8977                  --  Verify that the subprogram does not have a completion
8978                  --  through a renaming declaration. For other completions the
8979                  --  pragma appears as a too late representation.
8980
8981                  declare
8982                     Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
8983
8984                  begin
8985                     if Present (Decl)
8986                       and then Nkind (Decl) = N_Subprogram_Declaration
8987                       and then Present (Corresponding_Body (Decl))
8988                       and then Nkind (Unit_Declaration_Node
8989                                        (Corresponding_Body (Decl))) =
8990                                             N_Subprogram_Renaming_Declaration
8991                     then
8992                        Error_Msg_Sloc := Sloc (Def_Id);
8993                        Error_Msg_NE
8994                          ("cannot import&, renaming already provided for "
8995                           & "declaration #", N, Def_Id);
8996                     end if;
8997                  end;
8998
8999                  --  If the pragma comes from an aspect specification, there
9000                  --  must be an Import aspect specified as well. In the rare
9001                  --  case where Import is set to False, the suprogram needs to
9002                  --  have a local completion.
9003
9004                  declare
9005                     Imp_Aspect : constant Node_Id :=
9006                                    Find_Aspect (Def_Id, Aspect_Import);
9007                     Expr       : Node_Id;
9008
9009                  begin
9010                     if Present (Imp_Aspect)
9011                       and then Present (Expression (Imp_Aspect))
9012                     then
9013                        Expr := Expression (Imp_Aspect);
9014                        Analyze_And_Resolve (Expr, Standard_Boolean);
9015
9016                        if Is_Entity_Name (Expr)
9017                          and then Entity (Expr) = Standard_True
9018                        then
9019                           Set_Has_Completion (Def_Id);
9020                        end if;
9021
9022                     --  If there is no expression, the default is True, as for
9023                     --  all boolean aspects. Same for the older pragma.
9024
9025                     else
9026                        Set_Has_Completion (Def_Id);
9027                     end if;
9028                  end;
9029
9030                  Process_Interface_Name (Def_Id, Arg3, Arg4, N);
9031               end if;
9032
9033               if Is_Compilation_Unit (Hom_Id) then
9034
9035                  --  Its possible homonyms are not affected by the pragma.
9036                  --  Such homonyms might be present in the context of other
9037                  --  units being compiled.
9038
9039                  exit;
9040
9041               elsif From_Aspect_Specification (N) then
9042                  exit;
9043
9044               --  If the pragma was created by the compiler, then we don't
9045               --  want it to apply to other homonyms. This kind of case can
9046               --  occur when using pragma Provide_Shift_Operators, which
9047               --  generates implicit shift and rotate operators with Import
9048               --  pragmas that might apply to earlier explicit or implicit
9049               --  declarations marked with Import (for example, coming from
9050               --  an earlier pragma Provide_Shift_Operators for another type),
9051               --  and we don't generally want other homonyms being treated
9052               --  as imported or the pragma flagged as an illegal duplicate.
9053
9054               elsif not Comes_From_Source (N) then
9055                  exit;
9056
9057               else
9058                  Hom_Id := Homonym (Hom_Id);
9059               end if;
9060            end loop;
9061
9062         --  Import a CPP class
9063
9064         elsif C = Convention_CPP
9065           and then (Is_Record_Type (Def_Id)
9066                      or else Ekind (Def_Id) = E_Incomplete_Type)
9067         then
9068            if Ekind (Def_Id) = E_Incomplete_Type then
9069               if Present (Full_View (Def_Id)) then
9070                  Def_Id := Full_View (Def_Id);
9071
9072               else
9073                  Error_Msg_N
9074                    ("cannot import 'C'P'P type before full declaration seen",
9075                     Get_Pragma_Arg (Arg2));
9076
9077                  --  Although we have reported the error we decorate it as
9078                  --  CPP_Class to avoid reporting spurious errors
9079
9080                  Set_Is_CPP_Class (Def_Id);
9081                  return;
9082               end if;
9083            end if;
9084
9085            --  Types treated as CPP classes must be declared limited (note:
9086            --  this used to be a warning but there is no real benefit to it
9087            --  since we did effectively intend to treat the type as limited
9088            --  anyway).
9089
9090            if not Is_Limited_Type (Def_Id) then
9091               Error_Msg_N
9092                 ("imported 'C'P'P type must be limited",
9093                  Get_Pragma_Arg (Arg2));
9094            end if;
9095
9096            if Etype (Def_Id) /= Def_Id
9097              and then not Is_CPP_Class (Root_Type (Def_Id))
9098            then
9099               Error_Msg_N ("root type must be a 'C'P'P type", Arg1);
9100            end if;
9101
9102            Set_Is_CPP_Class (Def_Id);
9103
9104            --  Imported CPP types must not have discriminants (because C++
9105            --  classes do not have discriminants).
9106
9107            if Has_Discriminants (Def_Id) then
9108               Error_Msg_N
9109                 ("imported 'C'P'P type cannot have discriminants",
9110                  First (Discriminant_Specifications
9111                          (Declaration_Node (Def_Id))));
9112            end if;
9113
9114            --  Check that components of imported CPP types do not have default
9115            --  expressions. For private types this check is performed when the
9116            --  full view is analyzed (see Process_Full_View).
9117
9118            if not Is_Private_Type (Def_Id) then
9119               Check_CPP_Type_Has_No_Defaults (Def_Id);
9120            end if;
9121
9122         --  Import a CPP exception
9123
9124         elsif C = Convention_CPP
9125           and then Ekind (Def_Id) = E_Exception
9126         then
9127            if No (Arg3) then
9128               Error_Pragma_Arg
9129                 ("'External_'Name arguments is required for 'Cpp exception",
9130                  Arg3);
9131            else
9132               --  As only a string is allowed, Check_Arg_Is_External_Name
9133               --  isn't called.
9134
9135               Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
9136            end if;
9137
9138            if Present (Arg4) then
9139               Error_Pragma_Arg
9140                 ("Link_Name argument not allowed for imported Cpp exception",
9141                  Arg4);
9142            end if;
9143
9144            --  Do not call Set_Interface_Name as the name of the exception
9145            --  shouldn't be modified (and in particular it shouldn't be
9146            --  the External_Name). For exceptions, the External_Name is the
9147            --  name of the RTTI structure.
9148
9149            --  ??? Emit an error if pragma Import/Export_Exception is present
9150
9151         elsif Nkind (Parent (Def_Id)) = N_Incomplete_Type_Declaration then
9152            Check_No_Link_Name;
9153            Check_Arg_Count (3);
9154            Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
9155
9156            Process_Import_Predefined_Type;
9157
9158         else
9159            Error_Pragma_Arg
9160              ("second argument of pragma% must be object, subprogram "
9161               & "or incomplete type",
9162               Arg2);
9163         end if;
9164
9165         --  If this pragma applies to a compilation unit, then the unit, which
9166         --  is a subprogram, does not require (or allow) a body. We also do
9167         --  not need to elaborate imported procedures.
9168
9169         if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
9170            declare
9171               Cunit : constant Node_Id := Parent (Parent (N));
9172            begin
9173               Set_Body_Required (Cunit, False);
9174            end;
9175         end if;
9176      end Process_Import_Or_Interface;
9177
9178      --------------------
9179      -- Process_Inline --
9180      --------------------
9181
9182      procedure Process_Inline (Status : Inline_Status) is
9183         Applies : Boolean;
9184         Assoc   : Node_Id;
9185         Decl    : Node_Id;
9186         Subp    : Entity_Id;
9187         Subp_Id : Node_Id;
9188
9189         Ghost_Error_Posted : Boolean := False;
9190         --  Flag set when an error concerning the illegal mix of Ghost and
9191         --  non-Ghost subprograms is emitted.
9192
9193         Ghost_Id : Entity_Id := Empty;
9194         --  The entity of the first Ghost subprogram encountered while
9195         --  processing the arguments of the pragma.
9196
9197         procedure Check_Inline_Always_Placement (Spec_Id : Entity_Id);
9198         --  Verify the placement of pragma Inline_Always with respect to the
9199         --  initial declaration of subprogram Spec_Id.
9200
9201         function Inlining_Not_Possible (Subp : Entity_Id) return Boolean;
9202         --  Returns True if it can be determined at this stage that inlining
9203         --  is not possible, for example if the body is available and contains
9204         --  exception handlers, we prevent inlining, since otherwise we can
9205         --  get undefined symbols at link time. This function also emits a
9206         --  warning if the pragma appears too late.
9207         --
9208         --  ??? is business with link symbols still valid, or does it relate
9209         --  to front end ZCX which is being phased out ???
9210
9211         procedure Make_Inline (Subp : Entity_Id);
9212         --  Subp is the defining unit name of the subprogram declaration. If
9213         --  the pragma is valid, call Set_Inline_Flags on Subp, as well as on
9214         --  the corresponding body, if there is one present.
9215
9216         procedure Set_Inline_Flags (Subp : Entity_Id);
9217         --  Set Has_Pragma_{No_Inline,Inline,Inline_Always} flag on Subp.
9218         --  Also set or clear Is_Inlined flag on Subp depending on Status.
9219
9220         -----------------------------------
9221         -- Check_Inline_Always_Placement --
9222         -----------------------------------
9223
9224         procedure Check_Inline_Always_Placement (Spec_Id : Entity_Id) is
9225            Spec_Decl : constant Node_Id := Unit_Declaration_Node (Spec_Id);
9226
9227            function Compilation_Unit_OK return Boolean;
9228            pragma Inline (Compilation_Unit_OK);
9229            --  Determine whether pragma Inline_Always applies to a compatible
9230            --  compilation unit denoted by Spec_Id.
9231
9232            function Declarative_List_OK return Boolean;
9233            pragma Inline (Declarative_List_OK);
9234            --  Determine whether the initial declaration of subprogram Spec_Id
9235            --  and the pragma appear in compatible declarative lists.
9236
9237            function Subprogram_Body_OK return Boolean;
9238            pragma Inline (Subprogram_Body_OK);
9239            --  Determine whether pragma Inline_Always applies to a compatible
9240            --  subprogram body denoted by Spec_Id.
9241
9242            -------------------------
9243            -- Compilation_Unit_OK --
9244            -------------------------
9245
9246            function Compilation_Unit_OK return Boolean is
9247               Comp_Unit : constant Node_Id := Parent (Spec_Decl);
9248
9249            begin
9250               --  The pragma appears after the initial declaration of a
9251               --  compilation unit.
9252
9253               --    procedure Comp_Unit;
9254               --    pragma Inline_Always (Comp_Unit);
9255
9256               --  Note that for compatibility reasons, the following case is
9257               --  also accepted.
9258
9259               --    procedure Stand_Alone_Body_Comp_Unit is
9260               --       ...
9261               --    end Stand_Alone_Body_Comp_Unit;
9262               --    pragma Inline_Always (Stand_Alone_Body_Comp_Unit);
9263
9264               return
9265                 Nkind (Comp_Unit) = N_Compilation_Unit
9266                   and then Present (Aux_Decls_Node (Comp_Unit))
9267                   and then Is_List_Member (N)
9268                   and then List_Containing (N) =
9269                              Pragmas_After (Aux_Decls_Node (Comp_Unit));
9270            end Compilation_Unit_OK;
9271
9272            -------------------------
9273            -- Declarative_List_OK --
9274            -------------------------
9275
9276            function Declarative_List_OK return Boolean is
9277               Context : constant Node_Id := Parent (Spec_Decl);
9278
9279               Init_Decl : Node_Id;
9280               Init_List : List_Id;
9281               Prag_List : List_Id;
9282
9283            begin
9284               --  Determine the proper initial declaration. In general this is
9285               --  the declaration node of the subprogram except when the input
9286               --  denotes a generic instantiation.
9287
9288               --    procedure Inst is new Gen;
9289               --    pragma Inline_Always (Inst);
9290
9291               --  In this case the original subprogram is moved inside an
9292               --  anonymous package while pragma Inline_Always remains at the
9293               --  level of the anonymous package. Use the declaration of the
9294               --  package because it reflects the placement of the original
9295               --  instantiation.
9296
9297               --    package Anon_Pack is
9298               --       procedure Inst is ... end Inst;  --  original
9299               --    end Anon_Pack;
9300
9301               --    procedure Inst renames Anon_Pack.Inst;
9302               --    pragma Inline_Always (Inst);
9303
9304               if Is_Generic_Instance (Spec_Id) then
9305                  Init_Decl := Parent (Parent (Spec_Decl));
9306                  pragma Assert (Nkind (Init_Decl) = N_Package_Declaration);
9307               else
9308                  Init_Decl := Spec_Decl;
9309               end if;
9310
9311               if Is_List_Member (Init_Decl) and then Is_List_Member (N) then
9312                  Init_List := List_Containing (Init_Decl);
9313                  Prag_List := List_Containing (N);
9314
9315                  --  The pragma and then initial declaration appear within the
9316                  --  same declarative list.
9317
9318                  if Init_List = Prag_List then
9319                     return True;
9320
9321                  --  A special case of the above is when both the pragma and
9322                  --  the initial declaration appear in different lists of a
9323                  --  package spec, protected definition, or a task definition.
9324
9325                  --    package Pack is
9326                  --       procedure Proc;
9327                  --    private
9328                  --       pragma Inline_Always (Proc);
9329                  --    end Pack;
9330
9331                  elsif Nkind_In (Context, N_Package_Specification,
9332                                           N_Protected_Definition,
9333                                           N_Task_Definition)
9334                    and then Init_List = Visible_Declarations (Context)
9335                    and then Prag_List = Private_Declarations (Context)
9336                  then
9337                     return True;
9338                  end if;
9339               end if;
9340
9341               return False;
9342            end Declarative_List_OK;
9343
9344            ------------------------
9345            -- Subprogram_Body_OK --
9346            ------------------------
9347
9348            function Subprogram_Body_OK return Boolean is
9349               Body_Decl : Node_Id;
9350
9351            begin
9352               --  The pragma appears within the declarative list of a stand-
9353               --  alone subprogram body.
9354
9355               --    procedure Stand_Alone_Body is
9356               --       pragma Inline_Always (Stand_Alone_Body);
9357               --    begin
9358               --       ...
9359               --    end Stand_Alone_Body;
9360
9361               --  The compiler creates a dummy spec in this case, however the
9362               --  pragma remains within the declarative list of the body.
9363
9364               if Nkind (Spec_Decl) = N_Subprogram_Declaration
9365                 and then not Comes_From_Source (Spec_Decl)
9366                 and then Present (Corresponding_Body (Spec_Decl))
9367               then
9368                  Body_Decl :=
9369                    Unit_Declaration_Node (Corresponding_Body (Spec_Decl));
9370
9371                  if Present (Declarations (Body_Decl))
9372                    and then Is_List_Member (N)
9373                    and then List_Containing (N) = Declarations (Body_Decl)
9374                  then
9375                     return True;
9376                  end if;
9377               end if;
9378
9379               return False;
9380            end Subprogram_Body_OK;
9381
9382         --  Start of processing for Check_Inline_Always_Placement
9383
9384         begin
9385            --  This check is relevant only for pragma Inline_Always
9386
9387            if Pname /= Name_Inline_Always then
9388               return;
9389
9390            --  Nothing to do when the pragma is internally generated on the
9391            --  assumption that it is properly placed.
9392
9393            elsif not Comes_From_Source (N) then
9394               return;
9395
9396            --  Nothing to do for internally generated subprograms that act
9397            --  as accidental homonyms of a source subprogram being inlined.
9398
9399            elsif not Comes_From_Source (Spec_Id) then
9400               return;
9401
9402            --  Nothing to do for generic formal subprograms that act as
9403            --  homonyms of another source subprogram being inlined.
9404
9405            elsif Is_Formal_Subprogram (Spec_Id) then
9406               return;
9407
9408            elsif Compilation_Unit_OK
9409              or else Declarative_List_OK
9410              or else Subprogram_Body_OK
9411            then
9412               return;
9413            end if;
9414
9415            --  At this point it is known that the pragma applies to or appears
9416            --  within a completing body, a completing stub, or a subunit.
9417
9418            Error_Msg_Name_1 := Pname;
9419            Error_Msg_Name_2 := Chars (Spec_Id);
9420            Error_Msg_Sloc   := Sloc (Spec_Id);
9421
9422            Error_Msg_N
9423              ("pragma % must appear on initial declaration of subprogram "
9424               & "% defined #", N);
9425         end Check_Inline_Always_Placement;
9426
9427         ---------------------------
9428         -- Inlining_Not_Possible --
9429         ---------------------------
9430
9431         function Inlining_Not_Possible (Subp : Entity_Id) return Boolean is
9432            Decl  : constant Node_Id := Unit_Declaration_Node (Subp);
9433            Stats : Node_Id;
9434
9435         begin
9436            if Nkind (Decl) = N_Subprogram_Body then
9437               Stats := Handled_Statement_Sequence (Decl);
9438               return Present (Exception_Handlers (Stats))
9439                 or else Present (At_End_Proc (Stats));
9440
9441            elsif Nkind (Decl) = N_Subprogram_Declaration
9442              and then Present (Corresponding_Body (Decl))
9443            then
9444               if Analyzed (Corresponding_Body (Decl)) then
9445                  Error_Msg_N ("pragma appears too late, ignored??", N);
9446                  return True;
9447
9448               --  If the subprogram is a renaming as body, the body is just a
9449               --  call to the renamed subprogram, and inlining is trivially
9450               --  possible.
9451
9452               elsif
9453                 Nkind (Unit_Declaration_Node (Corresponding_Body (Decl))) =
9454                                             N_Subprogram_Renaming_Declaration
9455               then
9456                  return False;
9457
9458               else
9459                  Stats :=
9460                    Handled_Statement_Sequence
9461                        (Unit_Declaration_Node (Corresponding_Body (Decl)));
9462
9463                  return
9464                    Present (Exception_Handlers (Stats))
9465                      or else Present (At_End_Proc (Stats));
9466               end if;
9467
9468            else
9469               --  If body is not available, assume the best, the check is
9470               --  performed again when compiling enclosing package bodies.
9471
9472               return False;
9473            end if;
9474         end Inlining_Not_Possible;
9475
9476         -----------------
9477         -- Make_Inline --
9478         -----------------
9479
9480         procedure Make_Inline (Subp : Entity_Id) is
9481            Kind       : constant Entity_Kind := Ekind (Subp);
9482            Inner_Subp : Entity_Id   := Subp;
9483
9484         begin
9485            --  Ignore if bad type, avoid cascaded error
9486
9487            if Etype (Subp) = Any_Type then
9488               Applies := True;
9489               return;
9490
9491            --  If inlining is not possible, for now do not treat as an error
9492
9493            elsif Status /= Suppressed
9494              and then Front_End_Inlining
9495              and then Inlining_Not_Possible (Subp)
9496            then
9497               Applies := True;
9498               return;
9499
9500            --  Here we have a candidate for inlining, but we must exclude
9501            --  derived operations. Otherwise we would end up trying to inline
9502            --  a phantom declaration, and the result would be to drag in a
9503            --  body which has no direct inlining associated with it. That
9504            --  would not only be inefficient but would also result in the
9505            --  backend doing cross-unit inlining in cases where it was
9506            --  definitely inappropriate to do so.
9507
9508            --  However, a simple Comes_From_Source test is insufficient, since
9509            --  we do want to allow inlining of generic instances which also do
9510            --  not come from source. We also need to recognize specs generated
9511            --  by the front-end for bodies that carry the pragma. Finally,
9512            --  predefined operators do not come from source but are not
9513            --  inlineable either.
9514
9515            elsif Is_Generic_Instance (Subp)
9516              or else Nkind (Parent (Parent (Subp))) = N_Subprogram_Declaration
9517            then
9518               null;
9519
9520            elsif not Comes_From_Source (Subp)
9521              and then Scope (Subp) /= Standard_Standard
9522            then
9523               Applies := True;
9524               return;
9525            end if;
9526
9527            --  The referenced entity must either be the enclosing entity, or
9528            --  an entity declared within the current open scope.
9529
9530            if Present (Scope (Subp))
9531              and then Scope (Subp) /= Current_Scope
9532              and then Subp /= Current_Scope
9533            then
9534               Error_Pragma_Arg
9535                 ("argument of% must be entity in current scope", Assoc);
9536               return;
9537            end if;
9538
9539            --  Processing for procedure, operator or function. If subprogram
9540            --  is aliased (as for an instance) indicate that the renamed
9541            --  entity (if declared in the same unit) is inlined.
9542            --  If this is the anonymous subprogram created for a subprogram
9543            --  instance, the inlining applies to it directly. Otherwise we
9544            --  retrieve it as the alias of the visible subprogram instance.
9545
9546            if Is_Subprogram (Subp) then
9547
9548               --  Ensure that pragma Inline_Always is associated with the
9549               --  initial declaration of the subprogram.
9550
9551               Check_Inline_Always_Placement (Subp);
9552
9553               if Is_Wrapper_Package (Scope (Subp)) then
9554                  Inner_Subp := Subp;
9555               else
9556                  Inner_Subp := Ultimate_Alias (Inner_Subp);
9557               end if;
9558
9559               if In_Same_Source_Unit (Subp, Inner_Subp) then
9560                  Set_Inline_Flags (Inner_Subp);
9561
9562                  Decl := Parent (Parent (Inner_Subp));
9563
9564                  if Nkind (Decl) = N_Subprogram_Declaration
9565                    and then Present (Corresponding_Body (Decl))
9566                  then
9567                     Set_Inline_Flags (Corresponding_Body (Decl));
9568
9569                  elsif Is_Generic_Instance (Subp)
9570                    and then Comes_From_Source (Subp)
9571                  then
9572                     --  Indicate that the body needs to be created for
9573                     --  inlining subsequent calls. The instantiation node
9574                     --  follows the declaration of the wrapper package
9575                     --  created for it. The subprogram that requires the
9576                     --  body is the anonymous one in the wrapper package.
9577
9578                     if Scope (Subp) /= Standard_Standard
9579                       and then
9580                         Need_Subprogram_Instance_Body
9581                           (Next (Unit_Declaration_Node
9582                             (Scope (Alias (Subp)))), Subp)
9583                     then
9584                        null;
9585                     end if;
9586
9587                  --  Inline is a program unit pragma (RM 10.1.5) and cannot
9588                  --  appear in a formal part to apply to a formal subprogram.
9589                  --  Do not apply check within an instance or a formal package
9590                  --  the test will have been applied to the original generic.
9591
9592                  elsif Nkind (Decl) in N_Formal_Subprogram_Declaration
9593                    and then List_Containing (Decl) = List_Containing (N)
9594                    and then not In_Instance
9595                  then
9596                     Error_Msg_N
9597                       ("Inline cannot apply to a formal subprogram", N);
9598
9599                  --  If Subp is a renaming, it is the renamed entity that
9600                  --  will appear in any call, and be inlined. However, for
9601                  --  ASIS uses it is convenient to indicate that the renaming
9602                  --  itself is an inlined subprogram, so that some gnatcheck
9603                  --  rules can be applied in the absence of expansion.
9604
9605                  elsif Nkind (Decl) = N_Subprogram_Renaming_Declaration then
9606                     Set_Inline_Flags (Subp);
9607                  end if;
9608               end if;
9609
9610               Applies := True;
9611
9612            --  For a generic subprogram set flag as well, for use at the point
9613            --  of instantiation, to determine whether the body should be
9614            --  generated.
9615
9616            elsif Is_Generic_Subprogram (Subp) then
9617               Set_Inline_Flags (Subp);
9618               Applies := True;
9619
9620            --  Literals are by definition inlined
9621
9622            elsif Kind = E_Enumeration_Literal then
9623               null;
9624
9625            --  Anything else is an error
9626
9627            else
9628               Error_Pragma_Arg
9629                 ("expect subprogram name for pragma%", Assoc);
9630            end if;
9631         end Make_Inline;
9632
9633         ----------------------
9634         -- Set_Inline_Flags --
9635         ----------------------
9636
9637         procedure Set_Inline_Flags (Subp : Entity_Id) is
9638         begin
9639            --  First set the Has_Pragma_XXX flags and issue the appropriate
9640            --  errors and warnings for suspicious combinations.
9641
9642            if Prag_Id = Pragma_No_Inline then
9643               if Has_Pragma_Inline_Always (Subp) then
9644                  Error_Msg_N
9645                    ("Inline_Always and No_Inline are mutually exclusive", N);
9646               elsif Has_Pragma_Inline (Subp) then
9647                  Error_Msg_NE
9648                    ("Inline and No_Inline both specified for& ??",
9649                     N, Entity (Subp_Id));
9650               end if;
9651
9652               Set_Has_Pragma_No_Inline (Subp);
9653            else
9654               if Prag_Id = Pragma_Inline_Always then
9655                  if Has_Pragma_No_Inline (Subp) then
9656                     Error_Msg_N
9657                       ("Inline_Always and No_Inline are mutually exclusive",
9658                        N);
9659                  end if;
9660
9661                  Set_Has_Pragma_Inline_Always (Subp);
9662               else
9663                  if Has_Pragma_No_Inline (Subp) then
9664                     Error_Msg_NE
9665                       ("Inline and No_Inline both specified for& ??",
9666                        N, Entity (Subp_Id));
9667                  end if;
9668               end if;
9669
9670               Set_Has_Pragma_Inline (Subp);
9671            end if;
9672
9673            --  Then adjust the Is_Inlined flag. It can never be set if the
9674            --  subprogram is subject to pragma No_Inline.
9675
9676            case Status is
9677               when Suppressed =>
9678                  Set_Is_Inlined (Subp, False);
9679
9680               when Disabled =>
9681                  null;
9682
9683               when Enabled =>
9684                  if not Has_Pragma_No_Inline (Subp) then
9685                     Set_Is_Inlined (Subp, True);
9686                  end if;
9687            end case;
9688
9689            --  A pragma that applies to a Ghost entity becomes Ghost for the
9690            --  purposes of legality checks and removal of ignored Ghost code.
9691
9692            Mark_Ghost_Pragma (N, Subp);
9693
9694            --  Capture the entity of the first Ghost subprogram being
9695            --  processed for error detection purposes.
9696
9697            if Is_Ghost_Entity (Subp) then
9698               if No (Ghost_Id) then
9699                  Ghost_Id := Subp;
9700               end if;
9701
9702            --  Otherwise the subprogram is non-Ghost. It is illegal to mix
9703            --  references to Ghost and non-Ghost entities (SPARK RM 6.9).
9704
9705            elsif Present (Ghost_Id) and then not Ghost_Error_Posted then
9706               Ghost_Error_Posted := True;
9707
9708               Error_Msg_Name_1 := Pname;
9709               Error_Msg_N
9710                 ("pragma % cannot mention ghost and non-ghost subprograms",
9711                  N);
9712
9713               Error_Msg_Sloc := Sloc (Ghost_Id);
9714               Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
9715
9716               Error_Msg_Sloc := Sloc (Subp);
9717               Error_Msg_NE ("\& # declared as non-ghost", N, Subp);
9718            end if;
9719         end Set_Inline_Flags;
9720
9721      --  Start of processing for Process_Inline
9722
9723      begin
9724         Check_No_Identifiers;
9725         Check_At_Least_N_Arguments (1);
9726
9727         if Status = Enabled then
9728            Inline_Processing_Required := True;
9729         end if;
9730
9731         Assoc := Arg1;
9732         while Present (Assoc) loop
9733            Subp_Id := Get_Pragma_Arg (Assoc);
9734            Analyze (Subp_Id);
9735            Applies := False;
9736
9737            if Is_Entity_Name (Subp_Id) then
9738               Subp := Entity (Subp_Id);
9739
9740               if Subp = Any_Id then
9741
9742                  --  If previous error, avoid cascaded errors
9743
9744                  Check_Error_Detected;
9745                  Applies := True;
9746
9747               else
9748                  Make_Inline (Subp);
9749
9750                  --  For the pragma case, climb homonym chain. This is
9751                  --  what implements allowing the pragma in the renaming
9752                  --  case, with the result applying to the ancestors, and
9753                  --  also allows Inline to apply to all previous homonyms.
9754
9755                  if not From_Aspect_Specification (N) then
9756                     while Present (Homonym (Subp))
9757                       and then Scope (Homonym (Subp)) = Current_Scope
9758                     loop
9759                        Make_Inline (Homonym (Subp));
9760                        Subp := Homonym (Subp);
9761                     end loop;
9762                  end if;
9763               end if;
9764            end if;
9765
9766            if not Applies then
9767               Error_Pragma_Arg ("inappropriate argument for pragma%", Assoc);
9768            end if;
9769
9770            Next (Assoc);
9771         end loop;
9772
9773         --  If the context is a package declaration, the pragma indicates
9774         --  that inlining will require the presence of the corresponding
9775         --  body. (this may be further refined).
9776
9777         if not In_Instance
9778           and then Nkind (Unit (Cunit (Current_Sem_Unit))) =
9779                      N_Package_Declaration
9780         then
9781            Set_Body_Needed_For_Inlining (Cunit_Entity (Current_Sem_Unit));
9782         end if;
9783      end Process_Inline;
9784
9785      ----------------------------
9786      -- Process_Interface_Name --
9787      ----------------------------
9788
9789      procedure Process_Interface_Name
9790        (Subprogram_Def : Entity_Id;
9791         Ext_Arg        : Node_Id;
9792         Link_Arg       : Node_Id;
9793         Prag           : Node_Id)
9794      is
9795         Ext_Nam    : Node_Id;
9796         Link_Nam   : Node_Id;
9797         String_Val : String_Id;
9798
9799         procedure Check_Form_Of_Interface_Name (SN : Node_Id);
9800         --  SN is a string literal node for an interface name. This routine
9801         --  performs some minimal checks that the name is reasonable. In
9802         --  particular that no spaces or other obviously incorrect characters
9803         --  appear. This is only a warning, since any characters are allowed.
9804
9805         ----------------------------------
9806         -- Check_Form_Of_Interface_Name --
9807         ----------------------------------
9808
9809         procedure Check_Form_Of_Interface_Name (SN : Node_Id) is
9810            S  : constant String_Id := Strval (Expr_Value_S (SN));
9811            SL : constant Nat       := String_Length (S);
9812            C  : Char_Code;
9813
9814         begin
9815            if SL = 0 then
9816               Error_Msg_N ("interface name cannot be null string", SN);
9817            end if;
9818
9819            for J in 1 .. SL loop
9820               C := Get_String_Char (S, J);
9821
9822               --  Look for dubious character and issue unconditional warning.
9823               --  Definitely dubious if not in character range.
9824
9825               if not In_Character_Range (C)
9826
9827                 --  Commas, spaces and (back)slashes are dubious
9828
9829                 or else Get_Character (C) = ','
9830                 or else Get_Character (C) = '\'
9831                 or else Get_Character (C) = ' '
9832                 or else Get_Character (C) = '/'
9833               then
9834                  Error_Msg
9835                    ("??interface name contains illegal character",
9836                     Sloc (SN) + Source_Ptr (J));
9837               end if;
9838            end loop;
9839         end Check_Form_Of_Interface_Name;
9840
9841      --  Start of processing for Process_Interface_Name
9842
9843      begin
9844         --  If we are looking at a pragma that comes from an aspect then it
9845         --  needs to have its corresponding aspect argument expressions
9846         --  analyzed in addition to the generated pragma so that aspects
9847         --  within generic units get properly resolved.
9848
9849         if Present (Prag) and then From_Aspect_Specification (Prag) then
9850            declare
9851               Asp     : constant Node_Id := Corresponding_Aspect (Prag);
9852               Dummy_1 : Node_Id;
9853               Dummy_2 : Node_Id;
9854               Dummy_3 : Node_Id;
9855               EN      : Node_Id;
9856               LN      : Node_Id;
9857
9858            begin
9859               --  Obtain all interfacing aspects used to construct the pragma
9860
9861               Get_Interfacing_Aspects
9862                 (Asp, Dummy_1, EN, Dummy_2, Dummy_3, LN);
9863
9864               --  Analyze the expression of aspect External_Name
9865
9866               if Present (EN) then
9867                  Analyze (Expression (EN));
9868               end if;
9869
9870               --  Analyze the expressio of aspect Link_Name
9871
9872               if Present (LN) then
9873                  Analyze (Expression (LN));
9874               end if;
9875            end;
9876         end if;
9877
9878         if No (Link_Arg) then
9879            if No (Ext_Arg) then
9880               return;
9881
9882            elsif Chars (Ext_Arg) = Name_Link_Name then
9883               Ext_Nam  := Empty;
9884               Link_Nam := Expression (Ext_Arg);
9885
9886            else
9887               Check_Optional_Identifier (Ext_Arg, Name_External_Name);
9888               Ext_Nam  := Expression (Ext_Arg);
9889               Link_Nam := Empty;
9890            end if;
9891
9892         else
9893            Check_Optional_Identifier (Ext_Arg,  Name_External_Name);
9894            Check_Optional_Identifier (Link_Arg, Name_Link_Name);
9895            Ext_Nam  := Expression (Ext_Arg);
9896            Link_Nam := Expression (Link_Arg);
9897         end if;
9898
9899         --  Check expressions for external name and link name are static
9900
9901         if Present (Ext_Nam) then
9902            Check_Arg_Is_OK_Static_Expression (Ext_Nam, Standard_String);
9903            Check_Form_Of_Interface_Name (Ext_Nam);
9904
9905            --  Verify that external name is not the name of a local entity,
9906            --  which would hide the imported one and could lead to run-time
9907            --  surprises. The problem can only arise for entities declared in
9908            --  a package body (otherwise the external name is fully qualified
9909            --  and will not conflict).
9910
9911            declare
9912               Nam : Name_Id;
9913               E   : Entity_Id;
9914               Par : Node_Id;
9915
9916            begin
9917               if Prag_Id = Pragma_Import then
9918                  Nam := String_To_Name (Strval (Expr_Value_S (Ext_Nam)));
9919                  E   := Entity_Id (Get_Name_Table_Int (Nam));
9920
9921                  if Nam /= Chars (Subprogram_Def)
9922                    and then Present (E)
9923                    and then not Is_Overloadable (E)
9924                    and then Is_Immediately_Visible (E)
9925                    and then not Is_Imported (E)
9926                    and then Ekind (Scope (E)) = E_Package
9927                  then
9928                     Par := Parent (E);
9929                     while Present (Par) loop
9930                        if Nkind (Par) = N_Package_Body then
9931                           Error_Msg_Sloc := Sloc (E);
9932                           Error_Msg_NE
9933                             ("imported entity is hidden by & declared#",
9934                              Ext_Arg, E);
9935                           exit;
9936                        end if;
9937
9938                        Par := Parent (Par);
9939                     end loop;
9940                  end if;
9941               end if;
9942            end;
9943         end if;
9944
9945         if Present (Link_Nam) then
9946            Check_Arg_Is_OK_Static_Expression (Link_Nam, Standard_String);
9947            Check_Form_Of_Interface_Name (Link_Nam);
9948         end if;
9949
9950         --  If there is no link name, just set the external name
9951
9952         if No (Link_Nam) then
9953            Link_Nam := Adjust_External_Name_Case (Expr_Value_S (Ext_Nam));
9954
9955         --  For the Link_Name case, the given literal is preceded by an
9956         --  asterisk, which indicates to GCC that the given name should be
9957         --  taken literally, and in particular that no prepending of
9958         --  underlines should occur, even in systems where this is the
9959         --  normal default.
9960
9961         else
9962            Start_String;
9963            Store_String_Char (Get_Char_Code ('*'));
9964            String_Val := Strval (Expr_Value_S (Link_Nam));
9965            Store_String_Chars (String_Val);
9966            Link_Nam :=
9967              Make_String_Literal (Sloc (Link_Nam),
9968                Strval => End_String);
9969         end if;
9970
9971         --  Set the interface name. If the entity is a generic instance, use
9972         --  its alias, which is the callable entity.
9973
9974         if Is_Generic_Instance (Subprogram_Def) then
9975            Set_Encoded_Interface_Name
9976              (Alias (Get_Base_Subprogram (Subprogram_Def)), Link_Nam);
9977         else
9978            Set_Encoded_Interface_Name
9979              (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
9980         end if;
9981
9982         Check_Duplicated_Export_Name (Link_Nam);
9983      end Process_Interface_Name;
9984
9985      -----------------------------------------
9986      -- Process_Interrupt_Or_Attach_Handler --
9987      -----------------------------------------
9988
9989      procedure Process_Interrupt_Or_Attach_Handler is
9990         Handler  : constant Entity_Id := Entity (Get_Pragma_Arg (Arg1));
9991         Prot_Typ : constant Entity_Id := Scope (Handler);
9992
9993      begin
9994         --  A pragma that applies to a Ghost entity becomes Ghost for the
9995         --  purposes of legality checks and removal of ignored Ghost code.
9996
9997         Mark_Ghost_Pragma (N, Handler);
9998         Set_Is_Interrupt_Handler (Handler);
9999
10000         pragma Assert (Ekind (Prot_Typ) = E_Protected_Type);
10001
10002         Record_Rep_Item (Prot_Typ, N);
10003
10004         --  Chain the pragma on the contract for completeness
10005
10006         Add_Contract_Item (N, Handler);
10007      end Process_Interrupt_Or_Attach_Handler;
10008
10009      --------------------------------------------------
10010      -- Process_Restrictions_Or_Restriction_Warnings --
10011      --------------------------------------------------
10012
10013      --  Note: some of the simple identifier cases were handled in par-prag,
10014      --  but it is harmless (and more straightforward) to simply handle all
10015      --  cases here, even if it means we repeat a bit of work in some cases.
10016
10017      procedure Process_Restrictions_Or_Restriction_Warnings
10018        (Warn : Boolean)
10019      is
10020         Arg   : Node_Id;
10021         R_Id  : Restriction_Id;
10022         Id    : Name_Id;
10023         Expr  : Node_Id;
10024         Val   : Uint;
10025
10026      begin
10027         --  Ignore all Restrictions pragmas in CodePeer mode
10028
10029         if CodePeer_Mode then
10030            return;
10031         end if;
10032
10033         Check_Ada_83_Warning;
10034         Check_At_Least_N_Arguments (1);
10035         Check_Valid_Configuration_Pragma;
10036
10037         Arg := Arg1;
10038         while Present (Arg) loop
10039            Id := Chars (Arg);
10040            Expr := Get_Pragma_Arg (Arg);
10041
10042            --  Case of no restriction identifier present
10043
10044            if Id = No_Name then
10045               if Nkind (Expr) /= N_Identifier then
10046                  Error_Pragma_Arg
10047                    ("invalid form for restriction", Arg);
10048               end if;
10049
10050               R_Id :=
10051                 Get_Restriction_Id
10052                   (Process_Restriction_Synonyms (Expr));
10053
10054               if R_Id not in All_Boolean_Restrictions then
10055                  Error_Msg_Name_1 := Pname;
10056                  Error_Msg_N
10057                    ("invalid restriction identifier&", Get_Pragma_Arg (Arg));
10058
10059                  --  Check for possible misspelling
10060
10061                  for J in Restriction_Id loop
10062                     declare
10063                        Rnm : constant String := Restriction_Id'Image (J);
10064
10065                     begin
10066                        Name_Buffer (1 .. Rnm'Length) := Rnm;
10067                        Name_Len := Rnm'Length;
10068                        Set_Casing (All_Lower_Case);
10069
10070                        if Is_Bad_Spelling_Of (Chars (Expr), Name_Enter) then
10071                           Set_Casing
10072                             (Identifier_Casing
10073                               (Source_Index (Current_Sem_Unit)));
10074                           Error_Msg_String (1 .. Rnm'Length) :=
10075                             Name_Buffer (1 .. Name_Len);
10076                           Error_Msg_Strlen := Rnm'Length;
10077                           Error_Msg_N -- CODEFIX
10078                             ("\possible misspelling of ""~""",
10079                              Get_Pragma_Arg (Arg));
10080                           exit;
10081                        end if;
10082                     end;
10083                  end loop;
10084
10085                  raise Pragma_Exit;
10086               end if;
10087
10088               if Implementation_Restriction (R_Id) then
10089                  Check_Restriction (No_Implementation_Restrictions, Arg);
10090               end if;
10091
10092               --  Special processing for No_Elaboration_Code restriction
10093
10094               if R_Id = No_Elaboration_Code then
10095
10096                  --  Restriction is only recognized within a configuration
10097                  --  pragma file, or within a unit of the main extended
10098                  --  program. Note: the test for Main_Unit is needed to
10099                  --  properly include the case of configuration pragma files.
10100
10101                  if not (Current_Sem_Unit = Main_Unit
10102                           or else In_Extended_Main_Source_Unit (N))
10103                  then
10104                     return;
10105
10106                  --  Don't allow in a subunit unless already specified in
10107                  --  body or spec.
10108
10109                  elsif Nkind (Parent (N)) = N_Compilation_Unit
10110                    and then Nkind (Unit (Parent (N))) = N_Subunit
10111                    and then not Restriction_Active (No_Elaboration_Code)
10112                  then
10113                     Error_Msg_N
10114                       ("invalid specification of ""No_Elaboration_Code""",
10115                        N);
10116                     Error_Msg_N
10117                       ("\restriction cannot be specified in a subunit", N);
10118                     Error_Msg_N
10119                       ("\unless also specified in body or spec", N);
10120                     return;
10121
10122                  --  If we accept a No_Elaboration_Code restriction, then it
10123                  --  needs to be added to the configuration restriction set so
10124                  --  that we get proper application to other units in the main
10125                  --  extended source as required.
10126
10127                  else
10128                     Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
10129                  end if;
10130               end if;
10131
10132               --  If this is a warning, then set the warning unless we already
10133               --  have a real restriction active (we never want a warning to
10134               --  override a real restriction).
10135
10136               if Warn then
10137                  if not Restriction_Active (R_Id) then
10138                     Set_Restriction (R_Id, N);
10139                     Restriction_Warnings (R_Id) := True;
10140                  end if;
10141
10142               --  If real restriction case, then set it and make sure that the
10143               --  restriction warning flag is off, since a real restriction
10144               --  always overrides a warning.
10145
10146               else
10147                  Set_Restriction (R_Id, N);
10148                  Restriction_Warnings (R_Id) := False;
10149               end if;
10150
10151               --  Check for obsolescent restrictions in Ada 2005 mode
10152
10153               if not Warn
10154                 and then Ada_Version >= Ada_2005
10155                 and then (R_Id = No_Asynchronous_Control
10156                            or else
10157                           R_Id = No_Unchecked_Deallocation
10158                            or else
10159                           R_Id = No_Unchecked_Conversion)
10160               then
10161                  Check_Restriction (No_Obsolescent_Features, N);
10162               end if;
10163
10164               --  A very special case that must be processed here: pragma
10165               --  Restrictions (No_Exceptions) turns off all run-time
10166               --  checking. This is a bit dubious in terms of the formal
10167               --  language definition, but it is what is intended by RM
10168               --  H.4(12). Restriction_Warnings never affects generated code
10169               --  so this is done only in the real restriction case.
10170
10171               --  Atomic_Synchronization is not a real check, so it is not
10172               --  affected by this processing).
10173
10174               --  Ignore the effect of pragma Restrictions (No_Exceptions) on
10175               --  run-time checks in CodePeer and GNATprove modes: we want to
10176               --  generate checks for analysis purposes, as set respectively
10177               --  by -gnatC and -gnatd.F
10178
10179               if not Warn
10180                 and then not (CodePeer_Mode or GNATprove_Mode)
10181                 and then R_Id = No_Exceptions
10182               then
10183                  for J in Scope_Suppress.Suppress'Range loop
10184                     if J /= Atomic_Synchronization then
10185                        Scope_Suppress.Suppress (J) := True;
10186                     end if;
10187                  end loop;
10188               end if;
10189
10190            --  Case of No_Dependence => unit-name. Note that the parser
10191            --  already made the necessary entry in the No_Dependence table.
10192
10193            elsif Id = Name_No_Dependence then
10194               if not OK_No_Dependence_Unit_Name (Expr) then
10195                  raise Pragma_Exit;
10196               end if;
10197
10198            --  Case of No_Specification_Of_Aspect => aspect-identifier
10199
10200            elsif Id = Name_No_Specification_Of_Aspect then
10201               declare
10202                  A_Id : Aspect_Id;
10203
10204               begin
10205                  if Nkind (Expr) /= N_Identifier then
10206                     A_Id := No_Aspect;
10207                  else
10208                     A_Id := Get_Aspect_Id (Chars (Expr));
10209                  end if;
10210
10211                  if A_Id = No_Aspect then
10212                     Error_Pragma_Arg ("invalid restriction name", Arg);
10213                  else
10214                     Set_Restriction_No_Specification_Of_Aspect (Expr, Warn);
10215                  end if;
10216               end;
10217
10218            --  Case of No_Use_Of_Attribute => attribute-identifier
10219
10220            elsif Id = Name_No_Use_Of_Attribute then
10221               if Nkind (Expr) /= N_Identifier
10222                 or else not Is_Attribute_Name (Chars (Expr))
10223               then
10224                  Error_Msg_N ("unknown attribute name??", Expr);
10225
10226               else
10227                  Set_Restriction_No_Use_Of_Attribute (Expr, Warn);
10228               end if;
10229
10230            --  Case of No_Use_Of_Entity => fully-qualified-name
10231
10232            elsif Id = Name_No_Use_Of_Entity then
10233
10234               --  Restriction is only recognized within a configuration
10235               --  pragma file, or within a unit of the main extended
10236               --  program. Note: the test for Main_Unit is needed to
10237               --  properly include the case of configuration pragma files.
10238
10239               if Current_Sem_Unit = Main_Unit
10240                 or else In_Extended_Main_Source_Unit (N)
10241               then
10242                  if not OK_No_Dependence_Unit_Name (Expr) then
10243                     Error_Msg_N ("wrong form for entity name", Expr);
10244                  else
10245                     Set_Restriction_No_Use_Of_Entity
10246                       (Expr, Warn, No_Profile);
10247                  end if;
10248               end if;
10249
10250            --  Case of No_Use_Of_Pragma => pragma-identifier
10251
10252            elsif Id = Name_No_Use_Of_Pragma then
10253               if Nkind (Expr) /= N_Identifier
10254                 or else not Is_Pragma_Name (Chars (Expr))
10255               then
10256                  Error_Msg_N ("unknown pragma name??", Expr);
10257               else
10258                  Set_Restriction_No_Use_Of_Pragma (Expr, Warn);
10259               end if;
10260
10261            --  All other cases of restriction identifier present
10262
10263            else
10264               R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
10265               Analyze_And_Resolve (Expr, Any_Integer);
10266
10267               if R_Id not in All_Parameter_Restrictions then
10268                  Error_Pragma_Arg
10269                    ("invalid restriction parameter identifier", Arg);
10270
10271               elsif not Is_OK_Static_Expression (Expr) then
10272                  Flag_Non_Static_Expr
10273                    ("value must be static expression!", Expr);
10274                  raise Pragma_Exit;
10275
10276               elsif not Is_Integer_Type (Etype (Expr))
10277                 or else Expr_Value (Expr) < 0
10278               then
10279                  Error_Pragma_Arg
10280                    ("value must be non-negative integer", Arg);
10281               end if;
10282
10283               --  Restriction pragma is active
10284
10285               Val := Expr_Value (Expr);
10286
10287               if not UI_Is_In_Int_Range (Val) then
10288                  Error_Pragma_Arg
10289                    ("pragma ignored, value too large??", Arg);
10290               end if;
10291
10292               --  Warning case. If the real restriction is active, then we
10293               --  ignore the request, since warning never overrides a real
10294               --  restriction. Otherwise we set the proper warning. Note that
10295               --  this circuit sets the warning again if it is already set,
10296               --  which is what we want, since the constant may have changed.
10297
10298               if Warn then
10299                  if not Restriction_Active (R_Id) then
10300                     Set_Restriction
10301                       (R_Id, N, Integer (UI_To_Int (Val)));
10302                     Restriction_Warnings (R_Id) := True;
10303                  end if;
10304
10305               --  Real restriction case, set restriction and make sure warning
10306               --  flag is off since real restriction always overrides warning.
10307
10308               else
10309                  Set_Restriction (R_Id, N, Integer (UI_To_Int (Val)));
10310                  Restriction_Warnings (R_Id) := False;
10311               end if;
10312            end if;
10313
10314            Next (Arg);
10315         end loop;
10316      end Process_Restrictions_Or_Restriction_Warnings;
10317
10318      ---------------------------------
10319      -- Process_Suppress_Unsuppress --
10320      ---------------------------------
10321
10322      --  Note: this procedure makes entries in the check suppress data
10323      --  structures managed by Sem. See spec of package Sem for full
10324      --  details on how we handle recording of check suppression.
10325
10326      procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
10327         C    : Check_Id;
10328         E    : Entity_Id;
10329         E_Id : Node_Id;
10330
10331         In_Package_Spec : constant Boolean :=
10332                             Is_Package_Or_Generic_Package (Current_Scope)
10333                               and then not In_Package_Body (Current_Scope);
10334
10335         procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
10336         --  Used to suppress a single check on the given entity
10337
10338         --------------------------------
10339         -- Suppress_Unsuppress_Echeck --
10340         --------------------------------
10341
10342         procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
10343         begin
10344            --  Check for error of trying to set atomic synchronization for
10345            --  a non-atomic variable.
10346
10347            if C = Atomic_Synchronization
10348              and then not (Is_Atomic (E) or else Has_Atomic_Components (E))
10349            then
10350               Error_Msg_N
10351                 ("pragma & requires atomic type or variable",
10352                  Pragma_Identifier (Original_Node (N)));
10353            end if;
10354
10355            Set_Checks_May_Be_Suppressed (E);
10356
10357            if In_Package_Spec then
10358               Push_Global_Suppress_Stack_Entry
10359                 (Entity   => E,
10360                  Check    => C,
10361                  Suppress => Suppress_Case);
10362            else
10363               Push_Local_Suppress_Stack_Entry
10364                 (Entity   => E,
10365                  Check    => C,
10366                  Suppress => Suppress_Case);
10367            end if;
10368
10369            --  If this is a first subtype, and the base type is distinct,
10370            --  then also set the suppress flags on the base type.
10371
10372            if Is_First_Subtype (E) and then Etype (E) /= E then
10373               Suppress_Unsuppress_Echeck (Etype (E), C);
10374            end if;
10375         end Suppress_Unsuppress_Echeck;
10376
10377      --  Start of processing for Process_Suppress_Unsuppress
10378
10379      begin
10380         --  Ignore pragma Suppress/Unsuppress in CodePeer and GNATprove modes
10381         --  on user code: we want to generate checks for analysis purposes, as
10382         --  set respectively by -gnatC and -gnatd.F
10383
10384         if Comes_From_Source (N)
10385           and then (CodePeer_Mode or GNATprove_Mode)
10386         then
10387            return;
10388         end if;
10389
10390         --  Suppress/Unsuppress can appear as a configuration pragma, or in a
10391         --  declarative part or a package spec (RM 11.5(5)).
10392
10393         if not Is_Configuration_Pragma then
10394            Check_Is_In_Decl_Part_Or_Package_Spec;
10395         end if;
10396
10397         Check_At_Least_N_Arguments (1);
10398         Check_At_Most_N_Arguments (2);
10399         Check_No_Identifier (Arg1);
10400         Check_Arg_Is_Identifier (Arg1);
10401
10402         C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
10403
10404         if C = No_Check_Id then
10405            Error_Pragma_Arg
10406              ("argument of pragma% is not valid check name", Arg1);
10407         end if;
10408
10409         --  Warn that suppress of Elaboration_Check has no effect in SPARK
10410
10411         if C = Elaboration_Check and then SPARK_Mode = On then
10412            Error_Pragma_Arg
10413              ("Suppress of Elaboration_Check ignored in SPARK??",
10414               "\elaboration checking rules are statically enforced "
10415               & "(SPARK RM 7.7)", Arg1);
10416         end if;
10417
10418         --  One-argument case
10419
10420         if Arg_Count = 1 then
10421
10422            --  Make an entry in the local scope suppress table. This is the
10423            --  table that directly shows the current value of the scope
10424            --  suppress check for any check id value.
10425
10426            if C = All_Checks then
10427
10428               --  For All_Checks, we set all specific predefined checks with
10429               --  the exception of Elaboration_Check, which is handled
10430               --  specially because of not wanting All_Checks to have the
10431               --  effect of deactivating static elaboration order processing.
10432               --  Atomic_Synchronization is also not affected, since this is
10433               --  not a real check.
10434
10435               for J in Scope_Suppress.Suppress'Range loop
10436                  if J /= Elaboration_Check
10437                       and then
10438                     J /= Atomic_Synchronization
10439                  then
10440                     Scope_Suppress.Suppress (J) := Suppress_Case;
10441                  end if;
10442               end loop;
10443
10444            --  If not All_Checks, and predefined check, then set appropriate
10445            --  scope entry. Note that we will set Elaboration_Check if this
10446            --  is explicitly specified. Atomic_Synchronization is allowed
10447            --  only if internally generated and entity is atomic.
10448
10449            elsif C in Predefined_Check_Id
10450              and then (not Comes_From_Source (N)
10451                         or else C /= Atomic_Synchronization)
10452            then
10453               Scope_Suppress.Suppress (C) := Suppress_Case;
10454            end if;
10455
10456            --  Also make an entry in the Local_Entity_Suppress table
10457
10458            Push_Local_Suppress_Stack_Entry
10459              (Entity   => Empty,
10460               Check    => C,
10461               Suppress => Suppress_Case);
10462
10463         --  Case of two arguments present, where the check is suppressed for
10464         --  a specified entity (given as the second argument of the pragma)
10465
10466         else
10467            --  This is obsolescent in Ada 2005 mode
10468
10469            if Ada_Version >= Ada_2005 then
10470               Check_Restriction (No_Obsolescent_Features, Arg2);
10471            end if;
10472
10473            Check_Optional_Identifier (Arg2, Name_On);
10474            E_Id := Get_Pragma_Arg (Arg2);
10475            Analyze (E_Id);
10476
10477            if not Is_Entity_Name (E_Id) then
10478               Error_Pragma_Arg
10479                 ("second argument of pragma% must be entity name", Arg2);
10480            end if;
10481
10482            E := Entity (E_Id);
10483
10484            if E = Any_Id then
10485               return;
10486            end if;
10487
10488            --  A pragma that applies to a Ghost entity becomes Ghost for the
10489            --  purposes of legality checks and removal of ignored Ghost code.
10490
10491            Mark_Ghost_Pragma (N, E);
10492
10493            --  Enforce RM 11.5(7) which requires that for a pragma that
10494            --  appears within a package spec, the named entity must be
10495            --  within the package spec. We allow the package name itself
10496            --  to be mentioned since that makes sense, although it is not
10497            --  strictly allowed by 11.5(7).
10498
10499            if In_Package_Spec
10500              and then E /= Current_Scope
10501              and then Scope (E) /= Current_Scope
10502            then
10503               Error_Pragma_Arg
10504                 ("entity in pragma% is not in package spec (RM 11.5(7))",
10505                  Arg2);
10506            end if;
10507
10508            --  Loop through homonyms. As noted below, in the case of a package
10509            --  spec, only homonyms within the package spec are considered.
10510
10511            loop
10512               Suppress_Unsuppress_Echeck (E, C);
10513
10514               if Is_Generic_Instance (E)
10515                 and then Is_Subprogram (E)
10516                 and then Present (Alias (E))
10517               then
10518                  Suppress_Unsuppress_Echeck (Alias (E), C);
10519               end if;
10520
10521               --  Move to next homonym if not aspect spec case
10522
10523               exit when From_Aspect_Specification (N);
10524               E := Homonym (E);
10525               exit when No (E);
10526
10527               --  If we are within a package specification, the pragma only
10528               --  applies to homonyms in the same scope.
10529
10530               exit when In_Package_Spec
10531                 and then Scope (E) /= Current_Scope;
10532            end loop;
10533         end if;
10534      end Process_Suppress_Unsuppress;
10535
10536      -------------------------------
10537      -- Record_Independence_Check --
10538      -------------------------------
10539
10540      procedure Record_Independence_Check (N : Node_Id; E : Entity_Id) is
10541         pragma Unreferenced (N, E);
10542      begin
10543         --  For GCC back ends the validation is done a priori
10544         --  ??? This code is dead, might be useful in the future
10545
10546         --  if not AAMP_On_Target then
10547         --     return;
10548         --  end if;
10549
10550         --  Independence_Checks.Append ((N, E));
10551
10552         return;
10553      end Record_Independence_Check;
10554
10555      ------------------
10556      -- Set_Exported --
10557      ------------------
10558
10559      procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
10560      begin
10561         if Is_Imported (E) then
10562            Error_Pragma_Arg
10563              ("cannot export entity& that was previously imported", Arg);
10564
10565         elsif Present (Address_Clause (E))
10566           and then not Relaxed_RM_Semantics
10567         then
10568            Error_Pragma_Arg
10569              ("cannot export entity& that has an address clause", Arg);
10570         end if;
10571
10572         Set_Is_Exported (E);
10573
10574         --  Generate a reference for entity explicitly, because the
10575         --  identifier may be overloaded and name resolution will not
10576         --  generate one.
10577
10578         Generate_Reference (E, Arg);
10579
10580         --  Deal with exporting non-library level entity
10581
10582         if not Is_Library_Level_Entity (E) then
10583
10584            --  Not allowed at all for subprograms
10585
10586            if Is_Subprogram (E) then
10587               Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
10588
10589            --  Otherwise set public and statically allocated
10590
10591            else
10592               Set_Is_Public (E);
10593               Set_Is_Statically_Allocated (E);
10594
10595               --  Warn if the corresponding W flag is set
10596
10597               if Warn_On_Export_Import
10598
10599                 --  Only do this for something that was in the source. Not
10600                 --  clear if this can be False now (there used for sure to be
10601                 --  cases on some systems where it was False), but anyway the
10602                 --  test is harmless if not needed, so it is retained.
10603
10604                 and then Comes_From_Source (Arg)
10605               then
10606                  Error_Msg_NE
10607                    ("?x?& has been made static as a result of Export",
10608                     Arg, E);
10609                  Error_Msg_N
10610                    ("\?x?this usage is non-standard and non-portable",
10611                     Arg);
10612               end if;
10613            end if;
10614         end if;
10615
10616         if Warn_On_Export_Import and then Is_Type (E) then
10617            Error_Msg_NE ("exporting a type has no effect?x?", Arg, E);
10618         end if;
10619
10620         if Warn_On_Export_Import and Inside_A_Generic then
10621            Error_Msg_NE
10622              ("all instances of& will have the same external name?x?",
10623               Arg, E);
10624         end if;
10625      end Set_Exported;
10626
10627      ----------------------------------------------
10628      -- Set_Extended_Import_Export_External_Name --
10629      ----------------------------------------------
10630
10631      procedure Set_Extended_Import_Export_External_Name
10632        (Internal_Ent : Entity_Id;
10633         Arg_External : Node_Id)
10634      is
10635         Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
10636         New_Name : Node_Id;
10637
10638      begin
10639         if No (Arg_External) then
10640            return;
10641         end if;
10642
10643         Check_Arg_Is_External_Name (Arg_External);
10644
10645         if Nkind (Arg_External) = N_String_Literal then
10646            if String_Length (Strval (Arg_External)) = 0 then
10647               return;
10648            else
10649               New_Name := Adjust_External_Name_Case (Arg_External);
10650            end if;
10651
10652         elsif Nkind (Arg_External) = N_Identifier then
10653            New_Name := Get_Default_External_Name (Arg_External);
10654
10655         --  Check_Arg_Is_External_Name should let through only identifiers and
10656         --  string literals or static string expressions (which are folded to
10657         --  string literals).
10658
10659         else
10660            raise Program_Error;
10661         end if;
10662
10663         --  If we already have an external name set (by a prior normal Import
10664         --  or Export pragma), then the external names must match
10665
10666         if Present (Interface_Name (Internal_Ent)) then
10667
10668            --  Ignore mismatching names in CodePeer mode, to support some
10669            --  old compilers which would export the same procedure under
10670            --  different names, e.g:
10671            --     procedure P;
10672            --     pragma Export_Procedure (P, "a");
10673            --     pragma Export_Procedure (P, "b");
10674
10675            if CodePeer_Mode then
10676               return;
10677            end if;
10678
10679            Check_Matching_Internal_Names : declare
10680               S1 : constant String_Id := Strval (Old_Name);
10681               S2 : constant String_Id := Strval (New_Name);
10682
10683               procedure Mismatch;
10684               pragma No_Return (Mismatch);
10685               --  Called if names do not match
10686
10687               --------------
10688               -- Mismatch --
10689               --------------
10690
10691               procedure Mismatch is
10692               begin
10693                  Error_Msg_Sloc := Sloc (Old_Name);
10694                  Error_Pragma_Arg
10695                    ("external name does not match that given #",
10696                     Arg_External);
10697               end Mismatch;
10698
10699            --  Start of processing for Check_Matching_Internal_Names
10700
10701            begin
10702               if String_Length (S1) /= String_Length (S2) then
10703                  Mismatch;
10704
10705               else
10706                  for J in 1 .. String_Length (S1) loop
10707                     if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
10708                        Mismatch;
10709                     end if;
10710                  end loop;
10711               end if;
10712            end Check_Matching_Internal_Names;
10713
10714         --  Otherwise set the given name
10715
10716         else
10717            Set_Encoded_Interface_Name (Internal_Ent, New_Name);
10718            Check_Duplicated_Export_Name (New_Name);
10719         end if;
10720      end Set_Extended_Import_Export_External_Name;
10721
10722      ------------------
10723      -- Set_Imported --
10724      ------------------
10725
10726      procedure Set_Imported (E : Entity_Id) is
10727      begin
10728         --  Error message if already imported or exported
10729
10730         if Is_Exported (E) or else Is_Imported (E) then
10731
10732            --  Error if being set Exported twice
10733
10734            if Is_Exported (E) then
10735               Error_Msg_NE ("entity& was previously exported", N, E);
10736
10737            --  Ignore error in CodePeer mode where we treat all imported
10738            --  subprograms as unknown.
10739
10740            elsif CodePeer_Mode then
10741               goto OK;
10742
10743            --  OK if Import/Interface case
10744
10745            elsif Import_Interface_Present (N) then
10746               goto OK;
10747
10748            --  Error if being set Imported twice
10749
10750            else
10751               Error_Msg_NE ("entity& was previously imported", N, E);
10752            end if;
10753
10754            Error_Msg_Name_1 := Pname;
10755            Error_Msg_N
10756              ("\(pragma% applies to all previous entities)", N);
10757
10758            Error_Msg_Sloc  := Sloc (E);
10759            Error_Msg_NE ("\import not allowed for& declared#", N, E);
10760
10761         --  Here if not previously imported or exported, OK to import
10762
10763         else
10764            Set_Is_Imported (E);
10765
10766            --  For subprogram, set Import_Pragma field
10767
10768            if Is_Subprogram (E) then
10769               Set_Import_Pragma (E, N);
10770            end if;
10771
10772            --  If the entity is an object that is not at the library level,
10773            --  then it is statically allocated. We do not worry about objects
10774            --  with address clauses in this context since they are not really
10775            --  imported in the linker sense.
10776
10777            if Is_Object (E)
10778              and then not Is_Library_Level_Entity (E)
10779              and then No (Address_Clause (E))
10780            then
10781               Set_Is_Statically_Allocated (E);
10782            end if;
10783         end if;
10784
10785         <<OK>> null;
10786      end Set_Imported;
10787
10788      -------------------------
10789      -- Set_Mechanism_Value --
10790      -------------------------
10791
10792      --  Note: the mechanism name has not been analyzed (and cannot indeed be
10793      --  analyzed, since it is semantic nonsense), so we get it in the exact
10794      --  form created by the parser.
10795
10796      procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
10797         procedure Bad_Mechanism;
10798         pragma No_Return (Bad_Mechanism);
10799         --  Signal bad mechanism name
10800
10801         -------------------------
10802         -- Bad_Mechanism_Value --
10803         -------------------------
10804
10805         procedure Bad_Mechanism is
10806         begin
10807            Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
10808         end Bad_Mechanism;
10809
10810      --  Start of processing for Set_Mechanism_Value
10811
10812      begin
10813         if Mechanism (Ent) /= Default_Mechanism then
10814            Error_Msg_NE
10815              ("mechanism for & has already been set", Mech_Name, Ent);
10816         end if;
10817
10818         --  MECHANISM_NAME ::= value | reference
10819
10820         if Nkind (Mech_Name) = N_Identifier then
10821            if Chars (Mech_Name) = Name_Value then
10822               Set_Mechanism (Ent, By_Copy);
10823               return;
10824
10825            elsif Chars (Mech_Name) = Name_Reference then
10826               Set_Mechanism (Ent, By_Reference);
10827               return;
10828
10829            elsif Chars (Mech_Name) = Name_Copy then
10830               Error_Pragma_Arg
10831                 ("bad mechanism name, Value assumed", Mech_Name);
10832
10833            else
10834               Bad_Mechanism;
10835            end if;
10836
10837         else
10838            Bad_Mechanism;
10839         end if;
10840      end Set_Mechanism_Value;
10841
10842      --------------------------
10843      -- Set_Rational_Profile --
10844      --------------------------
10845
10846      --  The Rational profile includes Implicit_Packing, Use_Vads_Size, and
10847      --  extension to the semantics of renaming declarations.
10848
10849      procedure Set_Rational_Profile is
10850      begin
10851         Implicit_Packing     := True;
10852         Overriding_Renamings := True;
10853         Use_VADS_Size        := True;
10854      end Set_Rational_Profile;
10855
10856      ---------------------------
10857      -- Set_Ravenscar_Profile --
10858      ---------------------------
10859
10860      --  The tasks to be done here are
10861
10862      --    Set required policies
10863
10864      --      pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
10865      --        (For Ravenscar and GNAT_Extended_Ravenscar profiles)
10866      --      pragma Task_Dispatching_Policy (EDF_Across_Priorities)
10867      --        (For GNAT_Ravenscar_EDF profile)
10868      --      pragma Locking_Policy (Ceiling_Locking)
10869
10870      --    Set Detect_Blocking mode
10871
10872      --    Set required restrictions (see System.Rident for detailed list)
10873
10874      --    Set the No_Dependence rules
10875      --      No_Dependence => Ada.Asynchronous_Task_Control
10876      --      No_Dependence => Ada.Calendar
10877      --      No_Dependence => Ada.Execution_Time.Group_Budget
10878      --      No_Dependence => Ada.Execution_Time.Timers
10879      --      No_Dependence => Ada.Task_Attributes
10880      --      No_Dependence => System.Multiprocessors.Dispatching_Domains
10881
10882      procedure Set_Ravenscar_Profile (Profile : Profile_Name; N : Node_Id) is
10883         procedure Set_Error_Msg_To_Profile_Name;
10884         --  Set Error_Msg_String and Error_Msg_Strlen to the name of the
10885         --  profile.
10886
10887         -----------------------------------
10888         -- Set_Error_Msg_To_Profile_Name --
10889         -----------------------------------
10890
10891         procedure Set_Error_Msg_To_Profile_Name is
10892            Prof_Nam : constant Node_Id :=
10893                         Get_Pragma_Arg
10894                           (First (Pragma_Argument_Associations (N)));
10895
10896         begin
10897            Get_Name_String (Chars (Prof_Nam));
10898            Adjust_Name_Case (Global_Name_Buffer, Sloc (Prof_Nam));
10899            Error_Msg_Strlen := Name_Len;
10900            Error_Msg_String (1 .. Name_Len) := Name_Buffer (1 .. Name_Len);
10901         end Set_Error_Msg_To_Profile_Name;
10902
10903         --  Local variables
10904
10905         Nod     : Node_Id;
10906         Pref    : Node_Id;
10907         Pref_Id : Node_Id;
10908         Sel_Id  : Node_Id;
10909
10910         Profile_Dispatching_Policy : Character;
10911
10912      --  Start of processing for Set_Ravenscar_Profile
10913
10914      begin
10915         --  pragma Task_Dispatching_Policy (EDF_Across_Priorities)
10916
10917         if Profile = GNAT_Ravenscar_EDF then
10918            Profile_Dispatching_Policy := 'E';
10919
10920         --  pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
10921
10922         else
10923            Profile_Dispatching_Policy := 'F';
10924         end if;
10925
10926         if Task_Dispatching_Policy /= ' '
10927           and then Task_Dispatching_Policy /= Profile_Dispatching_Policy
10928         then
10929            Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
10930            Set_Error_Msg_To_Profile_Name;
10931            Error_Pragma ("Profile (~) incompatible with policy#");
10932
10933         --  Set the FIFO_Within_Priorities policy, but always preserve
10934         --  System_Location since we like the error message with the run time
10935         --  name.
10936
10937         else
10938            Task_Dispatching_Policy := Profile_Dispatching_Policy;
10939
10940            if Task_Dispatching_Policy_Sloc /= System_Location then
10941               Task_Dispatching_Policy_Sloc := Loc;
10942            end if;
10943         end if;
10944
10945         --  pragma Locking_Policy (Ceiling_Locking)
10946
10947         if Locking_Policy /= ' '
10948           and then Locking_Policy /= 'C'
10949         then
10950            Error_Msg_Sloc := Locking_Policy_Sloc;
10951            Set_Error_Msg_To_Profile_Name;
10952            Error_Pragma ("Profile (~) incompatible with policy#");
10953
10954         --  Set the Ceiling_Locking policy, but preserve System_Location since
10955         --  we like the error message with the run time name.
10956
10957         else
10958            Locking_Policy := 'C';
10959
10960            if Locking_Policy_Sloc /= System_Location then
10961               Locking_Policy_Sloc := Loc;
10962            end if;
10963         end if;
10964
10965         --  pragma Detect_Blocking
10966
10967         Detect_Blocking := True;
10968
10969         --  Set the corresponding restrictions
10970
10971         Set_Profile_Restrictions
10972           (Profile, N, Warn => Treat_Restrictions_As_Warnings);
10973
10974         --  Set the No_Dependence restrictions
10975
10976         --  The following No_Dependence restrictions:
10977         --    No_Dependence => Ada.Asynchronous_Task_Control
10978         --    No_Dependence => Ada.Calendar
10979         --    No_Dependence => Ada.Task_Attributes
10980         --  are already set by previous call to Set_Profile_Restrictions.
10981
10982         --  Set the following restrictions which were added to Ada 2005:
10983         --    No_Dependence => Ada.Execution_Time.Group_Budget
10984         --    No_Dependence => Ada.Execution_Time.Timers
10985
10986         if Ada_Version >= Ada_2005 then
10987            Pref_Id := Make_Identifier (Loc, Name_Find ("ada"));
10988            Sel_Id  := Make_Identifier (Loc, Name_Find ("execution_time"));
10989
10990            Pref :=
10991              Make_Selected_Component
10992                (Sloc          => Loc,
10993                 Prefix        => Pref_Id,
10994                 Selector_Name => Sel_Id);
10995
10996            Sel_Id := Make_Identifier (Loc, Name_Find ("group_budgets"));
10997
10998            Nod :=
10999              Make_Selected_Component
11000                (Sloc          => Loc,
11001                 Prefix        => Pref,
11002                 Selector_Name => Sel_Id);
11003
11004            Set_Restriction_No_Dependence
11005              (Unit    => Nod,
11006               Warn    => Treat_Restrictions_As_Warnings,
11007               Profile => Ravenscar);
11008
11009            Sel_Id := Make_Identifier (Loc, Name_Find ("timers"));
11010
11011            Nod :=
11012              Make_Selected_Component
11013                (Sloc          => Loc,
11014                 Prefix        => Pref,
11015                 Selector_Name => Sel_Id);
11016
11017            Set_Restriction_No_Dependence
11018              (Unit    => Nod,
11019               Warn    => Treat_Restrictions_As_Warnings,
11020               Profile => Ravenscar);
11021         end if;
11022
11023         --  Set the following restriction which was added to Ada 2012 (see
11024         --  AI-0171):
11025         --    No_Dependence => System.Multiprocessors.Dispatching_Domains
11026
11027         if Ada_Version >= Ada_2012 then
11028            Pref_Id := Make_Identifier (Loc, Name_Find ("system"));
11029            Sel_Id  := Make_Identifier (Loc, Name_Find ("multiprocessors"));
11030
11031            Pref :=
11032              Make_Selected_Component
11033                (Sloc          => Loc,
11034                 Prefix        => Pref_Id,
11035                 Selector_Name => Sel_Id);
11036
11037            Sel_Id := Make_Identifier (Loc, Name_Find ("dispatching_domains"));
11038
11039            Nod :=
11040              Make_Selected_Component
11041                (Sloc          => Loc,
11042                 Prefix        => Pref,
11043                 Selector_Name => Sel_Id);
11044
11045            Set_Restriction_No_Dependence
11046              (Unit    => Nod,
11047               Warn    => Treat_Restrictions_As_Warnings,
11048               Profile => Ravenscar);
11049         end if;
11050      end Set_Ravenscar_Profile;
11051
11052   --  Start of processing for Analyze_Pragma
11053
11054   begin
11055      --  The following code is a defense against recursion. Not clear that
11056      --  this can happen legitimately, but perhaps some error situations can
11057      --  cause it, and we did see this recursion during testing.
11058
11059      if Analyzed (N) then
11060         return;
11061      else
11062         Set_Analyzed (N);
11063      end if;
11064
11065      Check_Restriction_No_Use_Of_Pragma (N);
11066
11067      --  Ignore pragma if Ignore_Pragma applies. Also ignore pragma
11068      --  Default_Scalar_Storage_Order if the -gnatI switch was given.
11069
11070      if Should_Ignore_Pragma_Sem (N)
11071        or else (Prag_Id = Pragma_Default_Scalar_Storage_Order
11072                  and then Ignore_Rep_Clauses)
11073      then
11074         return;
11075      end if;
11076
11077      --  Deal with unrecognized pragma
11078
11079      if not Is_Pragma_Name (Pname) then
11080         if Warn_On_Unrecognized_Pragma then
11081            Error_Msg_Name_1 := Pname;
11082            Error_Msg_N ("?g?unrecognized pragma%!", Pragma_Identifier (N));
11083
11084            for PN in First_Pragma_Name .. Last_Pragma_Name loop
11085               if Is_Bad_Spelling_Of (Pname, PN) then
11086                  Error_Msg_Name_1 := PN;
11087                  Error_Msg_N -- CODEFIX
11088                    ("\?g?possible misspelling of %!", Pragma_Identifier (N));
11089                  exit;
11090               end if;
11091            end loop;
11092         end if;
11093
11094         return;
11095      end if;
11096
11097      --  Here to start processing for recognized pragma
11098
11099      Pname   := Original_Aspect_Pragma_Name (N);
11100
11101      --  Capture setting of Opt.Uneval_Old
11102
11103      case Opt.Uneval_Old is
11104         when 'A' =>
11105            Set_Uneval_Old_Accept (N);
11106
11107         when 'E' =>
11108            null;
11109
11110         when 'W' =>
11111            Set_Uneval_Old_Warn (N);
11112
11113         when others =>
11114            raise Program_Error;
11115      end case;
11116
11117      --  Check applicable policy. We skip this if Is_Checked or Is_Ignored
11118      --  is already set, indicating that we have already checked the policy
11119      --  at the right point. This happens for example in the case of a pragma
11120      --  that is derived from an Aspect.
11121
11122      if Is_Ignored (N) or else Is_Checked (N) then
11123         null;
11124
11125      --  For a pragma that is a rewriting of another pragma, copy the
11126      --  Is_Checked/Is_Ignored status from the rewritten pragma.
11127
11128      elsif Is_Rewrite_Substitution (N)
11129        and then Nkind (Original_Node (N)) = N_Pragma
11130        and then Original_Node (N) /= N
11131      then
11132         Set_Is_Ignored (N, Is_Ignored (Original_Node (N)));
11133         Set_Is_Checked (N, Is_Checked (Original_Node (N)));
11134
11135      --  Otherwise query the applicable policy at this point
11136
11137      else
11138         Check_Applicable_Policy (N);
11139
11140         --  If pragma is disabled, rewrite as NULL and skip analysis
11141
11142         if Is_Disabled (N) then
11143            Rewrite (N, Make_Null_Statement (Loc));
11144            Analyze (N);
11145            raise Pragma_Exit;
11146         end if;
11147      end if;
11148
11149      --  Preset arguments
11150
11151      Arg_Count := 0;
11152      Arg1      := Empty;
11153      Arg2      := Empty;
11154      Arg3      := Empty;
11155      Arg4      := Empty;
11156
11157      if Present (Pragma_Argument_Associations (N)) then
11158         Arg_Count := List_Length (Pragma_Argument_Associations (N));
11159         Arg1 := First (Pragma_Argument_Associations (N));
11160
11161         if Present (Arg1) then
11162            Arg2 := Next (Arg1);
11163
11164            if Present (Arg2) then
11165               Arg3 := Next (Arg2);
11166
11167               if Present (Arg3) then
11168                  Arg4 := Next (Arg3);
11169               end if;
11170            end if;
11171         end if;
11172      end if;
11173
11174      --  An enumeration type defines the pragmas that are supported by the
11175      --  implementation. Get_Pragma_Id (in package Prag) transforms a name
11176      --  into the corresponding enumeration value for the following case.
11177
11178      case Prag_Id is
11179
11180         -----------------
11181         -- Abort_Defer --
11182         -----------------
11183
11184         --  pragma Abort_Defer;
11185
11186         when Pragma_Abort_Defer =>
11187            GNAT_Pragma;
11188            Check_Arg_Count (0);
11189
11190            --  The only required semantic processing is to check the
11191            --  placement. This pragma must appear at the start of the
11192            --  statement sequence of a handled sequence of statements.
11193
11194            if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
11195              or else N /= First (Statements (Parent (N)))
11196            then
11197               Pragma_Misplaced;
11198            end if;
11199
11200         --------------------
11201         -- Abstract_State --
11202         --------------------
11203
11204         --  pragma Abstract_State (ABSTRACT_STATE_LIST);
11205
11206         --  ABSTRACT_STATE_LIST ::=
11207         --     null
11208         --  |  STATE_NAME_WITH_OPTIONS
11209         --  | (STATE_NAME_WITH_OPTIONS {, STATE_NAME_WITH_OPTIONS})
11210
11211         --  STATE_NAME_WITH_OPTIONS ::=
11212         --     STATE_NAME
11213         --  | (STATE_NAME with OPTION_LIST)
11214
11215         --  OPTION_LIST ::= OPTION {, OPTION}
11216
11217         --  OPTION ::=
11218         --    SIMPLE_OPTION
11219         --  | NAME_VALUE_OPTION
11220
11221         --  SIMPLE_OPTION ::= Ghost | Synchronous
11222
11223         --  NAME_VALUE_OPTION ::=
11224         --    Part_Of => ABSTRACT_STATE
11225         --  | External [=> EXTERNAL_PROPERTY_LIST]
11226
11227         --  EXTERNAL_PROPERTY_LIST ::=
11228         --     EXTERNAL_PROPERTY
11229         --  | (EXTERNAL_PROPERTY {, EXTERNAL_PROPERTY})
11230
11231         --  EXTERNAL_PROPERTY ::=
11232         --    Async_Readers    [=> boolean_EXPRESSION]
11233         --  | Async_Writers    [=> boolean_EXPRESSION]
11234         --  | Effective_Reads  [=> boolean_EXPRESSION]
11235         --  | Effective_Writes [=> boolean_EXPRESSION]
11236         --    others            => boolean_EXPRESSION
11237
11238         --  STATE_NAME ::= defining_identifier
11239
11240         --  ABSTRACT_STATE ::= name
11241
11242         --  Characteristics:
11243
11244         --    * Analysis - The annotation is fully analyzed immediately upon
11245         --    elaboration as it cannot forward reference entities.
11246
11247         --    * Expansion - None.
11248
11249         --    * Template - The annotation utilizes the generic template of the
11250         --    related package declaration.
11251
11252         --    * Globals - The annotation cannot reference global entities.
11253
11254         --    * Instance - The annotation is instantiated automatically when
11255         --    the related generic package is instantiated.
11256
11257         when Pragma_Abstract_State => Abstract_State : declare
11258            Missing_Parentheses : Boolean := False;
11259            --  Flag set when a state declaration with options is not properly
11260            --  parenthesized.
11261
11262            --  Flags used to verify the consistency of states
11263
11264            Non_Null_Seen : Boolean := False;
11265            Null_Seen     : Boolean := False;
11266
11267            procedure Analyze_Abstract_State
11268              (State   : Node_Id;
11269               Pack_Id : Entity_Id);
11270            --  Verify the legality of a single state declaration. Create and
11271            --  decorate a state abstraction entity and introduce it into the
11272            --  visibility chain. Pack_Id denotes the entity or the related
11273            --  package where pragma Abstract_State appears.
11274
11275            procedure Malformed_State_Error (State : Node_Id);
11276            --  Emit an error concerning the illegal declaration of abstract
11277            --  state State. This routine diagnoses syntax errors that lead to
11278            --  a different parse tree. The error is issued regardless of the
11279            --  SPARK mode in effect.
11280
11281            ----------------------------
11282            -- Analyze_Abstract_State --
11283            ----------------------------
11284
11285            procedure Analyze_Abstract_State
11286              (State   : Node_Id;
11287               Pack_Id : Entity_Id)
11288            is
11289               --  Flags used to verify the consistency of options
11290
11291               AR_Seen          : Boolean := False;
11292               AW_Seen          : Boolean := False;
11293               ER_Seen          : Boolean := False;
11294               EW_Seen          : Boolean := False;
11295               External_Seen    : Boolean := False;
11296               Ghost_Seen       : Boolean := False;
11297               Others_Seen      : Boolean := False;
11298               Part_Of_Seen     : Boolean := False;
11299               Synchronous_Seen : Boolean := False;
11300
11301               --  Flags used to store the static value of all external states'
11302               --  expressions.
11303
11304               AR_Val : Boolean := False;
11305               AW_Val : Boolean := False;
11306               ER_Val : Boolean := False;
11307               EW_Val : Boolean := False;
11308
11309               State_Id : Entity_Id := Empty;
11310               --  The entity to be generated for the current state declaration
11311
11312               procedure Analyze_External_Option (Opt : Node_Id);
11313               --  Verify the legality of option External
11314
11315               procedure Analyze_External_Property
11316                 (Prop : Node_Id;
11317                  Expr : Node_Id := Empty);
11318               --  Verify the legailty of a single external property. Prop
11319               --  denotes the external property. Expr is the expression used
11320               --  to set the property.
11321
11322               procedure Analyze_Part_Of_Option (Opt : Node_Id);
11323               --  Verify the legality of option Part_Of
11324
11325               procedure Check_Duplicate_Option
11326                 (Opt    : Node_Id;
11327                  Status : in out Boolean);
11328               --  Flag Status denotes whether a particular option has been
11329               --  seen while processing a state. This routine verifies that
11330               --  Opt is not a duplicate option and sets the flag Status
11331               --  (SPARK RM 7.1.4(1)).
11332
11333               procedure Check_Duplicate_Property
11334                 (Prop   : Node_Id;
11335                  Status : in out Boolean);
11336               --  Flag Status denotes whether a particular property has been
11337               --  seen while processing option External. This routine verifies
11338               --  that Prop is not a duplicate property and sets flag Status.
11339               --  Opt is not a duplicate property and sets the flag Status.
11340               --  (SPARK RM 7.1.4(2))
11341
11342               procedure Check_Ghost_Synchronous;
11343               --  Ensure that the abstract state is not subject to both Ghost
11344               --  and Synchronous simple options. Emit an error if this is the
11345               --  case.
11346
11347               procedure Create_Abstract_State
11348                 (Nam     : Name_Id;
11349                  Decl    : Node_Id;
11350                  Loc     : Source_Ptr;
11351                  Is_Null : Boolean);
11352               --  Generate an abstract state entity with name Nam and enter it
11353               --  into visibility. Decl is the "declaration" of the state as
11354               --  it appears in pragma Abstract_State. Loc is the location of
11355               --  the related state "declaration". Flag Is_Null should be set
11356               --  when the associated Abstract_State pragma defines a null
11357               --  state.
11358
11359               -----------------------------
11360               -- Analyze_External_Option --
11361               -----------------------------
11362
11363               procedure Analyze_External_Option (Opt : Node_Id) is
11364                  Errors : constant Nat := Serious_Errors_Detected;
11365                  Prop   : Node_Id;
11366                  Props  : Node_Id := Empty;
11367
11368               begin
11369                  if Nkind (Opt) = N_Component_Association then
11370                     Props := Expression (Opt);
11371                  end if;
11372
11373                  --  External state with properties
11374
11375                  if Present (Props) then
11376
11377                     --  Multiple properties appear as an aggregate
11378
11379                     if Nkind (Props) = N_Aggregate then
11380
11381                        --  Simple property form
11382
11383                        Prop := First (Expressions (Props));
11384                        while Present (Prop) loop
11385                           Analyze_External_Property (Prop);
11386                           Next (Prop);
11387                        end loop;
11388
11389                        --  Property with expression form
11390
11391                        Prop := First (Component_Associations (Props));
11392                        while Present (Prop) loop
11393                           Analyze_External_Property
11394                             (Prop => First (Choices (Prop)),
11395                              Expr => Expression (Prop));
11396
11397                           Next (Prop);
11398                        end loop;
11399
11400                     --  Single property
11401
11402                     else
11403                        Analyze_External_Property (Props);
11404                     end if;
11405
11406                  --  An external state defined without any properties defaults
11407                  --  all properties to True.
11408
11409                  else
11410                     AR_Val := True;
11411                     AW_Val := True;
11412                     ER_Val := True;
11413                     EW_Val := True;
11414                  end if;
11415
11416                  --  Once all external properties have been processed, verify
11417                  --  their mutual interaction. Do not perform the check when
11418                  --  at least one of the properties is illegal as this will
11419                  --  produce a bogus error.
11420
11421                  if Errors = Serious_Errors_Detected then
11422                     Check_External_Properties
11423                       (State, AR_Val, AW_Val, ER_Val, EW_Val);
11424                  end if;
11425               end Analyze_External_Option;
11426
11427               -------------------------------
11428               -- Analyze_External_Property --
11429               -------------------------------
11430
11431               procedure Analyze_External_Property
11432                 (Prop : Node_Id;
11433                  Expr : Node_Id := Empty)
11434               is
11435                  Expr_Val : Boolean;
11436
11437               begin
11438                  --  Check the placement of "others" (if available)
11439
11440                  if Nkind (Prop) = N_Others_Choice then
11441                     if Others_Seen then
11442                        SPARK_Msg_N
11443                          ("only one others choice allowed in option External",
11444                           Prop);
11445                     else
11446                        Others_Seen := True;
11447                     end if;
11448
11449                  elsif Others_Seen then
11450                     SPARK_Msg_N
11451                       ("others must be the last property in option External",
11452                        Prop);
11453
11454                  --  The only remaining legal options are the four predefined
11455                  --  external properties.
11456
11457                  elsif Nkind (Prop) = N_Identifier
11458                    and then Nam_In (Chars (Prop), Name_Async_Readers,
11459                                                   Name_Async_Writers,
11460                                                   Name_Effective_Reads,
11461                                                   Name_Effective_Writes)
11462                  then
11463                     null;
11464
11465                  --  Otherwise the construct is not a valid property
11466
11467                  else
11468                     SPARK_Msg_N ("invalid external state property", Prop);
11469                     return;
11470                  end if;
11471
11472                  --  Ensure that the expression of the external state property
11473                  --  is static Boolean (if applicable) (SPARK RM 7.1.2(5)).
11474
11475                  if Present (Expr) then
11476                     Analyze_And_Resolve (Expr, Standard_Boolean);
11477
11478                     if Is_OK_Static_Expression (Expr) then
11479                        Expr_Val := Is_True (Expr_Value (Expr));
11480                     else
11481                        SPARK_Msg_N
11482                          ("expression of external state property must be "
11483                           & "static", Expr);
11484                        return;
11485                     end if;
11486
11487                  --  The lack of expression defaults the property to True
11488
11489                  else
11490                     Expr_Val := True;
11491                  end if;
11492
11493                  --  Named properties
11494
11495                  if Nkind (Prop) = N_Identifier then
11496                     if Chars (Prop) = Name_Async_Readers then
11497                        Check_Duplicate_Property (Prop, AR_Seen);
11498                        AR_Val := Expr_Val;
11499
11500                     elsif Chars (Prop) = Name_Async_Writers then
11501                        Check_Duplicate_Property (Prop, AW_Seen);
11502                        AW_Val := Expr_Val;
11503
11504                     elsif Chars (Prop) = Name_Effective_Reads then
11505                        Check_Duplicate_Property (Prop, ER_Seen);
11506                        ER_Val := Expr_Val;
11507
11508                     else
11509                        Check_Duplicate_Property (Prop, EW_Seen);
11510                        EW_Val := Expr_Val;
11511                     end if;
11512
11513                  --  The handling of property "others" must take into account
11514                  --  all other named properties that have been encountered so
11515                  --  far. Only those that have not been seen are affected by
11516                  --  "others".
11517
11518                  else
11519                     if not AR_Seen then
11520                        AR_Val := Expr_Val;
11521                     end if;
11522
11523                     if not AW_Seen then
11524                        AW_Val := Expr_Val;
11525                     end if;
11526
11527                     if not ER_Seen then
11528                        ER_Val := Expr_Val;
11529                     end if;
11530
11531                     if not EW_Seen then
11532                        EW_Val := Expr_Val;
11533                     end if;
11534                  end if;
11535               end Analyze_External_Property;
11536
11537               ----------------------------
11538               -- Analyze_Part_Of_Option --
11539               ----------------------------
11540
11541               procedure Analyze_Part_Of_Option (Opt : Node_Id) is
11542                  Encap    : constant Node_Id := Expression (Opt);
11543                  Constits : Elist_Id;
11544                  Encap_Id : Entity_Id;
11545                  Legal    : Boolean;
11546
11547               begin
11548                  Check_Duplicate_Option (Opt, Part_Of_Seen);
11549
11550                  Analyze_Part_Of
11551                    (Indic    => First (Choices (Opt)),
11552                     Item_Id  => State_Id,
11553                     Encap    => Encap,
11554                     Encap_Id => Encap_Id,
11555                     Legal    => Legal);
11556
11557                  --  The Part_Of indicator transforms the abstract state into
11558                  --  a constituent of the encapsulating state or single
11559                  --  concurrent type.
11560
11561                  if Legal then
11562                     pragma Assert (Present (Encap_Id));
11563                     Constits := Part_Of_Constituents (Encap_Id);
11564
11565                     if No (Constits) then
11566                        Constits := New_Elmt_List;
11567                        Set_Part_Of_Constituents (Encap_Id, Constits);
11568                     end if;
11569
11570                     Append_Elmt (State_Id, Constits);
11571                     Set_Encapsulating_State (State_Id, Encap_Id);
11572                  end if;
11573               end Analyze_Part_Of_Option;
11574
11575               ----------------------------
11576               -- Check_Duplicate_Option --
11577               ----------------------------
11578
11579               procedure Check_Duplicate_Option
11580                 (Opt    : Node_Id;
11581                  Status : in out Boolean)
11582               is
11583               begin
11584                  if Status then
11585                     SPARK_Msg_N ("duplicate state option", Opt);
11586                  end if;
11587
11588                  Status := True;
11589               end Check_Duplicate_Option;
11590
11591               ------------------------------
11592               -- Check_Duplicate_Property --
11593               ------------------------------
11594
11595               procedure Check_Duplicate_Property
11596                 (Prop   : Node_Id;
11597                  Status : in out Boolean)
11598               is
11599               begin
11600                  if Status then
11601                     SPARK_Msg_N ("duplicate external property", Prop);
11602                  end if;
11603
11604                  Status := True;
11605               end Check_Duplicate_Property;
11606
11607               -----------------------------
11608               -- Check_Ghost_Synchronous --
11609               -----------------------------
11610
11611               procedure Check_Ghost_Synchronous is
11612               begin
11613                  --  A synchronized abstract state cannot be Ghost and vice
11614                  --  versa (SPARK RM 6.9(19)).
11615
11616                  if Ghost_Seen and Synchronous_Seen then
11617                     SPARK_Msg_N ("synchronized state cannot be ghost", State);
11618                  end if;
11619               end Check_Ghost_Synchronous;
11620
11621               ---------------------------
11622               -- Create_Abstract_State --
11623               ---------------------------
11624
11625               procedure Create_Abstract_State
11626                 (Nam     : Name_Id;
11627                  Decl    : Node_Id;
11628                  Loc     : Source_Ptr;
11629                  Is_Null : Boolean)
11630               is
11631               begin
11632                  --  The abstract state may be semi-declared when the related
11633                  --  package was withed through a limited with clause. In that
11634                  --  case reuse the entity to fully declare the state.
11635
11636                  if Present (Decl) and then Present (Entity (Decl)) then
11637                     State_Id := Entity (Decl);
11638
11639                  --  Otherwise the elaboration of pragma Abstract_State
11640                  --  declares the state.
11641
11642                  else
11643                     State_Id := Make_Defining_Identifier (Loc, Nam);
11644
11645                     if Present (Decl) then
11646                        Set_Entity (Decl, State_Id);
11647                     end if;
11648                  end if;
11649
11650                  --  Null states never come from source
11651
11652                  Set_Comes_From_Source   (State_Id, not Is_Null);
11653                  Set_Parent              (State_Id, State);
11654                  Set_Ekind               (State_Id, E_Abstract_State);
11655                  Set_Etype               (State_Id, Standard_Void_Type);
11656                  Set_Encapsulating_State (State_Id, Empty);
11657
11658                  --  Set the SPARK mode from the current context
11659
11660                  Set_SPARK_Pragma           (State_Id, SPARK_Mode_Pragma);
11661                  Set_SPARK_Pragma_Inherited (State_Id);
11662
11663                  --  An abstract state declared within a Ghost region becomes
11664                  --  Ghost (SPARK RM 6.9(2)).
11665
11666                  if Ghost_Mode > None or else Is_Ghost_Entity (Pack_Id) then
11667                     Set_Is_Ghost_Entity (State_Id);
11668                  end if;
11669
11670                  --  Establish a link between the state declaration and the
11671                  --  abstract state entity. Note that a null state remains as
11672                  --  N_Null and does not carry any linkages.
11673
11674                  if not Is_Null then
11675                     if Present (Decl) then
11676                        Set_Entity (Decl, State_Id);
11677                        Set_Etype  (Decl, Standard_Void_Type);
11678                     end if;
11679
11680                     --  Every non-null state must be defined, nameable and
11681                     --  resolvable.
11682
11683                     Push_Scope (Pack_Id);
11684                     Generate_Definition (State_Id);
11685                     Enter_Name (State_Id);
11686                     Pop_Scope;
11687                  end if;
11688               end Create_Abstract_State;
11689
11690               --  Local variables
11691
11692               Opt     : Node_Id;
11693               Opt_Nam : Node_Id;
11694
11695            --  Start of processing for Analyze_Abstract_State
11696
11697            begin
11698               --  A package with a null abstract state is not allowed to
11699               --  declare additional states.
11700
11701               if Null_Seen then
11702                  SPARK_Msg_NE
11703                    ("package & has null abstract state", State, Pack_Id);
11704
11705               --  Null states appear as internally generated entities
11706
11707               elsif Nkind (State) = N_Null then
11708                  Create_Abstract_State
11709                    (Nam     => New_Internal_Name ('S'),
11710                     Decl    => Empty,
11711                     Loc     => Sloc (State),
11712                     Is_Null => True);
11713                  Null_Seen := True;
11714
11715                  --  Catch a case where a null state appears in a list of
11716                  --  non-null states.
11717
11718                  if Non_Null_Seen then
11719                     SPARK_Msg_NE
11720                       ("package & has non-null abstract state",
11721                        State, Pack_Id);
11722                  end if;
11723
11724               --  Simple state declaration
11725
11726               elsif Nkind (State) = N_Identifier then
11727                  Create_Abstract_State
11728                    (Nam     => Chars (State),
11729                     Decl    => State,
11730                     Loc     => Sloc (State),
11731                     Is_Null => False);
11732                  Non_Null_Seen := True;
11733
11734               --  State declaration with various options. This construct
11735               --  appears as an extension aggregate in the tree.
11736
11737               elsif Nkind (State) = N_Extension_Aggregate then
11738                  if Nkind (Ancestor_Part (State)) = N_Identifier then
11739                     Create_Abstract_State
11740                       (Nam     => Chars (Ancestor_Part (State)),
11741                        Decl    => Ancestor_Part (State),
11742                        Loc     => Sloc (Ancestor_Part (State)),
11743                        Is_Null => False);
11744                     Non_Null_Seen := True;
11745                  else
11746                     SPARK_Msg_N
11747                       ("state name must be an identifier",
11748                        Ancestor_Part (State));
11749                  end if;
11750
11751                  --  Options External, Ghost and Synchronous appear as
11752                  --  expressions.
11753
11754                  Opt := First (Expressions (State));
11755                  while Present (Opt) loop
11756                     if Nkind (Opt) = N_Identifier then
11757
11758                        --  External
11759
11760                        if Chars (Opt) = Name_External then
11761                           Check_Duplicate_Option (Opt, External_Seen);
11762                           Analyze_External_Option (Opt);
11763
11764                        --  Ghost
11765
11766                        elsif Chars (Opt) = Name_Ghost then
11767                           Check_Duplicate_Option (Opt, Ghost_Seen);
11768                           Check_Ghost_Synchronous;
11769
11770                           if Present (State_Id) then
11771                              Set_Is_Ghost_Entity (State_Id);
11772                           end if;
11773
11774                        --  Synchronous
11775
11776                        elsif Chars (Opt) = Name_Synchronous then
11777                           Check_Duplicate_Option (Opt, Synchronous_Seen);
11778                           Check_Ghost_Synchronous;
11779
11780                        --  Option Part_Of without an encapsulating state is
11781                        --  illegal (SPARK RM 7.1.4(9)).
11782
11783                        elsif Chars (Opt) = Name_Part_Of then
11784                           SPARK_Msg_N
11785                             ("indicator Part_Of must denote abstract state, "
11786                              & "single protected type or single task type",
11787                              Opt);
11788
11789                        --  Do not emit an error message when a previous state
11790                        --  declaration with options was not parenthesized as
11791                        --  the option is actually another state declaration.
11792                        --
11793                        --    with Abstract_State
11794                        --      (State_1 with ...,   --  missing parentheses
11795                        --      (State_2 with ...),
11796                        --       State_3)            --  ok state declaration
11797
11798                        elsif Missing_Parentheses then
11799                           null;
11800
11801                        --  Otherwise the option is not allowed. Note that it
11802                        --  is not possible to distinguish between an option
11803                        --  and a state declaration when a previous state with
11804                        --  options not properly parentheses.
11805                        --
11806                        --    with Abstract_State
11807                        --      (State_1 with ...,  --  missing parentheses
11808                        --       State_2);          --  could be an option
11809
11810                        else
11811                           SPARK_Msg_N
11812                             ("simple option not allowed in state declaration",
11813                              Opt);
11814                        end if;
11815
11816                     --  Catch a case where missing parentheses around a state
11817                     --  declaration with options cause a subsequent state
11818                     --  declaration with options to be treated as an option.
11819                     --
11820                     --    with Abstract_State
11821                     --      (State_1 with ...,   --  missing parentheses
11822                     --      (State_2 with ...))
11823
11824                     elsif Nkind (Opt) = N_Extension_Aggregate then
11825                        Missing_Parentheses := True;
11826                        SPARK_Msg_N
11827                          ("state declaration must be parenthesized",
11828                           Ancestor_Part (State));
11829
11830                     --  Otherwise the option is malformed
11831
11832                     else
11833                        SPARK_Msg_N ("malformed option", Opt);
11834                     end if;
11835
11836                     Next (Opt);
11837                  end loop;
11838
11839                  --  Options External and Part_Of appear as component
11840                  --  associations.
11841
11842                  Opt := First (Component_Associations (State));
11843                  while Present (Opt) loop
11844                     Opt_Nam := First (Choices (Opt));
11845
11846                     if Nkind (Opt_Nam) = N_Identifier then
11847                        if Chars (Opt_Nam) = Name_External then
11848                           Analyze_External_Option (Opt);
11849
11850                        elsif Chars (Opt_Nam) = Name_Part_Of then
11851                           Analyze_Part_Of_Option (Opt);
11852
11853                        else
11854                           SPARK_Msg_N ("invalid state option", Opt);
11855                        end if;
11856                     else
11857                        SPARK_Msg_N ("invalid state option", Opt);
11858                     end if;
11859
11860                     Next (Opt);
11861                  end loop;
11862
11863               --  Any other attempt to declare a state is illegal
11864
11865               else
11866                  Malformed_State_Error (State);
11867                  return;
11868               end if;
11869
11870               --  Guard against a junk state. In such cases no entity is
11871               --  generated and the subsequent checks cannot be applied.
11872
11873               if Present (State_Id) then
11874
11875                  --  Verify whether the state does not introduce an illegal
11876                  --  hidden state within a package subject to a null abstract
11877                  --  state.
11878
11879                  Check_No_Hidden_State (State_Id);
11880
11881                  --  Check whether the lack of option Part_Of agrees with the
11882                  --  placement of the abstract state with respect to the state
11883                  --  space.
11884
11885                  if not Part_Of_Seen then
11886                     Check_Missing_Part_Of (State_Id);
11887                  end if;
11888
11889                  --  Associate the state with its related package
11890
11891                  if No (Abstract_States (Pack_Id)) then
11892                     Set_Abstract_States (Pack_Id, New_Elmt_List);
11893                  end if;
11894
11895                  Append_Elmt (State_Id, Abstract_States (Pack_Id));
11896               end if;
11897            end Analyze_Abstract_State;
11898
11899            ---------------------------
11900            -- Malformed_State_Error --
11901            ---------------------------
11902
11903            procedure Malformed_State_Error (State : Node_Id) is
11904            begin
11905               Error_Msg_N ("malformed abstract state declaration", State);
11906
11907               --  An abstract state with a simple option is being declared
11908               --  with "=>" rather than the legal "with". The state appears
11909               --  as a component association.
11910
11911               if Nkind (State) = N_Component_Association then
11912                  Error_Msg_N ("\use WITH to specify simple option", State);
11913               end if;
11914            end Malformed_State_Error;
11915
11916            --  Local variables
11917
11918            Pack_Decl : Node_Id;
11919            Pack_Id   : Entity_Id;
11920            State     : Node_Id;
11921            States    : Node_Id;
11922
11923         --  Start of processing for Abstract_State
11924
11925         begin
11926            GNAT_Pragma;
11927            Check_No_Identifiers;
11928            Check_Arg_Count (1);
11929
11930            Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
11931
11932            --  Ensure the proper placement of the pragma. Abstract states must
11933            --  be associated with a package declaration.
11934
11935            if Nkind_In (Pack_Decl, N_Generic_Package_Declaration,
11936                                    N_Package_Declaration)
11937            then
11938               null;
11939
11940            --  Otherwise the pragma is associated with an illegal construct
11941
11942            else
11943               Pragma_Misplaced;
11944               return;
11945            end if;
11946
11947            Pack_Id := Defining_Entity (Pack_Decl);
11948
11949            --  A pragma that applies to a Ghost entity becomes Ghost for the
11950            --  purposes of legality checks and removal of ignored Ghost code.
11951
11952            Mark_Ghost_Pragma (N, Pack_Id);
11953            Ensure_Aggregate_Form (Get_Argument (N, Pack_Id));
11954
11955            --  Chain the pragma on the contract for completeness
11956
11957            Add_Contract_Item (N, Pack_Id);
11958
11959            --  The legality checks of pragmas Abstract_State, Initializes, and
11960            --  Initial_Condition are affected by the SPARK mode in effect. In
11961            --  addition, these three pragmas are subject to an inherent order:
11962
11963            --    1) Abstract_State
11964            --    2) Initializes
11965            --    3) Initial_Condition
11966
11967            --  Analyze all these pragmas in the order outlined above
11968
11969            Analyze_If_Present (Pragma_SPARK_Mode);
11970            States := Expression (Get_Argument (N, Pack_Id));
11971
11972            --  Multiple non-null abstract states appear as an aggregate
11973
11974            if Nkind (States) = N_Aggregate then
11975               State := First (Expressions (States));
11976               while Present (State) loop
11977                  Analyze_Abstract_State (State, Pack_Id);
11978                  Next (State);
11979               end loop;
11980
11981               --  An abstract state with a simple option is being illegaly
11982               --  declared with "=>" rather than "with". In this case the
11983               --  state declaration appears as a component association.
11984
11985               if Present (Component_Associations (States)) then
11986                  State := First (Component_Associations (States));
11987                  while Present (State) loop
11988                     Malformed_State_Error (State);
11989                     Next (State);
11990                  end loop;
11991               end if;
11992
11993            --  Various forms of a single abstract state. Note that these may
11994            --  include malformed state declarations.
11995
11996            else
11997               Analyze_Abstract_State (States, Pack_Id);
11998            end if;
11999
12000            Analyze_If_Present (Pragma_Initializes);
12001            Analyze_If_Present (Pragma_Initial_Condition);
12002         end Abstract_State;
12003
12004         ------------
12005         -- Ada_83 --
12006         ------------
12007
12008         --  pragma Ada_83;
12009
12010         --  Note: this pragma also has some specific processing in Par.Prag
12011         --  because we want to set the Ada version mode during parsing.
12012
12013         when Pragma_Ada_83 =>
12014            GNAT_Pragma;
12015            Check_Arg_Count (0);
12016
12017            --  We really should check unconditionally for proper configuration
12018            --  pragma placement, since we really don't want mixed Ada modes
12019            --  within a single unit, and the GNAT reference manual has always
12020            --  said this was a configuration pragma, but we did not check and
12021            --  are hesitant to add the check now.
12022
12023            --  However, we really cannot tolerate mixing Ada 2005 or Ada 2012
12024            --  with Ada 83 or Ada 95, so we must check if we are in Ada 2005
12025            --  or Ada 2012 mode.
12026
12027            if Ada_Version >= Ada_2005 then
12028               Check_Valid_Configuration_Pragma;
12029            end if;
12030
12031            --  Now set Ada 83 mode
12032
12033            if Latest_Ada_Only then
12034               Error_Pragma ("??pragma% ignored");
12035            else
12036               Ada_Version          := Ada_83;
12037               Ada_Version_Explicit := Ada_83;
12038               Ada_Version_Pragma   := N;
12039            end if;
12040
12041         ------------
12042         -- Ada_95 --
12043         ------------
12044
12045         --  pragma Ada_95;
12046
12047         --  Note: this pragma also has some specific processing in Par.Prag
12048         --  because we want to set the Ada 83 version mode during parsing.
12049
12050         when Pragma_Ada_95 =>
12051            GNAT_Pragma;
12052            Check_Arg_Count (0);
12053
12054            --  We really should check unconditionally for proper configuration
12055            --  pragma placement, since we really don't want mixed Ada modes
12056            --  within a single unit, and the GNAT reference manual has always
12057            --  said this was a configuration pragma, but we did not check and
12058            --  are hesitant to add the check now.
12059
12060            --  However, we really cannot tolerate mixing Ada 2005 with Ada 83
12061            --  or Ada 95, so we must check if we are in Ada 2005 mode.
12062
12063            if Ada_Version >= Ada_2005 then
12064               Check_Valid_Configuration_Pragma;
12065            end if;
12066
12067            --  Now set Ada 95 mode
12068
12069            if Latest_Ada_Only then
12070               Error_Pragma ("??pragma% ignored");
12071            else
12072               Ada_Version          := Ada_95;
12073               Ada_Version_Explicit := Ada_95;
12074               Ada_Version_Pragma   := N;
12075            end if;
12076
12077         ---------------------
12078         -- Ada_05/Ada_2005 --
12079         ---------------------
12080
12081         --  pragma Ada_05;
12082         --  pragma Ada_05 (LOCAL_NAME);
12083
12084         --  pragma Ada_2005;
12085         --  pragma Ada_2005 (LOCAL_NAME):
12086
12087         --  Note: these pragmas also have some specific processing in Par.Prag
12088         --  because we want to set the Ada 2005 version mode during parsing.
12089
12090         --  The one argument form is used for managing the transition from
12091         --  Ada 95 to Ada 2005 in the run-time library. If an entity is marked
12092         --  as Ada_2005 only, then referencing the entity in Ada_83 or Ada_95
12093         --  mode will generate a warning. In addition, in Ada_83 or Ada_95
12094         --  mode, a preference rule is established which does not choose
12095         --  such an entity unless it is unambiguously specified. This avoids
12096         --  extra subprograms marked this way from generating ambiguities in
12097         --  otherwise legal pre-Ada_2005 programs. The one argument form is
12098         --  intended for exclusive use in the GNAT run-time library.
12099
12100         when Pragma_Ada_05
12101            | Pragma_Ada_2005
12102         =>
12103         declare
12104            E_Id : Node_Id;
12105
12106         begin
12107            GNAT_Pragma;
12108
12109            if Arg_Count = 1 then
12110               Check_Arg_Is_Local_Name (Arg1);
12111               E_Id := Get_Pragma_Arg (Arg1);
12112
12113               if Etype (E_Id) = Any_Type then
12114                  return;
12115               end if;
12116
12117               Set_Is_Ada_2005_Only (Entity (E_Id));
12118               Record_Rep_Item (Entity (E_Id), N);
12119
12120            else
12121               Check_Arg_Count (0);
12122
12123               --  For Ada_2005 we unconditionally enforce the documented
12124               --  configuration pragma placement, since we do not want to
12125               --  tolerate mixed modes in a unit involving Ada 2005. That
12126               --  would cause real difficulties for those cases where there
12127               --  are incompatibilities between Ada 95 and Ada 2005.
12128
12129               Check_Valid_Configuration_Pragma;
12130
12131               --  Now set appropriate Ada mode
12132
12133               if Latest_Ada_Only then
12134                  Error_Pragma ("??pragma% ignored");
12135               else
12136                  Ada_Version          := Ada_2005;
12137                  Ada_Version_Explicit := Ada_2005;
12138                  Ada_Version_Pragma   := N;
12139               end if;
12140            end if;
12141         end;
12142
12143         ---------------------
12144         -- Ada_12/Ada_2012 --
12145         ---------------------
12146
12147         --  pragma Ada_12;
12148         --  pragma Ada_12 (LOCAL_NAME);
12149
12150         --  pragma Ada_2012;
12151         --  pragma Ada_2012 (LOCAL_NAME):
12152
12153         --  Note: these pragmas also have some specific processing in Par.Prag
12154         --  because we want to set the Ada 2012 version mode during parsing.
12155
12156         --  The one argument form is used for managing the transition from Ada
12157         --  2005 to Ada 2012 in the run-time library. If an entity is marked
12158         --  as Ada_2012 only, then referencing the entity in any pre-Ada_2012
12159         --  mode will generate a warning. In addition, in any pre-Ada_2012
12160         --  mode, a preference rule is established which does not choose
12161         --  such an entity unless it is unambiguously specified. This avoids
12162         --  extra subprograms marked this way from generating ambiguities in
12163         --  otherwise legal pre-Ada_2012 programs. The one argument form is
12164         --  intended for exclusive use in the GNAT run-time library.
12165
12166         when Pragma_Ada_12
12167            | Pragma_Ada_2012
12168         =>
12169         declare
12170            E_Id : Node_Id;
12171
12172         begin
12173            GNAT_Pragma;
12174
12175            if Arg_Count = 1 then
12176               Check_Arg_Is_Local_Name (Arg1);
12177               E_Id := Get_Pragma_Arg (Arg1);
12178
12179               if Etype (E_Id) = Any_Type then
12180                  return;
12181               end if;
12182
12183               Set_Is_Ada_2012_Only (Entity (E_Id));
12184               Record_Rep_Item (Entity (E_Id), N);
12185
12186            else
12187               Check_Arg_Count (0);
12188
12189               --  For Ada_2012 we unconditionally enforce the documented
12190               --  configuration pragma placement, since we do not want to
12191               --  tolerate mixed modes in a unit involving Ada 2012. That
12192               --  would cause real difficulties for those cases where there
12193               --  are incompatibilities between Ada 95 and Ada 2012. We could
12194               --  allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
12195
12196               Check_Valid_Configuration_Pragma;
12197
12198               --  Now set appropriate Ada mode
12199
12200               Ada_Version          := Ada_2012;
12201               Ada_Version_Explicit := Ada_2012;
12202               Ada_Version_Pragma   := N;
12203            end if;
12204         end;
12205
12206         --------------
12207         -- Ada_2020 --
12208         --------------
12209
12210         --  pragma Ada_2020;
12211
12212         --  Note: this pragma also has some specific processing in Par.Prag
12213         --  because we want to set the Ada 2020 version mode during parsing.
12214
12215         when Pragma_Ada_2020 =>
12216            GNAT_Pragma;
12217
12218            Check_Arg_Count (0);
12219
12220            Check_Valid_Configuration_Pragma;
12221
12222            --  Now set appropriate Ada mode
12223
12224            Ada_Version          := Ada_2020;
12225            Ada_Version_Explicit := Ada_2020;
12226            Ada_Version_Pragma   := N;
12227
12228         ----------------------
12229         -- All_Calls_Remote --
12230         ----------------------
12231
12232         --  pragma All_Calls_Remote [(library_package_NAME)];
12233
12234         when Pragma_All_Calls_Remote => All_Calls_Remote : declare
12235            Lib_Entity : Entity_Id;
12236
12237         begin
12238            Check_Ada_83_Warning;
12239            Check_Valid_Library_Unit_Pragma;
12240
12241            if Nkind (N) = N_Null_Statement then
12242               return;
12243            end if;
12244
12245            Lib_Entity := Find_Lib_Unit_Name;
12246
12247            --  A pragma that applies to a Ghost entity becomes Ghost for the
12248            --  purposes of legality checks and removal of ignored Ghost code.
12249
12250            Mark_Ghost_Pragma (N, Lib_Entity);
12251
12252            --  This pragma should only apply to a RCI unit (RM E.2.3(23))
12253
12254            if Present (Lib_Entity) and then not Debug_Flag_U then
12255               if not Is_Remote_Call_Interface (Lib_Entity) then
12256                  Error_Pragma ("pragma% only apply to rci unit");
12257
12258               --  Set flag for entity of the library unit
12259
12260               else
12261                  Set_Has_All_Calls_Remote (Lib_Entity);
12262               end if;
12263            end if;
12264         end All_Calls_Remote;
12265
12266         ---------------------------
12267         -- Allow_Integer_Address --
12268         ---------------------------
12269
12270         --  pragma Allow_Integer_Address;
12271
12272         when Pragma_Allow_Integer_Address =>
12273            GNAT_Pragma;
12274            Check_Valid_Configuration_Pragma;
12275            Check_Arg_Count (0);
12276
12277            --  If Address is a private type, then set the flag to allow
12278            --  integer address values. If Address is not private, then this
12279            --  pragma has no purpose, so it is simply ignored. Not clear if
12280            --  there are any such targets now.
12281
12282            if Opt.Address_Is_Private then
12283               Opt.Allow_Integer_Address := True;
12284            end if;
12285
12286         --------------
12287         -- Annotate --
12288         --------------
12289
12290         --  pragma Annotate
12291         --    (IDENTIFIER [, IDENTIFIER {, ARG}] [,Entity => local_NAME]);
12292         --  ARG ::= NAME | EXPRESSION
12293
12294         --  The first two arguments are by convention intended to refer to an
12295         --  external tool and a tool-specific function. These arguments are
12296         --  not analyzed.
12297
12298         when Pragma_Annotate => Annotate : declare
12299            Arg     : Node_Id;
12300            Expr    : Node_Id;
12301            Nam_Arg : Node_Id;
12302
12303         begin
12304            GNAT_Pragma;
12305            Check_At_Least_N_Arguments (1);
12306
12307            Nam_Arg := Last (Pragma_Argument_Associations (N));
12308
12309            --  Determine whether the last argument is "Entity => local_NAME"
12310            --  and if it is, perform the required semantic checks. Remove the
12311            --  argument from further processing.
12312
12313            if Nkind (Nam_Arg) = N_Pragma_Argument_Association
12314              and then Chars (Nam_Arg) = Name_Entity
12315            then
12316               Check_Arg_Is_Local_Name (Nam_Arg);
12317               Arg_Count := Arg_Count - 1;
12318
12319               --  A pragma that applies to a Ghost entity becomes Ghost for
12320               --  the purposes of legality checks and removal of ignored Ghost
12321               --  code.
12322
12323               if Is_Entity_Name (Get_Pragma_Arg (Nam_Arg))
12324                 and then Present (Entity (Get_Pragma_Arg (Nam_Arg)))
12325               then
12326                  Mark_Ghost_Pragma (N, Entity (Get_Pragma_Arg (Nam_Arg)));
12327               end if;
12328
12329               --  Not allowed in compiler units (bootstrap issues)
12330
12331               Check_Compiler_Unit ("Entity for pragma Annotate", N);
12332            end if;
12333
12334            --  Continue the processing with last argument removed for now
12335
12336            Check_Arg_Is_Identifier (Arg1);
12337            Check_No_Identifiers;
12338            Store_Note (N);
12339
12340            --  The second parameter is optional, it is never analyzed
12341
12342            if No (Arg2) then
12343               null;
12344
12345            --  Otherwise there is a second parameter
12346
12347            else
12348               --  The second parameter must be an identifier
12349
12350               Check_Arg_Is_Identifier (Arg2);
12351
12352               --  Process the remaining parameters (if any)
12353
12354               Arg := Next (Arg2);
12355               while Present (Arg) loop
12356                  Expr := Get_Pragma_Arg (Arg);
12357                  Analyze (Expr);
12358
12359                  if Is_Entity_Name (Expr) then
12360                     null;
12361
12362                  --  For string literals, we assume Standard_String as the
12363                  --  type, unless the string contains wide or wide_wide
12364                  --  characters.
12365
12366                  elsif Nkind (Expr) = N_String_Literal then
12367                     if Has_Wide_Wide_Character (Expr) then
12368                        Resolve (Expr, Standard_Wide_Wide_String);
12369                     elsif Has_Wide_Character (Expr) then
12370                        Resolve (Expr, Standard_Wide_String);
12371                     else
12372                        Resolve (Expr, Standard_String);
12373                     end if;
12374
12375                  elsif Is_Overloaded (Expr) then
12376                     Error_Pragma_Arg ("ambiguous argument for pragma%", Expr);
12377
12378                  else
12379                     Resolve (Expr);
12380                  end if;
12381
12382                  Next (Arg);
12383               end loop;
12384            end if;
12385         end Annotate;
12386
12387         -------------------------------------------------
12388         -- Assert/Assert_And_Cut/Assume/Loop_Invariant --
12389         -------------------------------------------------
12390
12391         --  pragma Assert
12392         --    (   [Check => ]  Boolean_EXPRESSION
12393         --     [, [Message =>] Static_String_EXPRESSION]);
12394
12395         --  pragma Assert_And_Cut
12396         --    (   [Check => ]  Boolean_EXPRESSION
12397         --     [, [Message =>] Static_String_EXPRESSION]);
12398
12399         --  pragma Assume
12400         --    (   [Check => ]  Boolean_EXPRESSION
12401         --     [, [Message =>] Static_String_EXPRESSION]);
12402
12403         --  pragma Loop_Invariant
12404         --    (   [Check => ]  Boolean_EXPRESSION
12405         --     [, [Message =>] Static_String_EXPRESSION]);
12406
12407         when Pragma_Assert
12408            | Pragma_Assert_And_Cut
12409            | Pragma_Assume
12410            | Pragma_Loop_Invariant
12411         =>
12412         Assert : declare
12413            function Contains_Loop_Entry (Expr : Node_Id) return Boolean;
12414            --  Determine whether expression Expr contains a Loop_Entry
12415            --  attribute reference.
12416
12417            -------------------------
12418            -- Contains_Loop_Entry --
12419            -------------------------
12420
12421            function Contains_Loop_Entry (Expr : Node_Id) return Boolean is
12422               Has_Loop_Entry : Boolean := False;
12423
12424               function Process (N : Node_Id) return Traverse_Result;
12425               --  Process function for traversal to look for Loop_Entry
12426
12427               -------------
12428               -- Process --
12429               -------------
12430
12431               function Process (N : Node_Id) return Traverse_Result is
12432               begin
12433                  if Nkind (N) = N_Attribute_Reference
12434                    and then Attribute_Name (N) = Name_Loop_Entry
12435                  then
12436                     Has_Loop_Entry := True;
12437                     return Abandon;
12438                  else
12439                     return OK;
12440                  end if;
12441               end Process;
12442
12443               procedure Traverse is new Traverse_Proc (Process);
12444
12445            --  Start of processing for Contains_Loop_Entry
12446
12447            begin
12448               Traverse (Expr);
12449               return Has_Loop_Entry;
12450            end Contains_Loop_Entry;
12451
12452            --  Local variables
12453
12454            Expr     : Node_Id;
12455            New_Args : List_Id;
12456
12457         --  Start of processing for Assert
12458
12459         begin
12460            --  Assert is an Ada 2005 RM-defined pragma
12461
12462            if Prag_Id = Pragma_Assert then
12463               Ada_2005_Pragma;
12464
12465            --  The remaining ones are GNAT pragmas
12466
12467            else
12468               GNAT_Pragma;
12469            end if;
12470
12471            Check_At_Least_N_Arguments (1);
12472            Check_At_Most_N_Arguments (2);
12473            Check_Arg_Order ((Name_Check, Name_Message));
12474            Check_Optional_Identifier (Arg1, Name_Check);
12475            Expr := Get_Pragma_Arg (Arg1);
12476
12477            --  Special processing for Loop_Invariant, Loop_Variant or for
12478            --  other cases where a Loop_Entry attribute is present. If the
12479            --  assertion pragma contains attribute Loop_Entry, ensure that
12480            --  the related pragma is within a loop.
12481
12482            if        Prag_Id = Pragma_Loop_Invariant
12483              or else Prag_Id = Pragma_Loop_Variant
12484              or else Contains_Loop_Entry (Expr)
12485            then
12486               Check_Loop_Pragma_Placement;
12487
12488               --  Perform preanalysis to deal with embedded Loop_Entry
12489               --  attributes.
12490
12491               Preanalyze_Assert_Expression (Expr, Any_Boolean);
12492            end if;
12493
12494            --  Implement Assert[_And_Cut]/Assume/Loop_Invariant by generating
12495            --  a corresponding Check pragma:
12496
12497            --    pragma Check (name, condition [, msg]);
12498
12499            --  Where name is the identifier matching the pragma name. So
12500            --  rewrite pragma in this manner, transfer the message argument
12501            --  if present, and analyze the result
12502
12503            --  Note: When dealing with a semantically analyzed tree, the
12504            --  information that a Check node N corresponds to a source Assert,
12505            --  Assume, or Assert_And_Cut pragma can be retrieved from the
12506            --  pragma kind of Original_Node(N).
12507
12508            New_Args := New_List (
12509              Make_Pragma_Argument_Association (Loc,
12510                Expression => Make_Identifier (Loc, Pname)),
12511              Make_Pragma_Argument_Association (Sloc (Expr),
12512                Expression => Expr));
12513
12514            if Arg_Count > 1 then
12515               Check_Optional_Identifier (Arg2, Name_Message);
12516
12517               --  Provide semantic annnotations for optional argument, for
12518               --  ASIS use, before rewriting.
12519
12520               Preanalyze_And_Resolve (Expression (Arg2), Standard_String);
12521               Append_To (New_Args, New_Copy_Tree (Arg2));
12522            end if;
12523
12524            --  Rewrite as Check pragma
12525
12526            Rewrite (N,
12527              Make_Pragma (Loc,
12528                Chars                        => Name_Check,
12529                Pragma_Argument_Associations => New_Args));
12530
12531            Analyze (N);
12532         end Assert;
12533
12534         ----------------------
12535         -- Assertion_Policy --
12536         ----------------------
12537
12538         --  pragma Assertion_Policy (POLICY_IDENTIFIER);
12539
12540         --  The following form is Ada 2012 only, but we allow it in all modes
12541
12542         --  Pragma Assertion_Policy (
12543         --      ASSERTION_KIND => POLICY_IDENTIFIER
12544         --   {, ASSERTION_KIND => POLICY_IDENTIFIER});
12545
12546         --  ASSERTION_KIND ::= RM_ASSERTION_KIND | ID_ASSERTION_KIND
12547
12548         --  RM_ASSERTION_KIND ::= Assert               |
12549         --                        Static_Predicate     |
12550         --                        Dynamic_Predicate    |
12551         --                        Pre                  |
12552         --                        Pre'Class            |
12553         --                        Post                 |
12554         --                        Post'Class           |
12555         --                        Type_Invariant       |
12556         --                        Type_Invariant'Class
12557
12558         --  ID_ASSERTION_KIND ::= Assert_And_Cut            |
12559         --                        Assume                    |
12560         --                        Contract_Cases            |
12561         --                        Debug                     |
12562         --                        Default_Initial_Condition |
12563         --                        Ghost                     |
12564         --                        Initial_Condition         |
12565         --                        Loop_Invariant            |
12566         --                        Loop_Variant              |
12567         --                        Postcondition             |
12568         --                        Precondition              |
12569         --                        Predicate                 |
12570         --                        Refined_Post              |
12571         --                        Statement_Assertions
12572
12573         --  Note: The RM_ASSERTION_KIND list is language-defined, and the
12574         --  ID_ASSERTION_KIND list contains implementation-defined additions
12575         --  recognized by GNAT. The effect is to control the behavior of
12576         --  identically named aspects and pragmas, depending on the specified
12577         --  policy identifier:
12578
12579         --  POLICY_IDENTIFIER ::= Check | Disable | Ignore | Suppressible
12580
12581         --  Note: Check and Ignore are language-defined. Disable is a GNAT
12582         --  implementation-defined addition that results in totally ignoring
12583         --  the corresponding assertion. If Disable is specified, then the
12584         --  argument of the assertion is not even analyzed. This is useful
12585         --  when the aspect/pragma argument references entities in a with'ed
12586         --  package that is replaced by a dummy package in the final build.
12587
12588         --  Note: the attribute forms Pre'Class, Post'Class, Invariant'Class,
12589         --  and Type_Invariant'Class were recognized by the parser and
12590         --  transformed into references to the special internal identifiers
12591         --  _Pre, _Post, _Invariant, and _Type_Invariant, so no special
12592         --  processing is required here.
12593
12594         when Pragma_Assertion_Policy => Assertion_Policy : declare
12595            procedure Resolve_Suppressible (Policy : Node_Id);
12596            --  Converts the assertion policy 'Suppressible' to either Check or
12597            --  Ignore based on whether checks are suppressed via -gnatp.
12598
12599            --------------------------
12600            -- Resolve_Suppressible --
12601            --------------------------
12602
12603            procedure Resolve_Suppressible (Policy : Node_Id) is
12604               Arg : constant Node_Id := Get_Pragma_Arg (Policy);
12605               Nam : Name_Id;
12606
12607            begin
12608               --  Transform policy argument Suppressible into either Ignore or
12609               --  Check depending on whether checks are enabled or suppressed.
12610
12611               if Chars (Arg) = Name_Suppressible then
12612                  if Suppress_Checks then
12613                     Nam := Name_Ignore;
12614                  else
12615                     Nam := Name_Check;
12616                  end if;
12617
12618                  Rewrite (Arg, Make_Identifier (Sloc (Arg), Nam));
12619               end if;
12620            end Resolve_Suppressible;
12621
12622            --  Local variables
12623
12624            Arg    : Node_Id;
12625            Kind   : Name_Id;
12626            LocP   : Source_Ptr;
12627            Policy : Node_Id;
12628
12629         begin
12630            Ada_2005_Pragma;
12631
12632            --  This can always appear as a configuration pragma
12633
12634            if Is_Configuration_Pragma then
12635               null;
12636
12637            --  It can also appear in a declarative part or package spec in Ada
12638            --  2012 mode. We allow this in other modes, but in that case we
12639            --  consider that we have an Ada 2012 pragma on our hands.
12640
12641            else
12642               Check_Is_In_Decl_Part_Or_Package_Spec;
12643               Ada_2012_Pragma;
12644            end if;
12645
12646            --  One argument case with no identifier (first form above)
12647
12648            if Arg_Count = 1
12649              and then (Nkind (Arg1) /= N_Pragma_Argument_Association
12650                         or else Chars (Arg1) = No_Name)
12651            then
12652               Check_Arg_Is_One_Of (Arg1,
12653                 Name_Check, Name_Disable, Name_Ignore, Name_Suppressible);
12654
12655               Resolve_Suppressible (Arg1);
12656
12657               --  Treat one argument Assertion_Policy as equivalent to:
12658
12659               --    pragma Check_Policy (Assertion, policy)
12660
12661               --  So rewrite pragma in that manner and link on to the chain
12662               --  of Check_Policy pragmas, marking the pragma as analyzed.
12663
12664               Policy := Get_Pragma_Arg (Arg1);
12665
12666               Rewrite (N,
12667                 Make_Pragma (Loc,
12668                   Chars                        => Name_Check_Policy,
12669                   Pragma_Argument_Associations => New_List (
12670                     Make_Pragma_Argument_Association (Loc,
12671                       Expression => Make_Identifier (Loc, Name_Assertion)),
12672
12673                     Make_Pragma_Argument_Association (Loc,
12674                       Expression =>
12675                         Make_Identifier (Sloc (Policy), Chars (Policy))))));
12676               Analyze (N);
12677
12678            --  Here if we have two or more arguments
12679
12680            else
12681               Check_At_Least_N_Arguments (1);
12682               Ada_2012_Pragma;
12683
12684               --  Loop through arguments
12685
12686               Arg := Arg1;
12687               while Present (Arg) loop
12688                  LocP := Sloc (Arg);
12689
12690                  --  Kind must be specified
12691
12692                  if Nkind (Arg) /= N_Pragma_Argument_Association
12693                    or else Chars (Arg) = No_Name
12694                  then
12695                     Error_Pragma_Arg
12696                       ("missing assertion kind for pragma%", Arg);
12697                  end if;
12698
12699                  --  Check Kind and Policy have allowed forms
12700
12701                  Kind   := Chars (Arg);
12702                  Policy := Get_Pragma_Arg (Arg);
12703
12704                  if not Is_Valid_Assertion_Kind (Kind) then
12705                     Error_Pragma_Arg
12706                       ("invalid assertion kind for pragma%", Arg);
12707                  end if;
12708
12709                  Check_Arg_Is_One_Of (Arg,
12710                    Name_Check, Name_Disable, Name_Ignore, Name_Suppressible);
12711
12712                  Resolve_Suppressible (Arg);
12713
12714                  if Kind = Name_Ghost then
12715
12716                     --  The Ghost policy must be either Check or Ignore
12717                     --  (SPARK RM 6.9(6)).
12718
12719                     if not Nam_In (Chars (Policy), Name_Check,
12720                                                    Name_Ignore)
12721                     then
12722                        Error_Pragma_Arg
12723                          ("argument of pragma % Ghost must be Check or "
12724                           & "Ignore", Policy);
12725                     end if;
12726
12727                     --  Pragma Assertion_Policy specifying a Ghost policy
12728                     --  cannot occur within a Ghost subprogram or package
12729                     --  (SPARK RM 6.9(14)).
12730
12731                     if Ghost_Mode > None then
12732                        Error_Pragma
12733                          ("pragma % cannot appear within ghost subprogram or "
12734                           & "package");
12735                     end if;
12736                  end if;
12737
12738                  --  Rewrite the Assertion_Policy pragma as a series of
12739                  --  Check_Policy pragmas of the form:
12740
12741                  --    Check_Policy (Kind, Policy);
12742
12743                  --  Note: the insertion of the pragmas cannot be done with
12744                  --  Insert_Action because in the configuration case, there
12745                  --  are no scopes on the scope stack and the mechanism will
12746                  --  fail.
12747
12748                  Insert_Before_And_Analyze (N,
12749                    Make_Pragma (LocP,
12750                      Chars                        => Name_Check_Policy,
12751                      Pragma_Argument_Associations => New_List (
12752                         Make_Pragma_Argument_Association (LocP,
12753                           Expression => Make_Identifier (LocP, Kind)),
12754                         Make_Pragma_Argument_Association (LocP,
12755                           Expression => Policy))));
12756
12757                  Arg := Next (Arg);
12758               end loop;
12759
12760               --  Rewrite the Assertion_Policy pragma as null since we have
12761               --  now inserted all the equivalent Check pragmas.
12762
12763               Rewrite (N, Make_Null_Statement (Loc));
12764               Analyze (N);
12765            end if;
12766         end Assertion_Policy;
12767
12768         ------------------------------
12769         -- Assume_No_Invalid_Values --
12770         ------------------------------
12771
12772         --  pragma Assume_No_Invalid_Values (On | Off);
12773
12774         when Pragma_Assume_No_Invalid_Values =>
12775            GNAT_Pragma;
12776            Check_Valid_Configuration_Pragma;
12777            Check_Arg_Count (1);
12778            Check_No_Identifiers;
12779            Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
12780
12781            if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
12782               Assume_No_Invalid_Values := True;
12783            else
12784               Assume_No_Invalid_Values := False;
12785            end if;
12786
12787         --------------------------
12788         -- Attribute_Definition --
12789         --------------------------
12790
12791         --  pragma Attribute_Definition
12792         --    ([Attribute  =>] ATTRIBUTE_DESIGNATOR,
12793         --     [Entity     =>] LOCAL_NAME,
12794         --     [Expression =>] EXPRESSION | NAME);
12795
12796         when Pragma_Attribute_Definition => Attribute_Definition : declare
12797            Attribute_Designator : constant Node_Id := Get_Pragma_Arg (Arg1);
12798            Aname                : Name_Id;
12799
12800         begin
12801            GNAT_Pragma;
12802            Check_Arg_Count (3);
12803            Check_Optional_Identifier (Arg1, "attribute");
12804            Check_Optional_Identifier (Arg2, "entity");
12805            Check_Optional_Identifier (Arg3, "expression");
12806
12807            if Nkind (Attribute_Designator) /= N_Identifier then
12808               Error_Msg_N ("attribute name expected", Attribute_Designator);
12809               return;
12810            end if;
12811
12812            Check_Arg_Is_Local_Name (Arg2);
12813
12814            --  If the attribute is not recognized, then issue a warning (not
12815            --  an error), and ignore the pragma.
12816
12817            Aname := Chars (Attribute_Designator);
12818
12819            if not Is_Attribute_Name (Aname) then
12820               Bad_Attribute (Attribute_Designator, Aname, Warn => True);
12821               return;
12822            end if;
12823
12824            --  Otherwise, rewrite the pragma as an attribute definition clause
12825
12826            Rewrite (N,
12827              Make_Attribute_Definition_Clause (Loc,
12828                Name       => Get_Pragma_Arg (Arg2),
12829                Chars      => Aname,
12830                Expression => Get_Pragma_Arg (Arg3)));
12831            Analyze (N);
12832         end Attribute_Definition;
12833
12834         ------------------------------------------------------------------
12835         -- Async_Readers/Async_Writers/Effective_Reads/Effective_Writes --
12836         ------------------------------------------------------------------
12837
12838         --  pragma Asynch_Readers   [ (boolean_EXPRESSION) ];
12839         --  pragma Asynch_Writers   [ (boolean_EXPRESSION) ];
12840         --  pragma Effective_Reads  [ (boolean_EXPRESSION) ];
12841         --  pragma Effective_Writes [ (boolean_EXPRESSION) ];
12842
12843         when Pragma_Async_Readers
12844            | Pragma_Async_Writers
12845            | Pragma_Effective_Reads
12846            | Pragma_Effective_Writes
12847         =>
12848         Async_Effective : declare
12849            Obj_Decl : Node_Id;
12850            Obj_Id   : Entity_Id;
12851
12852         begin
12853            GNAT_Pragma;
12854            Check_No_Identifiers;
12855            Check_At_Most_N_Arguments  (1);
12856
12857            Obj_Decl := Find_Related_Context (N, Do_Checks => True);
12858
12859            --  Object declaration
12860
12861            if Nkind (Obj_Decl) = N_Object_Declaration then
12862               null;
12863
12864            --  Otherwise the pragma is associated with an illegal construact
12865
12866            else
12867               Pragma_Misplaced;
12868               return;
12869            end if;
12870
12871            Obj_Id := Defining_Entity (Obj_Decl);
12872
12873            --  Perform minimal verification to ensure that the argument is at
12874            --  least a variable. Subsequent finer grained checks will be done
12875            --  at the end of the declarative region the contains the pragma.
12876
12877            if Ekind (Obj_Id) = E_Variable then
12878
12879               --  A pragma that applies to a Ghost entity becomes Ghost for
12880               --  the purposes of legality checks and removal of ignored Ghost
12881               --  code.
12882
12883               Mark_Ghost_Pragma (N, Obj_Id);
12884
12885               --  Chain the pragma on the contract for further processing by
12886               --  Analyze_External_Property_In_Decl_Part.
12887
12888               Add_Contract_Item (N, Obj_Id);
12889
12890               --  Analyze the Boolean expression (if any)
12891
12892               if Present (Arg1) then
12893                  Check_Static_Boolean_Expression (Get_Pragma_Arg (Arg1));
12894               end if;
12895
12896            --  Otherwise the external property applies to a constant
12897
12898            else
12899               Error_Pragma ("pragma % must apply to a volatile object");
12900            end if;
12901         end Async_Effective;
12902
12903         ------------------
12904         -- Asynchronous --
12905         ------------------
12906
12907         --  pragma Asynchronous (LOCAL_NAME);
12908
12909         when Pragma_Asynchronous => Asynchronous : declare
12910            C_Ent  : Entity_Id;
12911            Decl   : Node_Id;
12912            Formal : Entity_Id;
12913            L      : List_Id;
12914            Nm     : Entity_Id;
12915            S      : Node_Id;
12916
12917            procedure Process_Async_Pragma;
12918            --  Common processing for procedure and access-to-procedure case
12919
12920            --------------------------
12921            -- Process_Async_Pragma --
12922            --------------------------
12923
12924            procedure Process_Async_Pragma is
12925            begin
12926               if No (L) then
12927                  Set_Is_Asynchronous (Nm);
12928                  return;
12929               end if;
12930
12931               --  The formals should be of mode IN (RM E.4.1(6))
12932
12933               S := First (L);
12934               while Present (S) loop
12935                  Formal := Defining_Identifier (S);
12936
12937                  if Nkind (Formal) = N_Defining_Identifier
12938                    and then Ekind (Formal) /= E_In_Parameter
12939                  then
12940                     Error_Pragma_Arg
12941                       ("pragma% procedure can only have IN parameter",
12942                        Arg1);
12943                  end if;
12944
12945                  Next (S);
12946               end loop;
12947
12948               Set_Is_Asynchronous (Nm);
12949            end Process_Async_Pragma;
12950
12951         --  Start of processing for pragma Asynchronous
12952
12953         begin
12954            Check_Ada_83_Warning;
12955            Check_No_Identifiers;
12956            Check_Arg_Count (1);
12957            Check_Arg_Is_Local_Name (Arg1);
12958
12959            if Debug_Flag_U then
12960               return;
12961            end if;
12962
12963            C_Ent := Cunit_Entity (Current_Sem_Unit);
12964            Analyze (Get_Pragma_Arg (Arg1));
12965            Nm := Entity (Get_Pragma_Arg (Arg1));
12966
12967            --  A pragma that applies to a Ghost entity becomes Ghost for the
12968            --  purposes of legality checks and removal of ignored Ghost code.
12969
12970            Mark_Ghost_Pragma (N, Nm);
12971
12972            if not Is_Remote_Call_Interface (C_Ent)
12973              and then not Is_Remote_Types (C_Ent)
12974            then
12975               --  This pragma should only appear in an RCI or Remote Types
12976               --  unit (RM E.4.1(4)).
12977
12978               Error_Pragma
12979                 ("pragma% not in Remote_Call_Interface or Remote_Types unit");
12980            end if;
12981
12982            if Ekind (Nm) = E_Procedure
12983              and then Nkind (Parent (Nm)) = N_Procedure_Specification
12984            then
12985               if not Is_Remote_Call_Interface (Nm) then
12986                  Error_Pragma_Arg
12987                    ("pragma% cannot be applied on non-remote procedure",
12988                     Arg1);
12989               end if;
12990
12991               L := Parameter_Specifications (Parent (Nm));
12992               Process_Async_Pragma;
12993               return;
12994
12995            elsif Ekind (Nm) = E_Function then
12996               Error_Pragma_Arg
12997                 ("pragma% cannot be applied to function", Arg1);
12998
12999            elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
13000               if Is_Record_Type (Nm) then
13001
13002                  --  A record type that is the Equivalent_Type for a remote
13003                  --  access-to-subprogram type.
13004
13005                  Decl := Declaration_Node (Corresponding_Remote_Type (Nm));
13006
13007               else
13008                  --  A non-expanded RAS type (distribution is not enabled)
13009
13010                  Decl := Declaration_Node (Nm);
13011               end if;
13012
13013               if Nkind (Decl) = N_Full_Type_Declaration
13014                 and then Nkind (Type_Definition (Decl)) =
13015                                     N_Access_Procedure_Definition
13016               then
13017                  L := Parameter_Specifications (Type_Definition (Decl));
13018                  Process_Async_Pragma;
13019
13020                  if Is_Asynchronous (Nm)
13021                    and then Expander_Active
13022                    and then Get_PCS_Name /= Name_No_DSA
13023                  then
13024                     RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
13025                  end if;
13026
13027               else
13028                  Error_Pragma_Arg
13029                    ("pragma% cannot reference access-to-function type",
13030                    Arg1);
13031               end if;
13032
13033            --  Only other possibility is Access-to-class-wide type
13034
13035            elsif Is_Access_Type (Nm)
13036              and then Is_Class_Wide_Type (Designated_Type (Nm))
13037            then
13038               Check_First_Subtype (Arg1);
13039               Set_Is_Asynchronous (Nm);
13040               if Expander_Active then
13041                  RACW_Type_Is_Asynchronous (Nm);
13042               end if;
13043
13044            else
13045               Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
13046            end if;
13047         end Asynchronous;
13048
13049         ------------
13050         -- Atomic --
13051         ------------
13052
13053         --  pragma Atomic (LOCAL_NAME);
13054
13055         when Pragma_Atomic =>
13056            Process_Atomic_Independent_Shared_Volatile;
13057
13058         -----------------------
13059         -- Atomic_Components --
13060         -----------------------
13061
13062         --  pragma Atomic_Components (array_LOCAL_NAME);
13063
13064         --  This processing is shared by Volatile_Components
13065
13066         when Pragma_Atomic_Components
13067            | Pragma_Volatile_Components
13068         =>
13069         Atomic_Components : declare
13070            D    : Node_Id;
13071            E    : Entity_Id;
13072            E_Id : Node_Id;
13073            K    : Node_Kind;
13074
13075         begin
13076            Check_Ada_83_Warning;
13077            Check_No_Identifiers;
13078            Check_Arg_Count (1);
13079            Check_Arg_Is_Local_Name (Arg1);
13080            E_Id := Get_Pragma_Arg (Arg1);
13081
13082            if Etype (E_Id) = Any_Type then
13083               return;
13084            end if;
13085
13086            E := Entity (E_Id);
13087
13088            --  A pragma that applies to a Ghost entity becomes Ghost for the
13089            --  purposes of legality checks and removal of ignored Ghost code.
13090
13091            Mark_Ghost_Pragma (N, E);
13092            Check_Duplicate_Pragma (E);
13093
13094            if Rep_Item_Too_Early (E, N)
13095                 or else
13096               Rep_Item_Too_Late (E, N)
13097            then
13098               return;
13099            end if;
13100
13101            D := Declaration_Node (E);
13102            K := Nkind (D);
13103
13104            if (K = N_Full_Type_Declaration and then Is_Array_Type (E))
13105              or else
13106                ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
13107                   and then Nkind (D) = N_Object_Declaration
13108                   and then Nkind (Object_Definition (D)) =
13109                                       N_Constrained_Array_Definition)
13110            then
13111               --  The flag is set on the object, or on the base type
13112
13113               if Nkind (D) /= N_Object_Declaration then
13114                  E := Base_Type (E);
13115               end if;
13116
13117               --  Atomic implies both Independent and Volatile
13118
13119               if Prag_Id = Pragma_Atomic_Components then
13120                  Set_Has_Atomic_Components (E);
13121                  Set_Has_Independent_Components (E);
13122               end if;
13123
13124               Set_Has_Volatile_Components (E);
13125
13126            else
13127               Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
13128            end if;
13129         end Atomic_Components;
13130
13131         --------------------
13132         -- Attach_Handler --
13133         --------------------
13134
13135         --  pragma Attach_Handler (handler_NAME, EXPRESSION);
13136
13137         when Pragma_Attach_Handler =>
13138            Check_Ada_83_Warning;
13139            Check_No_Identifiers;
13140            Check_Arg_Count (2);
13141
13142            if No_Run_Time_Mode then
13143               Error_Msg_CRT ("Attach_Handler pragma", N);
13144            else
13145               Check_Interrupt_Or_Attach_Handler;
13146
13147               --  The expression that designates the attribute may depend on a
13148               --  discriminant, and is therefore a per-object expression, to
13149               --  be expanded in the init proc. If expansion is enabled, then
13150               --  perform semantic checks on a copy only.
13151
13152               declare
13153                  Temp  : Node_Id;
13154                  Typ   : Node_Id;
13155                  Parg2 : constant Node_Id := Get_Pragma_Arg (Arg2);
13156
13157               begin
13158                  --  In Relaxed_RM_Semantics mode, we allow any static
13159                  --  integer value, for compatibility with other compilers.
13160
13161                  if Relaxed_RM_Semantics
13162                    and then Nkind (Parg2) = N_Integer_Literal
13163                  then
13164                     Typ := Standard_Integer;
13165                  else
13166                     Typ := RTE (RE_Interrupt_ID);
13167                  end if;
13168
13169                  if Expander_Active then
13170                     Temp := New_Copy_Tree (Parg2);
13171                     Set_Parent (Temp, N);
13172                     Preanalyze_And_Resolve (Temp, Typ);
13173                  else
13174                     Analyze (Parg2);
13175                     Resolve (Parg2, Typ);
13176                  end if;
13177               end;
13178
13179               Process_Interrupt_Or_Attach_Handler;
13180            end if;
13181
13182         --------------------
13183         -- C_Pass_By_Copy --
13184         --------------------
13185
13186         --  pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
13187
13188         when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
13189            Arg : Node_Id;
13190            Val : Uint;
13191
13192         begin
13193            GNAT_Pragma;
13194            Check_Valid_Configuration_Pragma;
13195            Check_Arg_Count (1);
13196            Check_Optional_Identifier (Arg1, "max_size");
13197
13198            Arg := Get_Pragma_Arg (Arg1);
13199            Check_Arg_Is_OK_Static_Expression (Arg, Any_Integer);
13200
13201            Val := Expr_Value (Arg);
13202
13203            if Val <= 0 then
13204               Error_Pragma_Arg
13205                 ("maximum size for pragma% must be positive", Arg1);
13206
13207            elsif UI_Is_In_Int_Range (Val) then
13208               Default_C_Record_Mechanism := UI_To_Int (Val);
13209
13210            --  If a giant value is given, Int'Last will do well enough.
13211            --  If sometime someone complains that a record larger than
13212            --  two gigabytes is not copied, we will worry about it then.
13213
13214            else
13215               Default_C_Record_Mechanism := Mechanism_Type'Last;
13216            end if;
13217         end C_Pass_By_Copy;
13218
13219         -----------
13220         -- Check --
13221         -----------
13222
13223         --  pragma Check ([Name    =>] CHECK_KIND,
13224         --                [Check   =>] Boolean_EXPRESSION
13225         --              [,[Message =>] String_EXPRESSION]);
13226
13227         --  CHECK_KIND ::= IDENTIFIER           |
13228         --                 Pre'Class            |
13229         --                 Post'Class           |
13230         --                 Invariant'Class      |
13231         --                 Type_Invariant'Class
13232
13233         --  The identifiers Assertions and Statement_Assertions are not
13234         --  allowed, since they have special meaning for Check_Policy.
13235
13236         --  WARNING: The code below manages Ghost regions. Return statements
13237         --  must be replaced by gotos which jump to the end of the code and
13238         --  restore the Ghost mode.
13239
13240         when Pragma_Check => Check : declare
13241            Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
13242            --  Save the Ghost mode to restore on exit
13243
13244            Cname : Name_Id;
13245            Eloc  : Source_Ptr;
13246            Expr  : Node_Id;
13247            Str   : Node_Id;
13248            pragma Warnings (Off, Str);
13249
13250         begin
13251            --  Pragma Check is Ghost when it applies to a Ghost entity. Set
13252            --  the mode now to ensure that any nodes generated during analysis
13253            --  and expansion are marked as Ghost.
13254
13255            Set_Ghost_Mode (N);
13256
13257            GNAT_Pragma;
13258            Check_At_Least_N_Arguments (2);
13259            Check_At_Most_N_Arguments (3);
13260            Check_Optional_Identifier (Arg1, Name_Name);
13261            Check_Optional_Identifier (Arg2, Name_Check);
13262
13263            if Arg_Count = 3 then
13264               Check_Optional_Identifier (Arg3, Name_Message);
13265               Str := Get_Pragma_Arg (Arg3);
13266            end if;
13267
13268            Rewrite_Assertion_Kind (Get_Pragma_Arg (Arg1));
13269            Check_Arg_Is_Identifier (Arg1);
13270            Cname := Chars (Get_Pragma_Arg (Arg1));
13271
13272            --  Check forbidden name Assertions or Statement_Assertions
13273
13274            case Cname is
13275               when Name_Assertions =>
13276                  Error_Pragma_Arg
13277                    ("""Assertions"" is not allowed as a check kind for "
13278                     & "pragma%", Arg1);
13279
13280               when Name_Statement_Assertions =>
13281                  Error_Pragma_Arg
13282                    ("""Statement_Assertions"" is not allowed as a check kind "
13283                     & "for pragma%", Arg1);
13284
13285               when others =>
13286                  null;
13287            end case;
13288
13289            --  Check applicable policy. We skip this if Checked/Ignored status
13290            --  is already set (e.g. in the case of a pragma from an aspect).
13291
13292            if Is_Checked (N) or else Is_Ignored (N) then
13293               null;
13294
13295            --  For a non-source pragma that is a rewriting of another pragma,
13296            --  copy the Is_Checked/Ignored status from the rewritten pragma.
13297
13298            elsif Is_Rewrite_Substitution (N)
13299              and then Nkind (Original_Node (N)) = N_Pragma
13300              and then Original_Node (N) /= N
13301            then
13302               Set_Is_Ignored (N, Is_Ignored (Original_Node (N)));
13303               Set_Is_Checked (N, Is_Checked (Original_Node (N)));
13304
13305            --  Otherwise query the applicable policy at this point
13306
13307            else
13308               case Check_Kind (Cname) is
13309                  when Name_Ignore =>
13310                     Set_Is_Ignored (N, True);
13311                     Set_Is_Checked (N, False);
13312
13313                  when Name_Check =>
13314                     Set_Is_Ignored (N, False);
13315                     Set_Is_Checked (N, True);
13316
13317                  --  For disable, rewrite pragma as null statement and skip
13318                  --  rest of the analysis of the pragma.
13319
13320                  when Name_Disable =>
13321                     Rewrite (N, Make_Null_Statement (Loc));
13322                     Analyze (N);
13323                     raise Pragma_Exit;
13324
13325                  --  No other possibilities
13326
13327                  when others =>
13328                     raise Program_Error;
13329               end case;
13330            end if;
13331
13332            --  If check kind was not Disable, then continue pragma analysis
13333
13334            Expr := Get_Pragma_Arg (Arg2);
13335
13336            --  Deal with SCO generation
13337
13338            if Is_Checked (N) and then not Split_PPC (N) then
13339               Set_SCO_Pragma_Enabled (Loc);
13340            end if;
13341
13342            --  Deal with analyzing the string argument. If checks are not
13343            --  on we don't want any expansion (since such expansion would
13344            --  not get properly deleted) but we do want to analyze (to get
13345            --  proper references). The Preanalyze_And_Resolve routine does
13346            --  just what we want. Ditto if pragma is active, because it will
13347            --  be rewritten as an if-statement whose analysis will complete
13348            --  analysis and expansion of the string message. This makes a
13349            --  difference in the unusual case where the expression for the
13350            --  string may have a side effect, such as raising an exception.
13351            --  This is mandated by RM 11.4.2, which specifies that the string
13352            --  expression is only evaluated if the check fails and
13353            --  Assertion_Error is to be raised.
13354
13355            if Arg_Count = 3 then
13356               Preanalyze_And_Resolve (Str, Standard_String);
13357            end if;
13358
13359            --  Now you might think we could just do the same with the Boolean
13360            --  expression if checks are off (and expansion is on) and then
13361            --  rewrite the check as a null statement. This would work but we
13362            --  would lose the useful warnings about an assertion being bound
13363            --  to fail even if assertions are turned off.
13364
13365            --  So instead we wrap the boolean expression in an if statement
13366            --  that looks like:
13367
13368            --    if False and then condition then
13369            --       null;
13370            --    end if;
13371
13372            --  The reason we do this rewriting during semantic analysis rather
13373            --  than as part of normal expansion is that we cannot analyze and
13374            --  expand the code for the boolean expression directly, or it may
13375            --  cause insertion of actions that would escape the attempt to
13376            --  suppress the check code.
13377
13378            --  Note that the Sloc for the if statement corresponds to the
13379            --  argument condition, not the pragma itself. The reason for
13380            --  this is that we may generate a warning if the condition is
13381            --  False at compile time, and we do not want to delete this
13382            --  warning when we delete the if statement.
13383
13384            if Expander_Active and Is_Ignored (N) then
13385               Eloc := Sloc (Expr);
13386
13387               Rewrite (N,
13388                 Make_If_Statement (Eloc,
13389                   Condition =>
13390                     Make_And_Then (Eloc,
13391                       Left_Opnd  => Make_Identifier (Eloc, Name_False),
13392                       Right_Opnd => Expr),
13393                   Then_Statements => New_List (
13394                     Make_Null_Statement (Eloc))));
13395
13396               --  Now go ahead and analyze the if statement
13397
13398               In_Assertion_Expr := In_Assertion_Expr + 1;
13399
13400               --  One rather special treatment. If we are now in Eliminated
13401               --  overflow mode, then suppress overflow checking since we do
13402               --  not want to drag in the bignum stuff if we are in Ignore
13403               --  mode anyway. This is particularly important if we are using
13404               --  a configurable run time that does not support bignum ops.
13405
13406               if Scope_Suppress.Overflow_Mode_Assertions = Eliminated then
13407                  declare
13408                     Svo : constant Boolean :=
13409                             Scope_Suppress.Suppress (Overflow_Check);
13410                  begin
13411                     Scope_Suppress.Overflow_Mode_Assertions  := Strict;
13412                     Scope_Suppress.Suppress (Overflow_Check) := True;
13413                     Analyze (N);
13414                     Scope_Suppress.Suppress (Overflow_Check) := Svo;
13415                     Scope_Suppress.Overflow_Mode_Assertions  := Eliminated;
13416                  end;
13417
13418               --  Not that special case
13419
13420               else
13421                  Analyze (N);
13422               end if;
13423
13424               --  All done with this check
13425
13426               In_Assertion_Expr := In_Assertion_Expr - 1;
13427
13428            --  Check is active or expansion not active. In these cases we can
13429            --  just go ahead and analyze the boolean with no worries.
13430
13431            else
13432               In_Assertion_Expr := In_Assertion_Expr + 1;
13433               Analyze_And_Resolve (Expr, Any_Boolean);
13434               In_Assertion_Expr := In_Assertion_Expr - 1;
13435            end if;
13436
13437            Restore_Ghost_Mode (Saved_GM);
13438         end Check;
13439
13440         --------------------------
13441         -- Check_Float_Overflow --
13442         --------------------------
13443
13444         --  pragma Check_Float_Overflow;
13445
13446         when Pragma_Check_Float_Overflow =>
13447            GNAT_Pragma;
13448            Check_Valid_Configuration_Pragma;
13449            Check_Arg_Count (0);
13450            Check_Float_Overflow := not Machine_Overflows_On_Target;
13451
13452         ----------------
13453         -- Check_Name --
13454         ----------------
13455
13456         --  pragma Check_Name (check_IDENTIFIER);
13457
13458         when Pragma_Check_Name =>
13459            GNAT_Pragma;
13460            Check_No_Identifiers;
13461            Check_Valid_Configuration_Pragma;
13462            Check_Arg_Count (1);
13463            Check_Arg_Is_Identifier (Arg1);
13464
13465            declare
13466               Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
13467
13468            begin
13469               for J in Check_Names.First .. Check_Names.Last loop
13470                  if Check_Names.Table (J) = Nam then
13471                     return;
13472                  end if;
13473               end loop;
13474
13475               Check_Names.Append (Nam);
13476            end;
13477
13478         ------------------
13479         -- Check_Policy --
13480         ------------------
13481
13482         --  This is the old style syntax, which is still allowed in all modes:
13483
13484         --  pragma Check_Policy ([Name   =>] CHECK_KIND
13485         --                       [Policy =>] POLICY_IDENTIFIER);
13486
13487         --  POLICY_IDENTIFIER ::= On | Off | Check | Disable | Ignore
13488
13489         --  CHECK_KIND ::= IDENTIFIER           |
13490         --                 Pre'Class            |
13491         --                 Post'Class           |
13492         --                 Type_Invariant'Class |
13493         --                 Invariant'Class
13494
13495         --  This is the new style syntax, compatible with Assertion_Policy
13496         --  and also allowed in all modes.
13497
13498         --  Pragma Check_Policy (
13499         --      CHECK_KIND => POLICY_IDENTIFIER
13500         --   {, CHECK_KIND => POLICY_IDENTIFIER});
13501
13502         --  Note: the identifiers Name and Policy are not allowed as
13503         --  Check_Kind values. This avoids ambiguities between the old and
13504         --  new form syntax.
13505
13506         when Pragma_Check_Policy => Check_Policy : declare
13507            Kind : Node_Id;
13508
13509         begin
13510            GNAT_Pragma;
13511            Check_At_Least_N_Arguments (1);
13512
13513            --  A Check_Policy pragma can appear either as a configuration
13514            --  pragma, or in a declarative part or a package spec (see RM
13515            --  11.5(5) for rules for Suppress/Unsuppress which are also
13516            --  followed for Check_Policy).
13517
13518            if not Is_Configuration_Pragma then
13519               Check_Is_In_Decl_Part_Or_Package_Spec;
13520            end if;
13521
13522            --  Figure out if we have the old or new syntax. We have the
13523            --  old syntax if the first argument has no identifier, or the
13524            --  identifier is Name.
13525
13526            if Nkind (Arg1) /= N_Pragma_Argument_Association
13527              or else Nam_In (Chars (Arg1), No_Name, Name_Name)
13528            then
13529               --  Old syntax
13530
13531               Check_Arg_Count (2);
13532               Check_Optional_Identifier (Arg1, Name_Name);
13533               Kind := Get_Pragma_Arg (Arg1);
13534               Rewrite_Assertion_Kind (Kind,
13535                 From_Policy => Comes_From_Source (N));
13536               Check_Arg_Is_Identifier (Arg1);
13537
13538               --  Check forbidden check kind
13539
13540               if Nam_In (Chars (Kind), Name_Name, Name_Policy) then
13541                  Error_Msg_Name_2 := Chars (Kind);
13542                  Error_Pragma_Arg
13543                    ("pragma% does not allow% as check name", Arg1);
13544               end if;
13545
13546               --  Check policy
13547
13548               Check_Optional_Identifier (Arg2, Name_Policy);
13549               Check_Arg_Is_One_Of
13550                 (Arg2,
13551                  Name_On, Name_Off, Name_Check, Name_Disable, Name_Ignore);
13552
13553               --  And chain pragma on the Check_Policy_List for search
13554
13555               Set_Next_Pragma (N, Opt.Check_Policy_List);
13556               Opt.Check_Policy_List := N;
13557
13558            --  For the new syntax, what we do is to convert each argument to
13559            --  an old syntax equivalent. We do that because we want to chain
13560            --  old style Check_Policy pragmas for the search (we don't want
13561            --  to have to deal with multiple arguments in the search).
13562
13563            else
13564               declare
13565                  Arg   : Node_Id;
13566                  Argx  : Node_Id;
13567                  LocP  : Source_Ptr;
13568                  New_P : Node_Id;
13569
13570               begin
13571                  Arg := Arg1;
13572                  while Present (Arg) loop
13573                     LocP := Sloc (Arg);
13574                     Argx := Get_Pragma_Arg (Arg);
13575
13576                     --  Kind must be specified
13577
13578                     if Nkind (Arg) /= N_Pragma_Argument_Association
13579                       or else Chars (Arg) = No_Name
13580                     then
13581                        Error_Pragma_Arg
13582                          ("missing assertion kind for pragma%", Arg);
13583                     end if;
13584
13585                     --  Construct equivalent old form syntax Check_Policy
13586                     --  pragma and insert it to get remaining checks.
13587
13588                     New_P :=
13589                       Make_Pragma (LocP,
13590                         Chars                        => Name_Check_Policy,
13591                         Pragma_Argument_Associations => New_List (
13592                           Make_Pragma_Argument_Association (LocP,
13593                             Expression =>
13594                               Make_Identifier (LocP, Chars (Arg))),
13595                           Make_Pragma_Argument_Association (Sloc (Argx),
13596                             Expression => Argx)));
13597
13598                     Arg := Next (Arg);
13599
13600                     --  For a configuration pragma, insert old form in
13601                     --  the corresponding file.
13602
13603                     if Is_Configuration_Pragma then
13604                        Insert_After (N, New_P);
13605                        Analyze (New_P);
13606
13607                     else
13608                        Insert_Action (N, New_P);
13609                     end if;
13610                  end loop;
13611
13612                  --  Rewrite original Check_Policy pragma to null, since we
13613                  --  have converted it into a series of old syntax pragmas.
13614
13615                  Rewrite (N, Make_Null_Statement (Loc));
13616                  Analyze (N);
13617               end;
13618            end if;
13619         end Check_Policy;
13620
13621         -------------
13622         -- Comment --
13623         -------------
13624
13625         --  pragma Comment (static_string_EXPRESSION)
13626
13627         --  Processing for pragma Comment shares the circuitry for pragma
13628         --  Ident. The only differences are that Ident enforces a limit of 31
13629         --  characters on its argument, and also enforces limitations on
13630         --  placement for DEC compatibility. Pragma Comment shares neither of
13631         --  these restrictions.
13632
13633         -------------------
13634         -- Common_Object --
13635         -------------------
13636
13637         --  pragma Common_Object (
13638         --        [Internal =>] LOCAL_NAME
13639         --     [, [External =>] EXTERNAL_SYMBOL]
13640         --     [, [Size     =>] EXTERNAL_SYMBOL]);
13641
13642         --  Processing for this pragma is shared with Psect_Object
13643
13644         ------------------------
13645         -- Compile_Time_Error --
13646         ------------------------
13647
13648         --  pragma Compile_Time_Error
13649         --    (boolean_EXPRESSION, static_string_EXPRESSION);
13650
13651         when Pragma_Compile_Time_Error =>
13652            GNAT_Pragma;
13653            Process_Compile_Time_Warning_Or_Error;
13654
13655         --------------------------
13656         -- Compile_Time_Warning --
13657         --------------------------
13658
13659         --  pragma Compile_Time_Warning
13660         --    (boolean_EXPRESSION, static_string_EXPRESSION);
13661
13662         when Pragma_Compile_Time_Warning =>
13663            GNAT_Pragma;
13664            Process_Compile_Time_Warning_Or_Error;
13665
13666         ---------------------------
13667         -- Compiler_Unit_Warning --
13668         ---------------------------
13669
13670         --  pragma Compiler_Unit_Warning;
13671
13672         --  Historical note
13673
13674         --  Originally, we had only pragma Compiler_Unit, and it resulted in
13675         --  errors not warnings. This means that we had introduced a big extra
13676         --  inertia to compiler changes, since even if we implemented a new
13677         --  feature, and even if all versions to be used for bootstrapping
13678         --  implemented this new feature, we could not use it, since old
13679         --  compilers would give errors for using this feature in units
13680         --  having Compiler_Unit pragmas.
13681
13682         --  By changing Compiler_Unit to Compiler_Unit_Warning, we solve the
13683         --  problem. We no longer have any units mentioning Compiler_Unit,
13684         --  so old compilers see Compiler_Unit_Warning which is unrecognized,
13685         --  and thus generates a warning which can be ignored. So that deals
13686         --  with the problem of old compilers not implementing the newer form
13687         --  of the pragma.
13688
13689         --  Newer compilers recognize the new pragma, but generate warning
13690         --  messages instead of errors, which again can be ignored in the
13691         --  case of an old compiler which implements a wanted new feature
13692         --  but at the time felt like warning about it for older compilers.
13693
13694         --  We retain Compiler_Unit so that new compilers can be used to build
13695         --  older run-times that use this pragma. That's an unusual case, but
13696         --  it's easy enough to handle, so why not?
13697
13698         when Pragma_Compiler_Unit
13699            | Pragma_Compiler_Unit_Warning
13700         =>
13701            GNAT_Pragma;
13702            Check_Arg_Count (0);
13703
13704            --  Only recognized in main unit
13705
13706            if Current_Sem_Unit = Main_Unit then
13707               Compiler_Unit := True;
13708            end if;
13709
13710         -----------------------------
13711         -- Complete_Representation --
13712         -----------------------------
13713
13714         --  pragma Complete_Representation;
13715
13716         when Pragma_Complete_Representation =>
13717            GNAT_Pragma;
13718            Check_Arg_Count (0);
13719
13720            if Nkind (Parent (N)) /= N_Record_Representation_Clause then
13721               Error_Pragma
13722                 ("pragma & must appear within record representation clause");
13723            end if;
13724
13725         ----------------------------
13726         -- Complex_Representation --
13727         ----------------------------
13728
13729         --  pragma Complex_Representation ([Entity =>] LOCAL_NAME);
13730
13731         when Pragma_Complex_Representation => Complex_Representation : declare
13732            E_Id : Entity_Id;
13733            E    : Entity_Id;
13734            Ent  : Entity_Id;
13735
13736         begin
13737            GNAT_Pragma;
13738            Check_Arg_Count (1);
13739            Check_Optional_Identifier (Arg1, Name_Entity);
13740            Check_Arg_Is_Local_Name (Arg1);
13741            E_Id := Get_Pragma_Arg (Arg1);
13742
13743            if Etype (E_Id) = Any_Type then
13744               return;
13745            end if;
13746
13747            E := Entity (E_Id);
13748
13749            if not Is_Record_Type (E) then
13750               Error_Pragma_Arg
13751                 ("argument for pragma% must be record type", Arg1);
13752            end if;
13753
13754            Ent := First_Entity (E);
13755
13756            if No (Ent)
13757              or else No (Next_Entity (Ent))
13758              or else Present (Next_Entity (Next_Entity (Ent)))
13759              or else not Is_Floating_Point_Type (Etype (Ent))
13760              or else Etype (Ent) /= Etype (Next_Entity (Ent))
13761            then
13762               Error_Pragma_Arg
13763                 ("record for pragma% must have two fields of the same "
13764                  & "floating-point type", Arg1);
13765
13766            else
13767               Set_Has_Complex_Representation (Base_Type (E));
13768
13769               --  We need to treat the type has having a non-standard
13770               --  representation, for back-end purposes, even though in
13771               --  general a complex will have the default representation
13772               --  of a record with two real components.
13773
13774               Set_Has_Non_Standard_Rep (Base_Type (E));
13775            end if;
13776         end Complex_Representation;
13777
13778         -------------------------
13779         -- Component_Alignment --
13780         -------------------------
13781
13782         --  pragma Component_Alignment (
13783         --        [Form =>] ALIGNMENT_CHOICE
13784         --     [, [Name =>] type_LOCAL_NAME]);
13785         --
13786         --   ALIGNMENT_CHOICE ::=
13787         --     Component_Size
13788         --   | Component_Size_4
13789         --   | Storage_Unit
13790         --   | Default
13791
13792         when Pragma_Component_Alignment => Component_AlignmentP : declare
13793            Args  : Args_List (1 .. 2);
13794            Names : constant Name_List (1 .. 2) := (
13795                      Name_Form,
13796                      Name_Name);
13797
13798            Form  : Node_Id renames Args (1);
13799            Name  : Node_Id renames Args (2);
13800
13801            Atype : Component_Alignment_Kind;
13802            Typ   : Entity_Id;
13803
13804         begin
13805            GNAT_Pragma;
13806            Gather_Associations (Names, Args);
13807
13808            if No (Form) then
13809               Error_Pragma ("missing Form argument for pragma%");
13810            end if;
13811
13812            Check_Arg_Is_Identifier (Form);
13813
13814            --  Get proper alignment, note that Default = Component_Size on all
13815            --  machines we have so far, and we want to set this value rather
13816            --  than the default value to indicate that it has been explicitly
13817            --  set (and thus will not get overridden by the default component
13818            --  alignment for the current scope)
13819
13820            if Chars (Form) = Name_Component_Size then
13821               Atype := Calign_Component_Size;
13822
13823            elsif Chars (Form) = Name_Component_Size_4 then
13824               Atype := Calign_Component_Size_4;
13825
13826            elsif Chars (Form) = Name_Default then
13827               Atype := Calign_Component_Size;
13828
13829            elsif Chars (Form) = Name_Storage_Unit then
13830               Atype := Calign_Storage_Unit;
13831
13832            else
13833               Error_Pragma_Arg
13834                 ("invalid Form parameter for pragma%", Form);
13835            end if;
13836
13837            --  The pragma appears in a configuration file
13838
13839            if No (Parent (N)) then
13840               Check_Valid_Configuration_Pragma;
13841
13842               --  Capture the component alignment in a global variable when
13843               --  the pragma appears in a configuration file. Note that the
13844               --  scope stack is empty at this point and cannot be used to
13845               --  store the alignment value.
13846
13847               Configuration_Component_Alignment := Atype;
13848
13849            --  Case with no name, supplied, affects scope table entry
13850
13851            elsif No (Name) then
13852               Scope_Stack.Table
13853                 (Scope_Stack.Last).Component_Alignment_Default := Atype;
13854
13855            --  Case of name supplied
13856
13857            else
13858               Check_Arg_Is_Local_Name (Name);
13859               Find_Type (Name);
13860               Typ := Entity (Name);
13861
13862               if Typ = Any_Type
13863                 or else Rep_Item_Too_Early (Typ, N)
13864               then
13865                  return;
13866               else
13867                  Typ := Underlying_Type (Typ);
13868               end if;
13869
13870               if not Is_Record_Type (Typ)
13871                 and then not Is_Array_Type (Typ)
13872               then
13873                  Error_Pragma_Arg
13874                    ("Name parameter of pragma% must identify record or "
13875                     & "array type", Name);
13876               end if;
13877
13878               --  An explicit Component_Alignment pragma overrides an
13879               --  implicit pragma Pack, but not an explicit one.
13880
13881               if not Has_Pragma_Pack (Base_Type (Typ)) then
13882                  Set_Is_Packed (Base_Type (Typ), False);
13883                  Set_Component_Alignment (Base_Type (Typ), Atype);
13884               end if;
13885            end if;
13886         end Component_AlignmentP;
13887
13888         --------------------------------
13889         -- Constant_After_Elaboration --
13890         --------------------------------
13891
13892         --  pragma Constant_After_Elaboration [ (boolean_EXPRESSION) ];
13893
13894         when Pragma_Constant_After_Elaboration => Constant_After_Elaboration :
13895         declare
13896            Obj_Decl : Node_Id;
13897            Obj_Id   : Entity_Id;
13898
13899         begin
13900            GNAT_Pragma;
13901            Check_No_Identifiers;
13902            Check_At_Most_N_Arguments (1);
13903
13904            Obj_Decl := Find_Related_Context (N, Do_Checks => True);
13905
13906            --  Object declaration
13907
13908            if Nkind (Obj_Decl) = N_Object_Declaration then
13909               null;
13910
13911            --  Otherwise the pragma is associated with an illegal construct
13912
13913            else
13914               Pragma_Misplaced;
13915               return;
13916            end if;
13917
13918            Obj_Id := Defining_Entity (Obj_Decl);
13919
13920            --  The object declaration must be a library-level variable which
13921            --  is either explicitly initialized or obtains a value during the
13922            --  elaboration of a package body (SPARK RM 3.3.1).
13923
13924            if Ekind (Obj_Id) = E_Variable then
13925               if not Is_Library_Level_Entity (Obj_Id) then
13926                  Error_Pragma
13927                    ("pragma % must apply to a library level variable");
13928                  return;
13929               end if;
13930
13931            --  Otherwise the pragma applies to a constant, which is illegal
13932
13933            else
13934               Error_Pragma ("pragma % must apply to a variable declaration");
13935               return;
13936            end if;
13937
13938            --  A pragma that applies to a Ghost entity becomes Ghost for the
13939            --  purposes of legality checks and removal of ignored Ghost code.
13940
13941            Mark_Ghost_Pragma (N, Obj_Id);
13942
13943            --  Chain the pragma on the contract for completeness
13944
13945            Add_Contract_Item (N, Obj_Id);
13946
13947            --  Analyze the Boolean expression (if any)
13948
13949            if Present (Arg1) then
13950               Check_Static_Boolean_Expression (Get_Pragma_Arg (Arg1));
13951            end if;
13952         end Constant_After_Elaboration;
13953
13954         --------------------
13955         -- Contract_Cases --
13956         --------------------
13957
13958         --  pragma Contract_Cases ((CONTRACT_CASE {, CONTRACT_CASE));
13959
13960         --  CONTRACT_CASE ::= CASE_GUARD => CONSEQUENCE
13961
13962         --  CASE_GUARD ::= boolean_EXPRESSION | others
13963
13964         --  CONSEQUENCE ::= boolean_EXPRESSION
13965
13966         --  Characteristics:
13967
13968         --    * Analysis - The annotation undergoes initial checks to verify
13969         --    the legal placement and context. Secondary checks preanalyze the
13970         --    expressions in:
13971
13972         --       Analyze_Contract_Cases_In_Decl_Part
13973
13974         --    * Expansion - The annotation is expanded during the expansion of
13975         --    the related subprogram [body] contract as performed in:
13976
13977         --       Expand_Subprogram_Contract
13978
13979         --    * Template - The annotation utilizes the generic template of the
13980         --    related subprogram [body] when it is:
13981
13982         --       aspect on subprogram declaration
13983         --       aspect on stand-alone subprogram body
13984         --       pragma on stand-alone subprogram body
13985
13986         --    The annotation must prepare its own template when it is:
13987
13988         --       pragma on subprogram declaration
13989
13990         --    * Globals - Capture of global references must occur after full
13991         --    analysis.
13992
13993         --    * Instance - The annotation is instantiated automatically when
13994         --    the related generic subprogram [body] is instantiated except for
13995         --    the "pragma on subprogram declaration" case. In that scenario
13996         --    the annotation must instantiate itself.
13997
13998         when Pragma_Contract_Cases => Contract_Cases : declare
13999            Spec_Id   : Entity_Id;
14000            Subp_Decl : Node_Id;
14001            Subp_Spec : Node_Id;
14002
14003         begin
14004            GNAT_Pragma;
14005            Check_No_Identifiers;
14006            Check_Arg_Count (1);
14007
14008            --  Ensure the proper placement of the pragma. Contract_Cases must
14009            --  be associated with a subprogram declaration or a body that acts
14010            --  as a spec.
14011
14012            Subp_Decl :=
14013              Find_Related_Declaration_Or_Body (N, Do_Checks => True);
14014
14015            --  Entry
14016
14017            if Nkind (Subp_Decl) = N_Entry_Declaration then
14018               null;
14019
14020            --  Generic subprogram
14021
14022            elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
14023               null;
14024
14025            --  Body acts as spec
14026
14027            elsif Nkind (Subp_Decl) = N_Subprogram_Body
14028              and then No (Corresponding_Spec (Subp_Decl))
14029            then
14030               null;
14031
14032            --  Body stub acts as spec
14033
14034            elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
14035              and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
14036            then
14037               null;
14038
14039            --  Subprogram
14040
14041            elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
14042               Subp_Spec := Specification (Subp_Decl);
14043
14044               --  Pragma Contract_Cases is forbidden on null procedures, as
14045               --  this may lead to potential ambiguities in behavior when
14046               --  interface null procedures are involved.
14047
14048               if Nkind (Subp_Spec) = N_Procedure_Specification
14049                 and then Null_Present (Subp_Spec)
14050               then
14051                  Error_Msg_N (Fix_Error
14052                    ("pragma % cannot apply to null procedure"), N);
14053                  return;
14054               end if;
14055
14056            else
14057               Pragma_Misplaced;
14058               return;
14059            end if;
14060
14061            Spec_Id := Unique_Defining_Entity (Subp_Decl);
14062
14063            --  A pragma that applies to a Ghost entity becomes Ghost for the
14064            --  purposes of legality checks and removal of ignored Ghost code.
14065
14066            Mark_Ghost_Pragma (N, Spec_Id);
14067            Ensure_Aggregate_Form (Get_Argument (N, Spec_Id));
14068
14069            --  Chain the pragma on the contract for further processing by
14070            --  Analyze_Contract_Cases_In_Decl_Part.
14071
14072            Add_Contract_Item (N, Defining_Entity (Subp_Decl));
14073
14074            --  Fully analyze the pragma when it appears inside an entry
14075            --  or subprogram body because it cannot benefit from forward
14076            --  references.
14077
14078            if Nkind_In (Subp_Decl, N_Entry_Body,
14079                                    N_Subprogram_Body,
14080                                    N_Subprogram_Body_Stub)
14081            then
14082               --  The legality checks of pragma Contract_Cases are affected by
14083               --  the SPARK mode in effect and the volatility of the context.
14084               --  Analyze all pragmas in a specific order.
14085
14086               Analyze_If_Present (Pragma_SPARK_Mode);
14087               Analyze_If_Present (Pragma_Volatile_Function);
14088               Analyze_Contract_Cases_In_Decl_Part (N);
14089            end if;
14090         end Contract_Cases;
14091
14092         ----------------
14093         -- Controlled --
14094         ----------------
14095
14096         --  pragma Controlled (first_subtype_LOCAL_NAME);
14097
14098         when Pragma_Controlled => Controlled : declare
14099            Arg : Node_Id;
14100
14101         begin
14102            Check_No_Identifiers;
14103            Check_Arg_Count (1);
14104            Check_Arg_Is_Local_Name (Arg1);
14105            Arg := Get_Pragma_Arg (Arg1);
14106
14107            if not Is_Entity_Name (Arg)
14108              or else not Is_Access_Type (Entity (Arg))
14109            then
14110               Error_Pragma_Arg ("pragma% requires access type", Arg1);
14111            else
14112               Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
14113            end if;
14114         end Controlled;
14115
14116         ----------------
14117         -- Convention --
14118         ----------------
14119
14120         --  pragma Convention ([Convention =>] convention_IDENTIFIER,
14121         --    [Entity =>] LOCAL_NAME);
14122
14123         when Pragma_Convention => Convention : declare
14124            C : Convention_Id;
14125            E : Entity_Id;
14126            pragma Warnings (Off, C);
14127            pragma Warnings (Off, E);
14128
14129         begin
14130            Check_Arg_Order ((Name_Convention, Name_Entity));
14131            Check_Ada_83_Warning;
14132            Check_Arg_Count (2);
14133            Process_Convention (C, E);
14134
14135            --  A pragma that applies to a Ghost entity becomes Ghost for the
14136            --  purposes of legality checks and removal of ignored Ghost code.
14137
14138            Mark_Ghost_Pragma (N, E);
14139         end Convention;
14140
14141         ---------------------------
14142         -- Convention_Identifier --
14143         ---------------------------
14144
14145         --  pragma Convention_Identifier ([Name =>] IDENTIFIER,
14146         --    [Convention =>] convention_IDENTIFIER);
14147
14148         when Pragma_Convention_Identifier => Convention_Identifier : declare
14149            Idnam : Name_Id;
14150            Cname : Name_Id;
14151
14152         begin
14153            GNAT_Pragma;
14154            Check_Arg_Order ((Name_Name, Name_Convention));
14155            Check_Arg_Count (2);
14156            Check_Optional_Identifier (Arg1, Name_Name);
14157            Check_Optional_Identifier (Arg2, Name_Convention);
14158            Check_Arg_Is_Identifier (Arg1);
14159            Check_Arg_Is_Identifier (Arg2);
14160            Idnam := Chars (Get_Pragma_Arg (Arg1));
14161            Cname := Chars (Get_Pragma_Arg (Arg2));
14162
14163            if Is_Convention_Name (Cname) then
14164               Record_Convention_Identifier
14165                 (Idnam, Get_Convention_Id (Cname));
14166            else
14167               Error_Pragma_Arg
14168                 ("second arg for % pragma must be convention", Arg2);
14169            end if;
14170         end Convention_Identifier;
14171
14172         ---------------
14173         -- CPP_Class --
14174         ---------------
14175
14176         --  pragma CPP_Class ([Entity =>] LOCAL_NAME)
14177
14178         when Pragma_CPP_Class =>
14179            GNAT_Pragma;
14180
14181            if Warn_On_Obsolescent_Feature then
14182               Error_Msg_N
14183                 ("'G'N'A'T pragma cpp'_class is now obsolete and has no "
14184                  & "effect; replace it by pragma import?j?", N);
14185            end if;
14186
14187            Check_Arg_Count (1);
14188
14189            Rewrite (N,
14190              Make_Pragma (Loc,
14191                Chars                        => Name_Import,
14192                Pragma_Argument_Associations => New_List (
14193                  Make_Pragma_Argument_Association (Loc,
14194                    Expression => Make_Identifier (Loc, Name_CPP)),
14195                  New_Copy (First (Pragma_Argument_Associations (N))))));
14196            Analyze (N);
14197
14198         ---------------------
14199         -- CPP_Constructor --
14200         ---------------------
14201
14202         --  pragma CPP_Constructor ([Entity =>] LOCAL_NAME
14203         --    [, [External_Name =>] static_string_EXPRESSION ]
14204         --    [, [Link_Name     =>] static_string_EXPRESSION ]);
14205
14206         when Pragma_CPP_Constructor => CPP_Constructor : declare
14207            Elmt    : Elmt_Id;
14208            Id      : Entity_Id;
14209            Def_Id  : Entity_Id;
14210            Tag_Typ : Entity_Id;
14211
14212         begin
14213            GNAT_Pragma;
14214            Check_At_Least_N_Arguments (1);
14215            Check_At_Most_N_Arguments (3);
14216            Check_Optional_Identifier (Arg1, Name_Entity);
14217            Check_Arg_Is_Local_Name (Arg1);
14218
14219            Id := Get_Pragma_Arg (Arg1);
14220            Find_Program_Unit_Name (Id);
14221
14222            --  If we did not find the name, we are done
14223
14224            if Etype (Id) = Any_Type then
14225               return;
14226            end if;
14227
14228            Def_Id := Entity (Id);
14229
14230            --  Check if already defined as constructor
14231
14232            if Is_Constructor (Def_Id) then
14233               Error_Msg_N
14234                 ("??duplicate argument for pragma 'C'P'P_Constructor", Arg1);
14235               return;
14236            end if;
14237
14238            if Ekind (Def_Id) = E_Function
14239              and then (Is_CPP_Class (Etype (Def_Id))
14240                         or else (Is_Class_Wide_Type (Etype (Def_Id))
14241                                   and then
14242                                  Is_CPP_Class (Root_Type (Etype (Def_Id)))))
14243            then
14244               if Scope (Def_Id) /= Scope (Etype (Def_Id)) then
14245                  Error_Msg_N
14246                    ("'C'P'P constructor must be defined in the scope of "
14247                     & "its returned type", Arg1);
14248               end if;
14249
14250               if Arg_Count >= 2 then
14251                  Set_Imported (Def_Id);
14252                  Set_Is_Public (Def_Id);
14253                  Process_Interface_Name (Def_Id, Arg2, Arg3, N);
14254               end if;
14255
14256               Set_Has_Completion (Def_Id);
14257               Set_Is_Constructor (Def_Id);
14258               Set_Convention (Def_Id, Convention_CPP);
14259
14260               --  Imported C++ constructors are not dispatching primitives
14261               --  because in C++ they don't have a dispatch table slot.
14262               --  However, in Ada the constructor has the profile of a
14263               --  function that returns a tagged type and therefore it has
14264               --  been treated as a primitive operation during semantic
14265               --  analysis. We now remove it from the list of primitive
14266               --  operations of the type.
14267
14268               if Is_Tagged_Type (Etype (Def_Id))
14269                 and then not Is_Class_Wide_Type (Etype (Def_Id))
14270                 and then Is_Dispatching_Operation (Def_Id)
14271               then
14272                  Tag_Typ := Etype (Def_Id);
14273
14274                  Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
14275                  while Present (Elmt) and then Node (Elmt) /= Def_Id loop
14276                     Next_Elmt (Elmt);
14277                  end loop;
14278
14279                  Remove_Elmt (Primitive_Operations (Tag_Typ), Elmt);
14280                  Set_Is_Dispatching_Operation (Def_Id, False);
14281               end if;
14282
14283               --  For backward compatibility, if the constructor returns a
14284               --  class wide type, and we internally change the return type to
14285               --  the corresponding root type.
14286
14287               if Is_Class_Wide_Type (Etype (Def_Id)) then
14288                  Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
14289               end if;
14290            else
14291               Error_Pragma_Arg
14292                 ("pragma% requires function returning a 'C'P'P_Class type",
14293                   Arg1);
14294            end if;
14295         end CPP_Constructor;
14296
14297         -----------------
14298         -- CPP_Virtual --
14299         -----------------
14300
14301         when Pragma_CPP_Virtual =>
14302            GNAT_Pragma;
14303
14304            if Warn_On_Obsolescent_Feature then
14305               Error_Msg_N
14306                 ("'G'N'A'T pragma Cpp'_Virtual is now obsolete and has no "
14307                  & "effect?j?", N);
14308            end if;
14309
14310         ----------------
14311         -- CPP_Vtable --
14312         ----------------
14313
14314         when Pragma_CPP_Vtable =>
14315            GNAT_Pragma;
14316
14317            if Warn_On_Obsolescent_Feature then
14318               Error_Msg_N
14319                 ("'G'N'A'T pragma Cpp'_Vtable is now obsolete and has no "
14320                  & "effect?j?", N);
14321            end if;
14322
14323         ---------
14324         -- CPU --
14325         ---------
14326
14327         --  pragma CPU (EXPRESSION);
14328
14329         when Pragma_CPU => CPU : declare
14330            P   : constant Node_Id := Parent (N);
14331            Arg : Node_Id;
14332            Ent : Entity_Id;
14333
14334         begin
14335            Ada_2012_Pragma;
14336            Check_No_Identifiers;
14337            Check_Arg_Count (1);
14338
14339            --  Subprogram case
14340
14341            if Nkind (P) = N_Subprogram_Body then
14342               Check_In_Main_Program;
14343
14344               Arg := Get_Pragma_Arg (Arg1);
14345               Analyze_And_Resolve (Arg, Any_Integer);
14346
14347               Ent := Defining_Unit_Name (Specification (P));
14348
14349               if Nkind (Ent) = N_Defining_Program_Unit_Name then
14350                  Ent := Defining_Identifier (Ent);
14351               end if;
14352
14353               --  Must be static
14354
14355               if not Is_OK_Static_Expression (Arg) then
14356                  Flag_Non_Static_Expr
14357                    ("main subprogram affinity is not static!", Arg);
14358                  raise Pragma_Exit;
14359
14360               --  If constraint error, then we already signalled an error
14361
14362               elsif Raises_Constraint_Error (Arg) then
14363                  null;
14364
14365               --  Otherwise check in range
14366
14367               else
14368                  declare
14369                     CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
14370                     --  This is the entity System.Multiprocessors.CPU_Range;
14371
14372                     Val : constant Uint := Expr_Value (Arg);
14373
14374                  begin
14375                     if Val < Expr_Value (Type_Low_Bound (CPU_Id))
14376                          or else
14377                        Val > Expr_Value (Type_High_Bound (CPU_Id))
14378                     then
14379                        Error_Pragma_Arg
14380                          ("main subprogram CPU is out of range", Arg1);
14381                     end if;
14382                  end;
14383               end if;
14384
14385               Set_Main_CPU
14386                    (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
14387
14388            --  Task case
14389
14390            elsif Nkind (P) = N_Task_Definition then
14391               Arg := Get_Pragma_Arg (Arg1);
14392               Ent := Defining_Identifier (Parent (P));
14393
14394               --  The expression must be analyzed in the special manner
14395               --  described in "Handling of Default and Per-Object
14396               --  Expressions" in sem.ads.
14397
14398               Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
14399
14400            --  Anything else is incorrect
14401
14402            else
14403               Pragma_Misplaced;
14404            end if;
14405
14406            --  Check duplicate pragma before we chain the pragma in the Rep
14407            --  Item chain of Ent.
14408
14409            Check_Duplicate_Pragma (Ent);
14410            Record_Rep_Item (Ent, N);
14411         end CPU;
14412
14413         --------------------
14414         -- Deadline_Floor --
14415         --------------------
14416
14417         --  pragma Deadline_Floor (time_span_EXPRESSION);
14418
14419         when Pragma_Deadline_Floor => Deadline_Floor : declare
14420            P   : constant Node_Id := Parent (N);
14421            Arg : Node_Id;
14422            Ent : Entity_Id;
14423
14424         begin
14425            GNAT_Pragma;
14426            Check_No_Identifiers;
14427            Check_Arg_Count (1);
14428
14429            Arg := Get_Pragma_Arg (Arg1);
14430
14431            --  The expression must be analyzed in the special manner described
14432            --  in "Handling of Default and Per-Object Expressions" in sem.ads.
14433
14434            Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
14435
14436            --  Only protected types allowed
14437
14438            if Nkind (P) /= N_Protected_Definition then
14439               Pragma_Misplaced;
14440
14441            else
14442               Ent := Defining_Identifier (Parent (P));
14443
14444               --  Check duplicate pragma before we chain the pragma in the Rep
14445               --  Item chain of Ent.
14446
14447               Check_Duplicate_Pragma (Ent);
14448               Record_Rep_Item (Ent, N);
14449            end if;
14450         end Deadline_Floor;
14451
14452         -----------
14453         -- Debug --
14454         -----------
14455
14456         --  pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
14457
14458         when Pragma_Debug => Debug : declare
14459            Cond : Node_Id;
14460            Call : Node_Id;
14461
14462         begin
14463            GNAT_Pragma;
14464
14465            --  The condition for executing the call is that the expander
14466            --  is active and that we are not ignoring this debug pragma.
14467
14468            Cond :=
14469              New_Occurrence_Of
14470                (Boolean_Literals
14471                  (Expander_Active and then not Is_Ignored (N)),
14472                 Loc);
14473
14474            if not Is_Ignored (N) then
14475               Set_SCO_Pragma_Enabled (Loc);
14476            end if;
14477
14478            if Arg_Count = 2 then
14479               Cond :=
14480                 Make_And_Then (Loc,
14481                   Left_Opnd  => Relocate_Node (Cond),
14482                   Right_Opnd => Get_Pragma_Arg (Arg1));
14483               Call := Get_Pragma_Arg (Arg2);
14484            else
14485               Call := Get_Pragma_Arg (Arg1);
14486            end if;
14487
14488            if Nkind_In (Call, N_Expanded_Name,
14489                               N_Function_Call,
14490                               N_Identifier,
14491                               N_Indexed_Component,
14492                               N_Selected_Component)
14493            then
14494               --  If this pragma Debug comes from source, its argument was
14495               --  parsed as a name form (which is syntactically identical).
14496               --  In a generic context a parameterless call will be left as
14497               --  an expanded name (if global) or selected_component if local.
14498               --  Change it to a procedure call statement now.
14499
14500               Change_Name_To_Procedure_Call_Statement (Call);
14501
14502            elsif Nkind (Call) = N_Procedure_Call_Statement then
14503
14504               --  Already in the form of a procedure call statement: nothing
14505               --  to do (could happen in case of an internally generated
14506               --  pragma Debug).
14507
14508               null;
14509
14510            else
14511               --  All other cases: diagnose error
14512
14513               Error_Msg
14514                 ("argument of pragma ""Debug"" is not procedure call",
14515                  Sloc (Call));
14516               return;
14517            end if;
14518
14519            --  Rewrite into a conditional with an appropriate condition. We
14520            --  wrap the procedure call in a block so that overhead from e.g.
14521            --  use of the secondary stack does not generate execution overhead
14522            --  for suppressed conditions.
14523
14524            --  Normally the analysis that follows will freeze the subprogram
14525            --  being called. However, if the call is to a null procedure,
14526            --  we want to freeze it before creating the block, because the
14527            --  analysis that follows may be done with expansion disabled, in
14528            --  which case the body will not be generated, leading to spurious
14529            --  errors.
14530
14531            if Nkind (Call) = N_Procedure_Call_Statement
14532              and then Is_Entity_Name (Name (Call))
14533            then
14534               Analyze (Name (Call));
14535               Freeze_Before (N, Entity (Name (Call)));
14536            end if;
14537
14538            Rewrite (N,
14539              Make_Implicit_If_Statement (N,
14540                Condition       => Cond,
14541                Then_Statements => New_List (
14542                  Make_Block_Statement (Loc,
14543                    Handled_Statement_Sequence =>
14544                      Make_Handled_Sequence_Of_Statements (Loc,
14545                        Statements => New_List (Relocate_Node (Call)))))));
14546            Analyze (N);
14547
14548            --  Ignore pragma Debug in GNATprove mode. Do this rewriting
14549            --  after analysis of the normally rewritten node, to capture all
14550            --  references to entities, which avoids issuing wrong warnings
14551            --  about unused entities.
14552
14553            if GNATprove_Mode then
14554               Rewrite (N, Make_Null_Statement (Loc));
14555            end if;
14556         end Debug;
14557
14558         ------------------
14559         -- Debug_Policy --
14560         ------------------
14561
14562         --  pragma Debug_Policy (On | Off | Check | Disable | Ignore)
14563
14564         when Pragma_Debug_Policy =>
14565            GNAT_Pragma;
14566            Check_Arg_Count (1);
14567            Check_No_Identifiers;
14568            Check_Arg_Is_Identifier (Arg1);
14569
14570            --  Exactly equivalent to pragma Check_Policy (Debug, arg), so
14571            --  rewrite it that way, and let the rest of the checking come
14572            --  from analyzing the rewritten pragma.
14573
14574            Rewrite (N,
14575              Make_Pragma (Loc,
14576                Chars                        => Name_Check_Policy,
14577                Pragma_Argument_Associations => New_List (
14578                  Make_Pragma_Argument_Association (Loc,
14579                    Expression => Make_Identifier (Loc, Name_Debug)),
14580
14581                  Make_Pragma_Argument_Association (Loc,
14582                    Expression => Get_Pragma_Arg (Arg1)))));
14583            Analyze (N);
14584
14585         -------------------------------
14586         -- Default_Initial_Condition --
14587         -------------------------------
14588
14589         --  pragma Default_Initial_Condition [ (null | boolean_EXPRESSION) ];
14590
14591         when Pragma_Default_Initial_Condition => DIC : declare
14592            Discard : Boolean;
14593            Stmt    : Node_Id;
14594            Typ     : Entity_Id;
14595
14596         begin
14597            GNAT_Pragma;
14598            Check_No_Identifiers;
14599            Check_At_Most_N_Arguments (1);
14600
14601            Typ  := Empty;
14602            Stmt := Prev (N);
14603            while Present (Stmt) loop
14604
14605               --  Skip prior pragmas, but check for duplicates
14606
14607               if Nkind (Stmt) = N_Pragma then
14608                  if Pragma_Name (Stmt) = Pname then
14609                     Duplication_Error
14610                       (Prag => N,
14611                        Prev => Stmt);
14612                     raise Pragma_Exit;
14613                  end if;
14614
14615               --  Skip internally generated code. Note that derived type
14616               --  declarations of untagged types with discriminants are
14617               --  rewritten as private type declarations.
14618
14619               elsif not Comes_From_Source (Stmt)
14620                 and then Nkind (Stmt) /= N_Private_Type_Declaration
14621               then
14622                  null;
14623
14624               --  The associated private type [extension] has been found, stop
14625               --  the search.
14626
14627               elsif Nkind_In (Stmt, N_Private_Extension_Declaration,
14628                                     N_Private_Type_Declaration)
14629               then
14630                  Typ := Defining_Entity (Stmt);
14631                  exit;
14632
14633               --  The pragma does not apply to a legal construct, issue an
14634               --  error and stop the analysis.
14635
14636               else
14637                  Pragma_Misplaced;
14638                  return;
14639               end if;
14640
14641               Stmt := Prev (Stmt);
14642            end loop;
14643
14644            --  The pragma does not apply to a legal construct, issue an error
14645            --  and stop the analysis.
14646
14647            if No (Typ) then
14648               Pragma_Misplaced;
14649               return;
14650            end if;
14651
14652            --  A pragma that applies to a Ghost entity becomes Ghost for the
14653            --  purposes of legality checks and removal of ignored Ghost code.
14654
14655            Mark_Ghost_Pragma (N, Typ);
14656
14657            --  The pragma signals that the type defines its own DIC assertion
14658            --  expression.
14659
14660            Set_Has_Own_DIC (Typ);
14661
14662            --  Chain the pragma on the rep item chain for further processing
14663
14664            Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
14665
14666            --  Create the declaration of the procedure which verifies the
14667            --  assertion expression of pragma DIC at runtime.
14668
14669            Build_DIC_Procedure_Declaration (Typ);
14670         end DIC;
14671
14672         ----------------------------------
14673         -- Default_Scalar_Storage_Order --
14674         ----------------------------------
14675
14676         --  pragma Default_Scalar_Storage_Order
14677         --           (High_Order_First | Low_Order_First);
14678
14679         when Pragma_Default_Scalar_Storage_Order => DSSO : declare
14680            Default : Character;
14681
14682         begin
14683            GNAT_Pragma;
14684            Check_Arg_Count (1);
14685
14686            --  Default_Scalar_Storage_Order can appear as a configuration
14687            --  pragma, or in a declarative part of a package spec.
14688
14689            if not Is_Configuration_Pragma then
14690               Check_Is_In_Decl_Part_Or_Package_Spec;
14691            end if;
14692
14693            Check_No_Identifiers;
14694            Check_Arg_Is_One_Of
14695              (Arg1, Name_High_Order_First, Name_Low_Order_First);
14696            Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
14697            Default := Fold_Upper (Name_Buffer (1));
14698
14699            if not Support_Nondefault_SSO_On_Target
14700              and then (Ttypes.Bytes_Big_Endian /= (Default = 'H'))
14701            then
14702               if Warn_On_Unrecognized_Pragma then
14703                  Error_Msg_N
14704                    ("non-default Scalar_Storage_Order not supported "
14705                     & "on target?g?", N);
14706                  Error_Msg_N
14707                    ("\pragma Default_Scalar_Storage_Order ignored?g?", N);
14708               end if;
14709
14710            --  Here set the specified default
14711
14712            else
14713               Opt.Default_SSO := Default;
14714            end if;
14715         end DSSO;
14716
14717         --------------------------
14718         -- Default_Storage_Pool --
14719         --------------------------
14720
14721         --  pragma Default_Storage_Pool (storage_pool_NAME | null);
14722
14723         when Pragma_Default_Storage_Pool => Default_Storage_Pool : declare
14724            Pool : Node_Id;
14725
14726         begin
14727            Ada_2012_Pragma;
14728            Check_Arg_Count (1);
14729
14730            --  Default_Storage_Pool can appear as a configuration pragma, or
14731            --  in a declarative part of a package spec.
14732
14733            if not Is_Configuration_Pragma then
14734               Check_Is_In_Decl_Part_Or_Package_Spec;
14735            end if;
14736
14737            if From_Aspect_Specification (N) then
14738               declare
14739                  E : constant Entity_Id := Entity (Corresponding_Aspect (N));
14740               begin
14741                  if not In_Open_Scopes (E) then
14742                     Error_Msg_N
14743                       ("aspect must apply to package or subprogram", N);
14744                  end if;
14745               end;
14746            end if;
14747
14748            if Present (Arg1) then
14749               Pool := Get_Pragma_Arg (Arg1);
14750
14751               --  Case of Default_Storage_Pool (null);
14752
14753               if Nkind (Pool) = N_Null then
14754                  Analyze (Pool);
14755
14756                  --  This is an odd case, this is not really an expression,
14757                  --  so we don't have a type for it. So just set the type to
14758                  --  Empty.
14759
14760                  Set_Etype (Pool, Empty);
14761
14762               --  Case of Default_Storage_Pool (storage_pool_NAME);
14763
14764               else
14765                  --  If it's a configuration pragma, then the only allowed
14766                  --  argument is "null".
14767
14768                  if Is_Configuration_Pragma then
14769                     Error_Pragma_Arg ("NULL expected", Arg1);
14770                  end if;
14771
14772                  --  The expected type for a non-"null" argument is
14773                  --  Root_Storage_Pool'Class, and the pool must be a variable.
14774
14775                  Analyze_And_Resolve
14776                    (Pool, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
14777
14778                  if Is_Variable (Pool) then
14779
14780                     --  A pragma that applies to a Ghost entity becomes Ghost
14781                     --  for the purposes of legality checks and removal of
14782                     --  ignored Ghost code.
14783
14784                     Mark_Ghost_Pragma (N, Entity (Pool));
14785
14786                  else
14787                     Error_Pragma_Arg
14788                       ("default storage pool must be a variable", Arg1);
14789                  end if;
14790               end if;
14791
14792               --  Record the pool name (or null). Freeze.Freeze_Entity for an
14793               --  access type will use this information to set the appropriate
14794               --  attributes of the access type. If the pragma appears in a
14795               --  generic unit it is ignored, given that it may refer to a
14796               --  local entity.
14797
14798               if not Inside_A_Generic then
14799                  Default_Pool := Pool;
14800               end if;
14801            end if;
14802         end Default_Storage_Pool;
14803
14804         -------------
14805         -- Depends --
14806         -------------
14807
14808         --  pragma Depends (DEPENDENCY_RELATION);
14809
14810         --  DEPENDENCY_RELATION ::=
14811         --     null
14812         --  | (DEPENDENCY_CLAUSE {, DEPENDENCY_CLAUSE})
14813
14814         --  DEPENDENCY_CLAUSE ::=
14815         --    OUTPUT_LIST =>[+] INPUT_LIST
14816         --  | NULL_DEPENDENCY_CLAUSE
14817
14818         --  NULL_DEPENDENCY_CLAUSE ::= null => INPUT_LIST
14819
14820         --  OUTPUT_LIST ::= OUTPUT | (OUTPUT {, OUTPUT})
14821
14822         --  INPUT_LIST ::= null | INPUT | (INPUT {, INPUT})
14823
14824         --  OUTPUT ::= NAME | FUNCTION_RESULT
14825         --  INPUT  ::= NAME
14826
14827         --  where FUNCTION_RESULT is a function Result attribute_reference
14828
14829         --  Characteristics:
14830
14831         --    * Analysis - The annotation undergoes initial checks to verify
14832         --    the legal placement and context. Secondary checks fully analyze
14833         --    the dependency clauses in:
14834
14835         --       Analyze_Depends_In_Decl_Part
14836
14837         --    * Expansion - None.
14838
14839         --    * Template - The annotation utilizes the generic template of the
14840         --    related subprogram [body] when it is:
14841
14842         --       aspect on subprogram declaration
14843         --       aspect on stand-alone subprogram body
14844         --       pragma on stand-alone subprogram body
14845
14846         --    The annotation must prepare its own template when it is:
14847
14848         --       pragma on subprogram declaration
14849
14850         --    * Globals - Capture of global references must occur after full
14851         --    analysis.
14852
14853         --    * Instance - The annotation is instantiated automatically when
14854         --    the related generic subprogram [body] is instantiated except for
14855         --    the "pragma on subprogram declaration" case. In that scenario
14856         --    the annotation must instantiate itself.
14857
14858         when Pragma_Depends => Depends : declare
14859            Legal     : Boolean;
14860            Spec_Id   : Entity_Id;
14861            Subp_Decl : Node_Id;
14862
14863         begin
14864            Analyze_Depends_Global (Spec_Id, Subp_Decl, Legal);
14865
14866            if Legal then
14867
14868               --  Chain the pragma on the contract for further processing by
14869               --  Analyze_Depends_In_Decl_Part.
14870
14871               Add_Contract_Item (N, Spec_Id);
14872
14873               --  Fully analyze the pragma when it appears inside an entry
14874               --  or subprogram body because it cannot benefit from forward
14875               --  references.
14876
14877               if Nkind_In (Subp_Decl, N_Entry_Body,
14878                                       N_Subprogram_Body,
14879                                       N_Subprogram_Body_Stub)
14880               then
14881                  --  The legality checks of pragmas Depends and Global are
14882                  --  affected by the SPARK mode in effect and the volatility
14883                  --  of the context. In addition these two pragmas are subject
14884                  --  to an inherent order:
14885
14886                  --    1) Global
14887                  --    2) Depends
14888
14889                  --  Analyze all these pragmas in the order outlined above
14890
14891                  Analyze_If_Present (Pragma_SPARK_Mode);
14892                  Analyze_If_Present (Pragma_Volatile_Function);
14893                  Analyze_If_Present (Pragma_Global);
14894                  Analyze_Depends_In_Decl_Part (N);
14895               end if;
14896            end if;
14897         end Depends;
14898
14899         ---------------------
14900         -- Detect_Blocking --
14901         ---------------------
14902
14903         --  pragma Detect_Blocking;
14904
14905         when Pragma_Detect_Blocking =>
14906            Ada_2005_Pragma;
14907            Check_Arg_Count (0);
14908            Check_Valid_Configuration_Pragma;
14909            Detect_Blocking := True;
14910
14911         ------------------------------------
14912         -- Disable_Atomic_Synchronization --
14913         ------------------------------------
14914
14915         --  pragma Disable_Atomic_Synchronization [(Entity)];
14916
14917         when Pragma_Disable_Atomic_Synchronization =>
14918            GNAT_Pragma;
14919            Process_Disable_Enable_Atomic_Sync (Name_Suppress);
14920
14921         -------------------
14922         -- Discard_Names --
14923         -------------------
14924
14925         --  pragma Discard_Names [([On =>] LOCAL_NAME)];
14926
14927         when Pragma_Discard_Names => Discard_Names : declare
14928            E    : Entity_Id;
14929            E_Id : Node_Id;
14930
14931         begin
14932            Check_Ada_83_Warning;
14933
14934            --  Deal with configuration pragma case
14935
14936            if Arg_Count = 0 and then Is_Configuration_Pragma then
14937               Global_Discard_Names := True;
14938               return;
14939
14940            --  Otherwise, check correct appropriate context
14941
14942            else
14943               Check_Is_In_Decl_Part_Or_Package_Spec;
14944
14945               if Arg_Count = 0 then
14946
14947                  --  If there is no parameter, then from now on this pragma
14948                  --  applies to any enumeration, exception or tagged type
14949                  --  defined in the current declarative part, and recursively
14950                  --  to any nested scope.
14951
14952                  Set_Discard_Names (Current_Scope);
14953                  return;
14954
14955               else
14956                  Check_Arg_Count (1);
14957                  Check_Optional_Identifier (Arg1, Name_On);
14958                  Check_Arg_Is_Local_Name (Arg1);
14959
14960                  E_Id := Get_Pragma_Arg (Arg1);
14961
14962                  if Etype (E_Id) = Any_Type then
14963                     return;
14964                  end if;
14965
14966                  E := Entity (E_Id);
14967
14968                  --  A pragma that applies to a Ghost entity becomes Ghost for
14969                  --  the purposes of legality checks and removal of ignored
14970                  --  Ghost code.
14971
14972                  Mark_Ghost_Pragma (N, E);
14973
14974                  if (Is_First_Subtype (E)
14975                      and then
14976                        (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
14977                    or else Ekind (E) = E_Exception
14978                  then
14979                     Set_Discard_Names (E);
14980                     Record_Rep_Item (E, N);
14981
14982                  else
14983                     Error_Pragma_Arg
14984                       ("inappropriate entity for pragma%", Arg1);
14985                  end if;
14986               end if;
14987            end if;
14988         end Discard_Names;
14989
14990         ------------------------
14991         -- Dispatching_Domain --
14992         ------------------------
14993
14994         --  pragma Dispatching_Domain (EXPRESSION);
14995
14996         when Pragma_Dispatching_Domain => Dispatching_Domain : declare
14997            P   : constant Node_Id := Parent (N);
14998            Arg : Node_Id;
14999            Ent : Entity_Id;
15000
15001         begin
15002            Ada_2012_Pragma;
15003            Check_No_Identifiers;
15004            Check_Arg_Count (1);
15005
15006            --  This pragma is born obsolete, but not the aspect
15007
15008            if not From_Aspect_Specification (N) then
15009               Check_Restriction
15010                 (No_Obsolescent_Features, Pragma_Identifier (N));
15011            end if;
15012
15013            if Nkind (P) = N_Task_Definition then
15014               Arg := Get_Pragma_Arg (Arg1);
15015               Ent := Defining_Identifier (Parent (P));
15016
15017               --  A pragma that applies to a Ghost entity becomes Ghost for
15018               --  the purposes of legality checks and removal of ignored Ghost
15019               --  code.
15020
15021               Mark_Ghost_Pragma (N, Ent);
15022
15023               --  The expression must be analyzed in the special manner
15024               --  described in "Handling of Default and Per-Object
15025               --  Expressions" in sem.ads.
15026
15027               Preanalyze_Spec_Expression (Arg, RTE (RE_Dispatching_Domain));
15028
15029               --  Check duplicate pragma before we chain the pragma in the Rep
15030               --  Item chain of Ent.
15031
15032               Check_Duplicate_Pragma (Ent);
15033               Record_Rep_Item (Ent, N);
15034
15035            --  Anything else is incorrect
15036
15037            else
15038               Pragma_Misplaced;
15039            end if;
15040         end Dispatching_Domain;
15041
15042         ---------------
15043         -- Elaborate --
15044         ---------------
15045
15046         --  pragma Elaborate (library_unit_NAME {, library_unit_NAME});
15047
15048         when Pragma_Elaborate => Elaborate : declare
15049            Arg   : Node_Id;
15050            Citem : Node_Id;
15051
15052         begin
15053            --  Pragma must be in context items list of a compilation unit
15054
15055            if not Is_In_Context_Clause then
15056               Pragma_Misplaced;
15057            end if;
15058
15059            --  Must be at least one argument
15060
15061            if Arg_Count = 0 then
15062               Error_Pragma ("pragma% requires at least one argument");
15063            end if;
15064
15065            --  In Ada 83 mode, there can be no items following it in the
15066            --  context list except other pragmas and implicit with clauses
15067            --  (e.g. those added by use of Rtsfind). In Ada 95 mode, this
15068            --  placement rule does not apply.
15069
15070            if Ada_Version = Ada_83 and then Comes_From_Source (N) then
15071               Citem := Next (N);
15072               while Present (Citem) loop
15073                  if Nkind (Citem) = N_Pragma
15074                    or else (Nkind (Citem) = N_With_Clause
15075                              and then Implicit_With (Citem))
15076                  then
15077                     null;
15078                  else
15079                     Error_Pragma
15080                       ("(Ada 83) pragma% must be at end of context clause");
15081                  end if;
15082
15083                  Next (Citem);
15084               end loop;
15085            end if;
15086
15087            --  Finally, the arguments must all be units mentioned in a with
15088            --  clause in the same context clause. Note we already checked (in
15089            --  Par.Prag) that the arguments are all identifiers or selected
15090            --  components.
15091
15092            Arg := Arg1;
15093            Outer : while Present (Arg) loop
15094               Citem := First (List_Containing (N));
15095               Inner : while Citem /= N loop
15096                  if Nkind (Citem) = N_With_Clause
15097                    and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
15098                  then
15099                     Set_Elaborate_Present (Citem, True);
15100                     Set_Elab_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
15101
15102                     --  With the pragma present, elaboration calls on
15103                     --  subprograms from the named unit need no further
15104                     --  checks, as long as the pragma appears in the current
15105                     --  compilation unit. If the pragma appears in some unit
15106                     --  in the context, there might still be a need for an
15107                     --  Elaborate_All_Desirable from the current compilation
15108                     --  to the named unit, so we keep the check enabled. This
15109                     --  does not apply in SPARK mode, where we allow pragma
15110                     --  Elaborate, but we don't trust it to be right so we
15111                     --  will still insist on the Elaborate_All.
15112
15113                     if Legacy_Elaboration_Checks
15114                       and then In_Extended_Main_Source_Unit (N)
15115                       and then SPARK_Mode /= On
15116                     then
15117                        Set_Suppress_Elaboration_Warnings
15118                          (Entity (Name (Citem)));
15119                     end if;
15120
15121                     exit Inner;
15122                  end if;
15123
15124                  Next (Citem);
15125               end loop Inner;
15126
15127               if Citem = N then
15128                  Error_Pragma_Arg
15129                    ("argument of pragma% is not withed unit", Arg);
15130               end if;
15131
15132               Next (Arg);
15133            end loop Outer;
15134         end Elaborate;
15135
15136         -------------------
15137         -- Elaborate_All --
15138         -------------------
15139
15140         --  pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
15141
15142         when Pragma_Elaborate_All => Elaborate_All : declare
15143            Arg   : Node_Id;
15144            Citem : Node_Id;
15145
15146         begin
15147            Check_Ada_83_Warning;
15148
15149            --  Pragma must be in context items list of a compilation unit
15150
15151            if not Is_In_Context_Clause then
15152               Pragma_Misplaced;
15153            end if;
15154
15155            --  Must be at least one argument
15156
15157            if Arg_Count = 0 then
15158               Error_Pragma ("pragma% requires at least one argument");
15159            end if;
15160
15161            --  Note: unlike pragma Elaborate, pragma Elaborate_All does not
15162            --  have to appear at the end of the context clause, but may
15163            --  appear mixed in with other items, even in Ada 83 mode.
15164
15165            --  Final check: the arguments must all be units mentioned in
15166            --  a with clause in the same context clause. Note that we
15167            --  already checked (in Par.Prag) that all the arguments are
15168            --  either identifiers or selected components.
15169
15170            Arg := Arg1;
15171            Outr : while Present (Arg) loop
15172               Citem := First (List_Containing (N));
15173               Innr : while Citem /= N loop
15174                  if Nkind (Citem) = N_With_Clause
15175                    and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
15176                  then
15177                     Set_Elaborate_All_Present (Citem, True);
15178                     Set_Elab_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
15179
15180                     --  Suppress warnings and elaboration checks on the named
15181                     --  unit if the pragma is in the current compilation, as
15182                     --  for pragma Elaborate.
15183
15184                     if Legacy_Elaboration_Checks
15185                       and then In_Extended_Main_Source_Unit (N)
15186                     then
15187                        Set_Suppress_Elaboration_Warnings
15188                          (Entity (Name (Citem)));
15189                     end if;
15190
15191                     exit Innr;
15192                  end if;
15193
15194                  Next (Citem);
15195               end loop Innr;
15196
15197               if Citem = N then
15198                  Set_Error_Posted (N);
15199                  Error_Pragma_Arg
15200                    ("argument of pragma% is not withed unit", Arg);
15201               end if;
15202
15203               Next (Arg);
15204            end loop Outr;
15205         end Elaborate_All;
15206
15207         --------------------
15208         -- Elaborate_Body --
15209         --------------------
15210
15211         --  pragma Elaborate_Body [( library_unit_NAME )];
15212
15213         when Pragma_Elaborate_Body => Elaborate_Body : declare
15214            Cunit_Node : Node_Id;
15215            Cunit_Ent  : Entity_Id;
15216
15217         begin
15218            Check_Ada_83_Warning;
15219            Check_Valid_Library_Unit_Pragma;
15220
15221            if Nkind (N) = N_Null_Statement then
15222               return;
15223            end if;
15224
15225            Cunit_Node := Cunit (Current_Sem_Unit);
15226            Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
15227
15228            --  A pragma that applies to a Ghost entity becomes Ghost for the
15229            --  purposes of legality checks and removal of ignored Ghost code.
15230
15231            Mark_Ghost_Pragma (N, Cunit_Ent);
15232
15233            if Nkind_In (Unit (Cunit_Node), N_Package_Body,
15234                                            N_Subprogram_Body)
15235            then
15236               Error_Pragma ("pragma% must refer to a spec, not a body");
15237            else
15238               Set_Body_Required (Cunit_Node);
15239               Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
15240
15241               --  If we are in dynamic elaboration mode, then we suppress
15242               --  elaboration warnings for the unit, since it is definitely
15243               --  fine NOT to do dynamic checks at the first level (and such
15244               --  checks will be suppressed because no elaboration boolean
15245               --  is created for Elaborate_Body packages).
15246               --
15247               --  But in the static model of elaboration, Elaborate_Body is
15248               --  definitely NOT good enough to ensure elaboration safety on
15249               --  its own, since the body may WITH other units that are not
15250               --  safe from an elaboration point of view, so a client must
15251               --  still do an Elaborate_All on such units.
15252               --
15253               --  Debug flag -gnatdD restores the old behavior of 3.13, where
15254               --  Elaborate_Body always suppressed elab warnings.
15255
15256               if Legacy_Elaboration_Checks
15257                 and then (Dynamic_Elaboration_Checks or Debug_Flag_DD)
15258               then
15259                  Set_Suppress_Elaboration_Warnings (Cunit_Ent);
15260               end if;
15261            end if;
15262         end Elaborate_Body;
15263
15264         ------------------------
15265         -- Elaboration_Checks --
15266         ------------------------
15267
15268         --  pragma Elaboration_Checks (Static | Dynamic);
15269
15270         when Pragma_Elaboration_Checks =>
15271            GNAT_Pragma;
15272            Check_Arg_Count (1);
15273            Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
15274
15275            --  Set flag accordingly (ignore attempt at dynamic elaboration
15276            --  checks in SPARK mode).
15277
15278            Dynamic_Elaboration_Checks :=
15279              Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic;
15280
15281         ---------------
15282         -- Eliminate --
15283         ---------------
15284
15285         --  pragma Eliminate (
15286         --      [Unit_Name        =>] IDENTIFIER | SELECTED_COMPONENT,
15287         --      [Entity           =>] IDENTIFIER |
15288         --                            SELECTED_COMPONENT |
15289         --                            STRING_LITERAL]
15290         --      [, Source_Location => SOURCE_TRACE]);
15291
15292         --  SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
15293         --  SOURCE_TRACE    ::= STRING_LITERAL
15294
15295         when Pragma_Eliminate => Eliminate : declare
15296            Args  : Args_List (1 .. 5);
15297            Names : constant Name_List (1 .. 5) := (
15298                      Name_Unit_Name,
15299                      Name_Entity,
15300                      Name_Parameter_Types,
15301                      Name_Result_Type,
15302                      Name_Source_Location);
15303
15304            --  Note : Parameter_Types and Result_Type are leftovers from
15305            --  prior implementations of the pragma. They are not generated
15306            --  by the gnatelim tool, and play no role in selecting which
15307            --  of a set of overloaded names is chosen for elimination.
15308
15309            Unit_Name       : Node_Id renames Args (1);
15310            Entity          : Node_Id renames Args (2);
15311            Parameter_Types : Node_Id renames Args (3);
15312            Result_Type     : Node_Id renames Args (4);
15313            Source_Location : Node_Id renames Args (5);
15314
15315         begin
15316            GNAT_Pragma;
15317            Check_Valid_Configuration_Pragma;
15318            Gather_Associations (Names, Args);
15319
15320            if No (Unit_Name) then
15321               Error_Pragma ("missing Unit_Name argument for pragma%");
15322            end if;
15323
15324            if No (Entity)
15325              and then (Present (Parameter_Types)
15326                          or else
15327                        Present (Result_Type)
15328                          or else
15329                        Present (Source_Location))
15330            then
15331               Error_Pragma ("missing Entity argument for pragma%");
15332            end if;
15333
15334            if (Present (Parameter_Types)
15335                  or else
15336                Present (Result_Type))
15337              and then
15338                Present (Source_Location)
15339            then
15340               Error_Pragma
15341                 ("parameter profile and source location cannot be used "
15342                  & "together in pragma%");
15343            end if;
15344
15345            Process_Eliminate_Pragma
15346              (N,
15347               Unit_Name,
15348               Entity,
15349               Parameter_Types,
15350               Result_Type,
15351               Source_Location);
15352         end Eliminate;
15353
15354         -----------------------------------
15355         -- Enable_Atomic_Synchronization --
15356         -----------------------------------
15357
15358         --  pragma Enable_Atomic_Synchronization [(Entity)];
15359
15360         when Pragma_Enable_Atomic_Synchronization =>
15361            GNAT_Pragma;
15362            Process_Disable_Enable_Atomic_Sync (Name_Unsuppress);
15363
15364         ------------
15365         -- Export --
15366         ------------
15367
15368         --  pragma Export (
15369         --    [   Convention    =>] convention_IDENTIFIER,
15370         --    [   Entity        =>] LOCAL_NAME
15371         --    [, [External_Name =>] static_string_EXPRESSION ]
15372         --    [, [Link_Name     =>] static_string_EXPRESSION ]);
15373
15374         when Pragma_Export => Export : declare
15375            C      : Convention_Id;
15376            Def_Id : Entity_Id;
15377
15378            pragma Warnings (Off, C);
15379
15380         begin
15381            Check_Ada_83_Warning;
15382            Check_Arg_Order
15383              ((Name_Convention,
15384                Name_Entity,
15385                Name_External_Name,
15386                Name_Link_Name));
15387
15388            Check_At_Least_N_Arguments (2);
15389            Check_At_Most_N_Arguments  (4);
15390
15391            --  In Relaxed_RM_Semantics, support old Ada 83 style:
15392            --  pragma Export (Entity, "external name");
15393
15394            if Relaxed_RM_Semantics
15395              and then Arg_Count = 2
15396              and then Nkind (Expression (Arg2)) = N_String_Literal
15397            then
15398               C := Convention_C;
15399               Def_Id := Get_Pragma_Arg (Arg1);
15400               Analyze (Def_Id);
15401
15402               if not Is_Entity_Name (Def_Id) then
15403                  Error_Pragma_Arg ("entity name required", Arg1);
15404               end if;
15405
15406               Def_Id := Entity (Def_Id);
15407               Set_Exported (Def_Id, Arg1);
15408
15409            else
15410               Process_Convention (C, Def_Id);
15411
15412               --  A pragma that applies to a Ghost entity becomes Ghost for
15413               --  the purposes of legality checks and removal of ignored Ghost
15414               --  code.
15415
15416               Mark_Ghost_Pragma (N, Def_Id);
15417
15418               if Ekind (Def_Id) /= E_Constant then
15419                  Note_Possible_Modification
15420                    (Get_Pragma_Arg (Arg2), Sure => False);
15421               end if;
15422
15423               Process_Interface_Name (Def_Id, Arg3, Arg4, N);
15424               Set_Exported (Def_Id, Arg2);
15425            end if;
15426
15427            --  If the entity is a deferred constant, propagate the information
15428            --  to the full view, because gigi elaborates the full view only.
15429
15430            if Ekind (Def_Id) = E_Constant
15431              and then Present (Full_View (Def_Id))
15432            then
15433               declare
15434                  Id2 : constant Entity_Id := Full_View (Def_Id);
15435               begin
15436                  Set_Is_Exported    (Id2, Is_Exported          (Def_Id));
15437                  Set_First_Rep_Item (Id2, First_Rep_Item       (Def_Id));
15438                  Set_Interface_Name (Id2, Einfo.Interface_Name (Def_Id));
15439               end;
15440            end if;
15441         end Export;
15442
15443         ---------------------
15444         -- Export_Function --
15445         ---------------------
15446
15447         --  pragma Export_Function (
15448         --        [Internal         =>] LOCAL_NAME
15449         --     [, [External         =>] EXTERNAL_SYMBOL]
15450         --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
15451         --     [, [Result_Type      =>] TYPE_DESIGNATOR]
15452         --     [, [Mechanism        =>] MECHANISM]
15453         --     [, [Result_Mechanism =>] MECHANISM_NAME]);
15454
15455         --  EXTERNAL_SYMBOL ::=
15456         --    IDENTIFIER
15457         --  | static_string_EXPRESSION
15458
15459         --  PARAMETER_TYPES ::=
15460         --    null
15461         --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
15462
15463         --  TYPE_DESIGNATOR ::=
15464         --    subtype_NAME
15465         --  | subtype_Name ' Access
15466
15467         --  MECHANISM ::=
15468         --    MECHANISM_NAME
15469         --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
15470
15471         --  MECHANISM_ASSOCIATION ::=
15472         --    [formal_parameter_NAME =>] MECHANISM_NAME
15473
15474         --  MECHANISM_NAME ::=
15475         --    Value
15476         --  | Reference
15477
15478         when Pragma_Export_Function => Export_Function : declare
15479            Args  : Args_List (1 .. 6);
15480            Names : constant Name_List (1 .. 6) := (
15481                      Name_Internal,
15482                      Name_External,
15483                      Name_Parameter_Types,
15484                      Name_Result_Type,
15485                      Name_Mechanism,
15486                      Name_Result_Mechanism);
15487
15488            Internal         : Node_Id renames Args (1);
15489            External         : Node_Id renames Args (2);
15490            Parameter_Types  : Node_Id renames Args (3);
15491            Result_Type      : Node_Id renames Args (4);
15492            Mechanism        : Node_Id renames Args (5);
15493            Result_Mechanism : Node_Id renames Args (6);
15494
15495         begin
15496            GNAT_Pragma;
15497            Gather_Associations (Names, Args);
15498            Process_Extended_Import_Export_Subprogram_Pragma (
15499              Arg_Internal         => Internal,
15500              Arg_External         => External,
15501              Arg_Parameter_Types  => Parameter_Types,
15502              Arg_Result_Type      => Result_Type,
15503              Arg_Mechanism        => Mechanism,
15504              Arg_Result_Mechanism => Result_Mechanism);
15505         end Export_Function;
15506
15507         -------------------
15508         -- Export_Object --
15509         -------------------
15510
15511         --  pragma Export_Object (
15512         --        [Internal =>] LOCAL_NAME
15513         --     [, [External =>] EXTERNAL_SYMBOL]
15514         --     [, [Size     =>] EXTERNAL_SYMBOL]);
15515
15516         --  EXTERNAL_SYMBOL ::=
15517         --    IDENTIFIER
15518         --  | static_string_EXPRESSION
15519
15520         --  PARAMETER_TYPES ::=
15521         --    null
15522         --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
15523
15524         --  TYPE_DESIGNATOR ::=
15525         --    subtype_NAME
15526         --  | subtype_Name ' Access
15527
15528         --  MECHANISM ::=
15529         --    MECHANISM_NAME
15530         --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
15531
15532         --  MECHANISM_ASSOCIATION ::=
15533         --    [formal_parameter_NAME =>] MECHANISM_NAME
15534
15535         --  MECHANISM_NAME ::=
15536         --    Value
15537         --  | Reference
15538
15539         when Pragma_Export_Object => Export_Object : declare
15540            Args  : Args_List (1 .. 3);
15541            Names : constant Name_List (1 .. 3) := (
15542                      Name_Internal,
15543                      Name_External,
15544                      Name_Size);
15545
15546            Internal : Node_Id renames Args (1);
15547            External : Node_Id renames Args (2);
15548            Size     : Node_Id renames Args (3);
15549
15550         begin
15551            GNAT_Pragma;
15552            Gather_Associations (Names, Args);
15553            Process_Extended_Import_Export_Object_Pragma (
15554              Arg_Internal => Internal,
15555              Arg_External => External,
15556              Arg_Size     => Size);
15557         end Export_Object;
15558
15559         ----------------------
15560         -- Export_Procedure --
15561         ----------------------
15562
15563         --  pragma Export_Procedure (
15564         --        [Internal         =>] LOCAL_NAME
15565         --     [, [External         =>] EXTERNAL_SYMBOL]
15566         --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
15567         --     [, [Mechanism        =>] MECHANISM]);
15568
15569         --  EXTERNAL_SYMBOL ::=
15570         --    IDENTIFIER
15571         --  | static_string_EXPRESSION
15572
15573         --  PARAMETER_TYPES ::=
15574         --    null
15575         --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
15576
15577         --  TYPE_DESIGNATOR ::=
15578         --    subtype_NAME
15579         --  | subtype_Name ' Access
15580
15581         --  MECHANISM ::=
15582         --    MECHANISM_NAME
15583         --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
15584
15585         --  MECHANISM_ASSOCIATION ::=
15586         --    [formal_parameter_NAME =>] MECHANISM_NAME
15587
15588         --  MECHANISM_NAME ::=
15589         --    Value
15590         --  | Reference
15591
15592         when Pragma_Export_Procedure => Export_Procedure : declare
15593            Args  : Args_List (1 .. 4);
15594            Names : constant Name_List (1 .. 4) := (
15595                      Name_Internal,
15596                      Name_External,
15597                      Name_Parameter_Types,
15598                      Name_Mechanism);
15599
15600            Internal        : Node_Id renames Args (1);
15601            External        : Node_Id renames Args (2);
15602            Parameter_Types : Node_Id renames Args (3);
15603            Mechanism       : Node_Id renames Args (4);
15604
15605         begin
15606            GNAT_Pragma;
15607            Gather_Associations (Names, Args);
15608            Process_Extended_Import_Export_Subprogram_Pragma (
15609              Arg_Internal        => Internal,
15610              Arg_External        => External,
15611              Arg_Parameter_Types => Parameter_Types,
15612              Arg_Mechanism       => Mechanism);
15613         end Export_Procedure;
15614
15615         ------------------
15616         -- Export_Value --
15617         ------------------
15618
15619         --  pragma Export_Value (
15620         --     [Value     =>] static_integer_EXPRESSION,
15621         --     [Link_Name =>] static_string_EXPRESSION);
15622
15623         when Pragma_Export_Value =>
15624            GNAT_Pragma;
15625            Check_Arg_Order ((Name_Value, Name_Link_Name));
15626            Check_Arg_Count (2);
15627
15628            Check_Optional_Identifier (Arg1, Name_Value);
15629            Check_Arg_Is_OK_Static_Expression (Arg1, Any_Integer);
15630
15631            Check_Optional_Identifier (Arg2, Name_Link_Name);
15632            Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
15633
15634         -----------------------------
15635         -- Export_Valued_Procedure --
15636         -----------------------------
15637
15638         --  pragma Export_Valued_Procedure (
15639         --        [Internal         =>] LOCAL_NAME
15640         --     [, [External         =>] EXTERNAL_SYMBOL,]
15641         --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
15642         --     [, [Mechanism        =>] MECHANISM]);
15643
15644         --  EXTERNAL_SYMBOL ::=
15645         --    IDENTIFIER
15646         --  | static_string_EXPRESSION
15647
15648         --  PARAMETER_TYPES ::=
15649         --    null
15650         --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
15651
15652         --  TYPE_DESIGNATOR ::=
15653         --    subtype_NAME
15654         --  | subtype_Name ' Access
15655
15656         --  MECHANISM ::=
15657         --    MECHANISM_NAME
15658         --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
15659
15660         --  MECHANISM_ASSOCIATION ::=
15661         --    [formal_parameter_NAME =>] MECHANISM_NAME
15662
15663         --  MECHANISM_NAME ::=
15664         --    Value
15665         --  | Reference
15666
15667         when Pragma_Export_Valued_Procedure =>
15668         Export_Valued_Procedure : declare
15669            Args  : Args_List (1 .. 4);
15670            Names : constant Name_List (1 .. 4) := (
15671                      Name_Internal,
15672                      Name_External,
15673                      Name_Parameter_Types,
15674                      Name_Mechanism);
15675
15676            Internal        : Node_Id renames Args (1);
15677            External        : Node_Id renames Args (2);
15678            Parameter_Types : Node_Id renames Args (3);
15679            Mechanism       : Node_Id renames Args (4);
15680
15681         begin
15682            GNAT_Pragma;
15683            Gather_Associations (Names, Args);
15684            Process_Extended_Import_Export_Subprogram_Pragma (
15685              Arg_Internal        => Internal,
15686              Arg_External        => External,
15687              Arg_Parameter_Types => Parameter_Types,
15688              Arg_Mechanism       => Mechanism);
15689         end Export_Valued_Procedure;
15690
15691         -------------------
15692         -- Extend_System --
15693         -------------------
15694
15695         --  pragma Extend_System ([Name =>] Identifier);
15696
15697         when Pragma_Extend_System =>
15698            GNAT_Pragma;
15699            Check_Valid_Configuration_Pragma;
15700            Check_Arg_Count (1);
15701            Check_Optional_Identifier (Arg1, Name_Name);
15702            Check_Arg_Is_Identifier (Arg1);
15703
15704            Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
15705
15706            if Name_Len > 4
15707              and then Name_Buffer (1 .. 4) = "aux_"
15708            then
15709               if Present (System_Extend_Pragma_Arg) then
15710                  if Chars (Get_Pragma_Arg (Arg1)) =
15711                     Chars (Expression (System_Extend_Pragma_Arg))
15712                  then
15713                     null;
15714                  else
15715                     Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
15716                     Error_Pragma ("pragma% conflicts with that #");
15717                  end if;
15718
15719               else
15720                  System_Extend_Pragma_Arg := Arg1;
15721
15722                  if not GNAT_Mode then
15723                     System_Extend_Unit := Arg1;
15724                  end if;
15725               end if;
15726            else
15727               Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
15728            end if;
15729
15730         ------------------------
15731         -- Extensions_Allowed --
15732         ------------------------
15733
15734         --  pragma Extensions_Allowed (ON | OFF);
15735
15736         when Pragma_Extensions_Allowed =>
15737            GNAT_Pragma;
15738            Check_Arg_Count (1);
15739            Check_No_Identifiers;
15740            Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
15741
15742            if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
15743               Extensions_Allowed := True;
15744               Ada_Version := Ada_Version_Type'Last;
15745
15746            else
15747               Extensions_Allowed := False;
15748               Ada_Version := Ada_Version_Explicit;
15749               Ada_Version_Pragma := Empty;
15750            end if;
15751
15752         ------------------------
15753         -- Extensions_Visible --
15754         ------------------------
15755
15756         --  pragma Extensions_Visible [ (boolean_EXPRESSION) ];
15757
15758         --  Characteristics:
15759
15760         --    * Analysis - The annotation is fully analyzed immediately upon
15761         --    elaboration as its expression must be static.
15762
15763         --    * Expansion - None.
15764
15765         --    * Template - The annotation utilizes the generic template of the
15766         --    related subprogram [body] when it is:
15767
15768         --       aspect on subprogram declaration
15769         --       aspect on stand-alone subprogram body
15770         --       pragma on stand-alone subprogram body
15771
15772         --    The annotation must prepare its own template when it is:
15773
15774         --       pragma on subprogram declaration
15775
15776         --    * Globals - Capture of global references must occur after full
15777         --    analysis.
15778
15779         --    * Instance - The annotation is instantiated automatically when
15780         --    the related generic subprogram [body] is instantiated except for
15781         --    the "pragma on subprogram declaration" case. In that scenario
15782         --    the annotation must instantiate itself.
15783
15784         when Pragma_Extensions_Visible => Extensions_Visible : declare
15785            Formal        : Entity_Id;
15786            Has_OK_Formal : Boolean := False;
15787            Spec_Id       : Entity_Id;
15788            Subp_Decl     : Node_Id;
15789
15790         begin
15791            GNAT_Pragma;
15792            Check_No_Identifiers;
15793            Check_At_Most_N_Arguments (1);
15794
15795            Subp_Decl :=
15796              Find_Related_Declaration_Or_Body (N, Do_Checks => True);
15797
15798            --  Abstract subprogram declaration
15799
15800            if Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
15801               null;
15802
15803            --  Generic subprogram declaration
15804
15805            elsif Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
15806               null;
15807
15808            --  Body acts as spec
15809
15810            elsif Nkind (Subp_Decl) = N_Subprogram_Body
15811              and then No (Corresponding_Spec (Subp_Decl))
15812            then
15813               null;
15814
15815            --  Body stub acts as spec
15816
15817            elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
15818              and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
15819            then
15820               null;
15821
15822            --  Subprogram declaration
15823
15824            elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
15825               null;
15826
15827            --  Otherwise the pragma is associated with an illegal construct
15828
15829            else
15830               Error_Pragma ("pragma % must apply to a subprogram");
15831               return;
15832            end if;
15833
15834            --  Mark the pragma as Ghost if the related subprogram is also
15835            --  Ghost. This also ensures that any expansion performed further
15836            --  below will produce Ghost nodes.
15837
15838            Spec_Id := Unique_Defining_Entity (Subp_Decl);
15839            Mark_Ghost_Pragma (N, Spec_Id);
15840
15841            --  Chain the pragma on the contract for completeness
15842
15843            Add_Contract_Item (N, Defining_Entity (Subp_Decl));
15844
15845            --  The legality checks of pragma Extension_Visible are affected
15846            --  by the SPARK mode in effect. Analyze all pragmas in specific
15847            --  order.
15848
15849            Analyze_If_Present (Pragma_SPARK_Mode);
15850
15851            --  Examine the formals of the related subprogram
15852
15853            Formal := First_Formal (Spec_Id);
15854            while Present (Formal) loop
15855
15856               --  At least one of the formals is of a specific tagged type,
15857               --  the pragma is legal.
15858
15859               if Is_Specific_Tagged_Type (Etype (Formal)) then
15860                  Has_OK_Formal := True;
15861                  exit;
15862
15863               --  A generic subprogram with at least one formal of a private
15864               --  type ensures the legality of the pragma because the actual
15865               --  may be specifically tagged. Note that this is verified by
15866               --  the check above at instantiation time.
15867
15868               elsif Is_Private_Type (Etype (Formal))
15869                 and then Is_Generic_Type (Etype (Formal))
15870               then
15871                  Has_OK_Formal := True;
15872                  exit;
15873               end if;
15874
15875               Next_Formal (Formal);
15876            end loop;
15877
15878            if not Has_OK_Formal then
15879               Error_Msg_Name_1 := Pname;
15880               Error_Msg_N (Fix_Error ("incorrect placement of pragma %"), N);
15881               Error_Msg_NE
15882                 ("\subprogram & lacks parameter of specific tagged or "
15883                  & "generic private type", N, Spec_Id);
15884
15885               return;
15886            end if;
15887
15888            --  Analyze the Boolean expression (if any)
15889
15890            if Present (Arg1) then
15891               Check_Static_Boolean_Expression
15892                 (Expression (Get_Argument (N, Spec_Id)));
15893            end if;
15894         end Extensions_Visible;
15895
15896         --------------
15897         -- External --
15898         --------------
15899
15900         --  pragma External (
15901         --    [   Convention    =>] convention_IDENTIFIER,
15902         --    [   Entity        =>] LOCAL_NAME
15903         --    [, [External_Name =>] static_string_EXPRESSION ]
15904         --    [, [Link_Name     =>] static_string_EXPRESSION ]);
15905
15906         when Pragma_External => External : declare
15907            C : Convention_Id;
15908            E : Entity_Id;
15909            pragma Warnings (Off, C);
15910
15911         begin
15912            GNAT_Pragma;
15913            Check_Arg_Order
15914              ((Name_Convention,
15915                Name_Entity,
15916                Name_External_Name,
15917                Name_Link_Name));
15918            Check_At_Least_N_Arguments (2);
15919            Check_At_Most_N_Arguments  (4);
15920            Process_Convention (C, E);
15921
15922            --  A pragma that applies to a Ghost entity becomes Ghost for the
15923            --  purposes of legality checks and removal of ignored Ghost code.
15924
15925            Mark_Ghost_Pragma (N, E);
15926
15927            Note_Possible_Modification
15928              (Get_Pragma_Arg (Arg2), Sure => False);
15929            Process_Interface_Name (E, Arg3, Arg4, N);
15930            Set_Exported (E, Arg2);
15931         end External;
15932
15933         --------------------------
15934         -- External_Name_Casing --
15935         --------------------------
15936
15937         --  pragma External_Name_Casing (
15938         --    UPPERCASE | LOWERCASE
15939         --    [, AS_IS | UPPERCASE | LOWERCASE]);
15940
15941         when Pragma_External_Name_Casing =>
15942            GNAT_Pragma;
15943            Check_No_Identifiers;
15944
15945            if Arg_Count = 2 then
15946               Check_Arg_Is_One_Of
15947                 (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
15948
15949               case Chars (Get_Pragma_Arg (Arg2)) is
15950                  when Name_As_Is     =>
15951                     Opt.External_Name_Exp_Casing := As_Is;
15952
15953                  when Name_Uppercase =>
15954                     Opt.External_Name_Exp_Casing := Uppercase;
15955
15956                  when Name_Lowercase =>
15957                     Opt.External_Name_Exp_Casing := Lowercase;
15958
15959                  when others =>
15960                     null;
15961               end case;
15962
15963            else
15964               Check_Arg_Count (1);
15965            end if;
15966
15967            Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
15968
15969            case Chars (Get_Pragma_Arg (Arg1)) is
15970               when Name_Uppercase =>
15971                  Opt.External_Name_Imp_Casing := Uppercase;
15972
15973               when Name_Lowercase =>
15974                  Opt.External_Name_Imp_Casing := Lowercase;
15975
15976               when others =>
15977                  null;
15978            end case;
15979
15980         ---------------
15981         -- Fast_Math --
15982         ---------------
15983
15984         --  pragma Fast_Math;
15985
15986         when Pragma_Fast_Math =>
15987            GNAT_Pragma;
15988            Check_No_Identifiers;
15989            Check_Valid_Configuration_Pragma;
15990            Fast_Math := True;
15991
15992         --------------------------
15993         -- Favor_Top_Level --
15994         --------------------------
15995
15996         --  pragma Favor_Top_Level (type_NAME);
15997
15998         when Pragma_Favor_Top_Level => Favor_Top_Level : declare
15999            Typ : Entity_Id;
16000
16001         begin
16002            GNAT_Pragma;
16003            Check_No_Identifiers;
16004            Check_Arg_Count (1);
16005            Check_Arg_Is_Local_Name (Arg1);
16006            Typ := Entity (Get_Pragma_Arg (Arg1));
16007
16008            --  A pragma that applies to a Ghost entity becomes Ghost for the
16009            --  purposes of legality checks and removal of ignored Ghost code.
16010
16011            Mark_Ghost_Pragma (N, Typ);
16012
16013            --  If it's an access-to-subprogram type (in particular, not a
16014            --  subtype), set the flag on that type.
16015
16016            if Is_Access_Subprogram_Type (Typ) then
16017               Set_Can_Use_Internal_Rep (Typ, False);
16018
16019            --  Otherwise it's an error (name denotes the wrong sort of entity)
16020
16021            else
16022               Error_Pragma_Arg
16023                 ("access-to-subprogram type expected",
16024                  Get_Pragma_Arg (Arg1));
16025            end if;
16026         end Favor_Top_Level;
16027
16028         ---------------------------
16029         -- Finalize_Storage_Only --
16030         ---------------------------
16031
16032         --  pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
16033
16034         when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
16035            Assoc   : constant Node_Id := Arg1;
16036            Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
16037            Typ     : Entity_Id;
16038
16039         begin
16040            GNAT_Pragma;
16041            Check_No_Identifiers;
16042            Check_Arg_Count (1);
16043            Check_Arg_Is_Local_Name (Arg1);
16044
16045            Find_Type (Type_Id);
16046            Typ := Entity (Type_Id);
16047
16048            if Typ = Any_Type
16049              or else Rep_Item_Too_Early (Typ, N)
16050            then
16051               return;
16052            else
16053               Typ := Underlying_Type (Typ);
16054            end if;
16055
16056            if not Is_Controlled (Typ) then
16057               Error_Pragma ("pragma% must specify controlled type");
16058            end if;
16059
16060            Check_First_Subtype (Arg1);
16061
16062            if Finalize_Storage_Only (Typ) then
16063               Error_Pragma ("duplicate pragma%, only one allowed");
16064
16065            elsif not Rep_Item_Too_Late (Typ, N) then
16066               Set_Finalize_Storage_Only (Base_Type (Typ), True);
16067            end if;
16068         end Finalize_Storage;
16069
16070         -----------
16071         -- Ghost --
16072         -----------
16073
16074         --  pragma Ghost [ (boolean_EXPRESSION) ];
16075
16076         when Pragma_Ghost => Ghost : declare
16077            Context   : Node_Id;
16078            Expr      : Node_Id;
16079            Id        : Entity_Id;
16080            Orig_Stmt : Node_Id;
16081            Prev_Id   : Entity_Id;
16082            Stmt      : Node_Id;
16083
16084         begin
16085            GNAT_Pragma;
16086            Check_No_Identifiers;
16087            Check_At_Most_N_Arguments (1);
16088
16089            Id   := Empty;
16090            Stmt := Prev (N);
16091            while Present (Stmt) loop
16092
16093               --  Skip prior pragmas, but check for duplicates
16094
16095               if Nkind (Stmt) = N_Pragma then
16096                  if Pragma_Name (Stmt) = Pname then
16097                     Duplication_Error
16098                       (Prag => N,
16099                        Prev => Stmt);
16100                     raise Pragma_Exit;
16101                  end if;
16102
16103               --  Task unit declared without a definition cannot be subject to
16104               --  pragma Ghost (SPARK RM 6.9(19)).
16105
16106               elsif Nkind_In (Stmt, N_Single_Task_Declaration,
16107                                     N_Task_Type_Declaration)
16108               then
16109                  Error_Pragma ("pragma % cannot apply to a task type");
16110                  return;
16111
16112               --  Skip internally generated code
16113
16114               elsif not Comes_From_Source (Stmt) then
16115                  Orig_Stmt := Original_Node (Stmt);
16116
16117                  --  When pragma Ghost applies to an untagged derivation, the
16118                  --  derivation is transformed into a [sub]type declaration.
16119
16120                  if Nkind_In (Stmt, N_Full_Type_Declaration,
16121                                     N_Subtype_Declaration)
16122                    and then Comes_From_Source (Orig_Stmt)
16123                    and then Nkind (Orig_Stmt) = N_Full_Type_Declaration
16124                    and then Nkind (Type_Definition (Orig_Stmt)) =
16125                               N_Derived_Type_Definition
16126                  then
16127                     Id := Defining_Entity (Stmt);
16128                     exit;
16129
16130                  --  When pragma Ghost applies to an object declaration which
16131                  --  is initialized by means of a function call that returns
16132                  --  on the secondary stack, the object declaration becomes a
16133                  --  renaming.
16134
16135                  elsif Nkind (Stmt) = N_Object_Renaming_Declaration
16136                    and then Comes_From_Source (Orig_Stmt)
16137                    and then Nkind (Orig_Stmt) = N_Object_Declaration
16138                  then
16139                     Id := Defining_Entity (Stmt);
16140                     exit;
16141
16142                  --  When pragma Ghost applies to an expression function, the
16143                  --  expression function is transformed into a subprogram.
16144
16145                  elsif Nkind (Stmt) = N_Subprogram_Declaration
16146                    and then Comes_From_Source (Orig_Stmt)
16147                    and then Nkind (Orig_Stmt) = N_Expression_Function
16148                  then
16149                     Id := Defining_Entity (Stmt);
16150                     exit;
16151                  end if;
16152
16153               --  The pragma applies to a legal construct, stop the traversal
16154
16155               elsif Nkind_In (Stmt, N_Abstract_Subprogram_Declaration,
16156                                     N_Full_Type_Declaration,
16157                                     N_Generic_Subprogram_Declaration,
16158                                     N_Object_Declaration,
16159                                     N_Private_Extension_Declaration,
16160                                     N_Private_Type_Declaration,
16161                                     N_Subprogram_Declaration,
16162                                     N_Subtype_Declaration)
16163               then
16164                  Id := Defining_Entity (Stmt);
16165                  exit;
16166
16167               --  The pragma does not apply to a legal construct, issue an
16168               --  error and stop the analysis.
16169
16170               else
16171                  Error_Pragma
16172                    ("pragma % must apply to an object, package, subprogram "
16173                     & "or type");
16174                  return;
16175               end if;
16176
16177               Stmt := Prev (Stmt);
16178            end loop;
16179
16180            Context := Parent (N);
16181
16182            --  Handle compilation units
16183
16184            if Nkind (Context) = N_Compilation_Unit_Aux then
16185               Context := Unit (Parent (Context));
16186            end if;
16187
16188            --  Protected and task types cannot be subject to pragma Ghost
16189            --  (SPARK RM 6.9(19)).
16190
16191            if Nkind_In (Context, N_Protected_Body, N_Protected_Definition)
16192            then
16193               Error_Pragma ("pragma % cannot apply to a protected type");
16194               return;
16195
16196            elsif Nkind_In (Context, N_Task_Body, N_Task_Definition) then
16197               Error_Pragma ("pragma % cannot apply to a task type");
16198               return;
16199            end if;
16200
16201            if No (Id) then
16202
16203               --  When pragma Ghost is associated with a [generic] package, it
16204               --  appears in the visible declarations.
16205
16206               if Nkind (Context) = N_Package_Specification
16207                 and then Present (Visible_Declarations (Context))
16208                 and then List_Containing (N) = Visible_Declarations (Context)
16209               then
16210                  Id := Defining_Entity (Context);
16211
16212               --  Pragma Ghost applies to a stand-alone subprogram body
16213
16214               elsif Nkind (Context) = N_Subprogram_Body
16215                 and then No (Corresponding_Spec (Context))
16216               then
16217                  Id := Defining_Entity (Context);
16218
16219               --  Pragma Ghost applies to a subprogram declaration that acts
16220               --  as a compilation unit.
16221
16222               elsif Nkind (Context) = N_Subprogram_Declaration then
16223                  Id := Defining_Entity (Context);
16224
16225               --  Pragma Ghost applies to a generic subprogram
16226
16227               elsif Nkind (Context) = N_Generic_Subprogram_Declaration then
16228                  Id := Defining_Entity (Specification (Context));
16229               end if;
16230            end if;
16231
16232            if No (Id) then
16233               Error_Pragma
16234                 ("pragma % must apply to an object, package, subprogram or "
16235                  & "type");
16236               return;
16237            end if;
16238
16239            --  Handle completions of types and constants that are subject to
16240            --  pragma Ghost.
16241
16242            if Is_Record_Type (Id) or else Ekind (Id) = E_Constant then
16243               Prev_Id := Incomplete_Or_Partial_View (Id);
16244
16245               if Present (Prev_Id) and then not Is_Ghost_Entity (Prev_Id) then
16246                  Error_Msg_Name_1 := Pname;
16247
16248                  --  The full declaration of a deferred constant cannot be
16249                  --  subject to pragma Ghost unless the deferred declaration
16250                  --  is also Ghost (SPARK RM 6.9(9)).
16251
16252                  if Ekind (Prev_Id) = E_Constant then
16253                     Error_Msg_Name_1 := Pname;
16254                     Error_Msg_NE (Fix_Error
16255                       ("pragma % must apply to declaration of deferred "
16256                        & "constant &"), N, Id);
16257                     return;
16258
16259                  --  Pragma Ghost may appear on the full view of an incomplete
16260                  --  type because the incomplete declaration lacks aspects and
16261                  --  cannot be subject to pragma Ghost.
16262
16263                  elsif Ekind (Prev_Id) = E_Incomplete_Type then
16264                     null;
16265
16266                  --  The full declaration of a type cannot be subject to
16267                  --  pragma Ghost unless the partial view is also Ghost
16268                  --  (SPARK RM 6.9(9)).
16269
16270                  else
16271                     Error_Msg_NE (Fix_Error
16272                       ("pragma % must apply to partial view of type &"),
16273                        N, Id);
16274                     return;
16275                  end if;
16276               end if;
16277
16278            --  A synchronized object cannot be subject to pragma Ghost
16279            --  (SPARK RM 6.9(19)).
16280
16281            elsif Ekind (Id) = E_Variable then
16282               if Is_Protected_Type (Etype (Id)) then
16283                  Error_Pragma ("pragma % cannot apply to a protected object");
16284                  return;
16285
16286               elsif Is_Task_Type (Etype (Id)) then
16287                  Error_Pragma ("pragma % cannot apply to a task object");
16288                  return;
16289               end if;
16290            end if;
16291
16292            --  Analyze the Boolean expression (if any)
16293
16294            if Present (Arg1) then
16295               Expr := Get_Pragma_Arg (Arg1);
16296
16297               Analyze_And_Resolve (Expr, Standard_Boolean);
16298
16299               if Is_OK_Static_Expression (Expr) then
16300
16301                  --  "Ghostness" cannot be turned off once enabled within a
16302                  --  region (SPARK RM 6.9(6)).
16303
16304                  if Is_False (Expr_Value (Expr))
16305                    and then Ghost_Mode > None
16306                  then
16307                     Error_Pragma
16308                       ("pragma % with value False cannot appear in enabled "
16309                        & "ghost region");
16310                     return;
16311                  end if;
16312
16313               --  Otherwie the expression is not static
16314
16315               else
16316                  Error_Pragma_Arg
16317                    ("expression of pragma % must be static", Expr);
16318                  return;
16319               end if;
16320            end if;
16321
16322            Set_Is_Ghost_Entity (Id);
16323         end Ghost;
16324
16325         ------------
16326         -- Global --
16327         ------------
16328
16329         --  pragma Global (GLOBAL_SPECIFICATION);
16330
16331         --  GLOBAL_SPECIFICATION ::=
16332         --     null
16333         --  | (GLOBAL_LIST)
16334         --  | (MODED_GLOBAL_LIST {, MODED_GLOBAL_LIST})
16335
16336         --  MODED_GLOBAL_LIST ::= MODE_SELECTOR => GLOBAL_LIST
16337
16338         --  MODE_SELECTOR ::= In_Out | Input | Output | Proof_In
16339         --  GLOBAL_LIST   ::= GLOBAL_ITEM | (GLOBAL_ITEM {, GLOBAL_ITEM})
16340         --  GLOBAL_ITEM   ::= NAME
16341
16342         --  Characteristics:
16343
16344         --    * Analysis - The annotation undergoes initial checks to verify
16345         --    the legal placement and context. Secondary checks fully analyze
16346         --    the dependency clauses in:
16347
16348         --       Analyze_Global_In_Decl_Part
16349
16350         --    * Expansion - None.
16351
16352         --    * Template - The annotation utilizes the generic template of the
16353         --    related subprogram [body] when it is:
16354
16355         --       aspect on subprogram declaration
16356         --       aspect on stand-alone subprogram body
16357         --       pragma on stand-alone subprogram body
16358
16359         --    The annotation must prepare its own template when it is:
16360
16361         --       pragma on subprogram declaration
16362
16363         --    * Globals - Capture of global references must occur after full
16364         --    analysis.
16365
16366         --    * Instance - The annotation is instantiated automatically when
16367         --    the related generic subprogram [body] is instantiated except for
16368         --    the "pragma on subprogram declaration" case. In that scenario
16369         --    the annotation must instantiate itself.
16370
16371         when Pragma_Global => Global : declare
16372            Legal     : Boolean;
16373            Spec_Id   : Entity_Id;
16374            Subp_Decl : Node_Id;
16375
16376         begin
16377            Analyze_Depends_Global (Spec_Id, Subp_Decl, Legal);
16378
16379            if Legal then
16380
16381               --  Chain the pragma on the contract for further processing by
16382               --  Analyze_Global_In_Decl_Part.
16383
16384               Add_Contract_Item (N, Spec_Id);
16385
16386               --  Fully analyze the pragma when it appears inside an entry
16387               --  or subprogram body because it cannot benefit from forward
16388               --  references.
16389
16390               if Nkind_In (Subp_Decl, N_Entry_Body,
16391                                       N_Subprogram_Body,
16392                                       N_Subprogram_Body_Stub)
16393               then
16394                  --  The legality checks of pragmas Depends and Global are
16395                  --  affected by the SPARK mode in effect and the volatility
16396                  --  of the context. In addition these two pragmas are subject
16397                  --  to an inherent order:
16398
16399                  --    1) Global
16400                  --    2) Depends
16401
16402                  --  Analyze all these pragmas in the order outlined above
16403
16404                  Analyze_If_Present (Pragma_SPARK_Mode);
16405                  Analyze_If_Present (Pragma_Volatile_Function);
16406                  Analyze_Global_In_Decl_Part (N);
16407                  Analyze_If_Present (Pragma_Depends);
16408               end if;
16409            end if;
16410         end Global;
16411
16412         -----------
16413         -- Ident --
16414         -----------
16415
16416         --  pragma Ident (static_string_EXPRESSION)
16417
16418         --  Note: pragma Comment shares this processing. Pragma Ident is
16419         --  identical in effect to pragma Commment.
16420
16421         when Pragma_Comment
16422            | Pragma_Ident
16423         =>
16424         Ident : declare
16425            Str : Node_Id;
16426
16427         begin
16428            GNAT_Pragma;
16429            Check_Arg_Count (1);
16430            Check_No_Identifiers;
16431            Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
16432            Store_Note (N);
16433
16434            Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
16435
16436            declare
16437               CS : Node_Id;
16438               GP : Node_Id;
16439
16440            begin
16441               GP := Parent (Parent (N));
16442
16443               if Nkind_In (GP, N_Package_Declaration,
16444                                N_Generic_Package_Declaration)
16445               then
16446                  GP := Parent (GP);
16447               end if;
16448
16449               --  If we have a compilation unit, then record the ident value,
16450               --  checking for improper duplication.
16451
16452               if Nkind (GP) = N_Compilation_Unit then
16453                  CS := Ident_String (Current_Sem_Unit);
16454
16455                  if Present (CS) then
16456
16457                     --  If we have multiple instances, concatenate them, but
16458                     --  not in ASIS, where we want the original tree.
16459
16460                     if not ASIS_Mode then
16461                        Start_String (Strval (CS));
16462                        Store_String_Char (' ');
16463                        Store_String_Chars (Strval (Str));
16464                        Set_Strval (CS, End_String);
16465                     end if;
16466
16467                  else
16468                     Set_Ident_String (Current_Sem_Unit, Str);
16469                  end if;
16470
16471               --  For subunits, we just ignore the Ident, since in GNAT these
16472               --  are not separate object files, and hence not separate units
16473               --  in the unit table.
16474
16475               elsif Nkind (GP) = N_Subunit then
16476                  null;
16477               end if;
16478            end;
16479         end Ident;
16480
16481         -------------------
16482         -- Ignore_Pragma --
16483         -------------------
16484
16485         --  pragma Ignore_Pragma (pragma_IDENTIFIER);
16486
16487         --  Entirely handled in the parser, nothing to do here
16488
16489         when Pragma_Ignore_Pragma =>
16490            null;
16491
16492         ----------------------------
16493         -- Implementation_Defined --
16494         ----------------------------
16495
16496         --  pragma Implementation_Defined (LOCAL_NAME);
16497
16498         --  Marks previously declared entity as implementation defined. For
16499         --  an overloaded entity, applies to the most recent homonym.
16500
16501         --  pragma Implementation_Defined;
16502
16503         --  The form with no arguments appears anywhere within a scope, most
16504         --  typically a package spec, and indicates that all entities that are
16505         --  defined within the package spec are Implementation_Defined.
16506
16507         when Pragma_Implementation_Defined => Implementation_Defined : declare
16508            Ent : Entity_Id;
16509
16510         begin
16511            GNAT_Pragma;
16512            Check_No_Identifiers;
16513
16514            --  Form with no arguments
16515
16516            if Arg_Count = 0 then
16517               Set_Is_Implementation_Defined (Current_Scope);
16518
16519            --  Form with one argument
16520
16521            else
16522               Check_Arg_Count (1);
16523               Check_Arg_Is_Local_Name (Arg1);
16524               Ent := Entity (Get_Pragma_Arg (Arg1));
16525               Set_Is_Implementation_Defined (Ent);
16526            end if;
16527         end Implementation_Defined;
16528
16529         -----------------
16530         -- Implemented --
16531         -----------------
16532
16533         --  pragma Implemented (procedure_LOCAL_NAME, IMPLEMENTATION_KIND);
16534
16535         --  IMPLEMENTATION_KIND ::=
16536         --    By_Entry | By_Protected_Procedure | By_Any | Optional
16537
16538         --  "By_Any" and "Optional" are treated as synonyms in order to
16539         --  support Ada 2012 aspect Synchronization.
16540
16541         when Pragma_Implemented => Implemented : declare
16542            Proc_Id : Entity_Id;
16543            Typ     : Entity_Id;
16544
16545         begin
16546            Ada_2012_Pragma;
16547            Check_Arg_Count (2);
16548            Check_No_Identifiers;
16549            Check_Arg_Is_Identifier (Arg1);
16550            Check_Arg_Is_Local_Name (Arg1);
16551            Check_Arg_Is_One_Of (Arg2,
16552              Name_By_Any,
16553              Name_By_Entry,
16554              Name_By_Protected_Procedure,
16555              Name_Optional);
16556
16557            --  Extract the name of the local procedure
16558
16559            Proc_Id := Entity (Get_Pragma_Arg (Arg1));
16560
16561            --  Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
16562            --  primitive procedure of a synchronized tagged type.
16563
16564            if Ekind (Proc_Id) = E_Procedure
16565              and then Is_Primitive (Proc_Id)
16566              and then Present (First_Formal (Proc_Id))
16567            then
16568               Typ := Etype (First_Formal (Proc_Id));
16569
16570               if Is_Tagged_Type (Typ)
16571                 and then
16572
16573                  --  Check for a protected, a synchronized or a task interface
16574
16575                   ((Is_Interface (Typ)
16576                       and then Is_Synchronized_Interface (Typ))
16577
16578                  --  Check for a protected type or a task type that implements
16579                  --  an interface.
16580
16581                   or else
16582                    (Is_Concurrent_Record_Type (Typ)
16583                       and then Present (Interfaces (Typ)))
16584
16585                  --  In analysis-only mode, examine original protected type
16586
16587                  or else
16588                    (Nkind (Parent (Typ)) = N_Protected_Type_Declaration
16589                      and then Present (Interface_List (Parent (Typ))))
16590
16591                  --  Check for a private record extension with keyword
16592                  --  "synchronized".
16593
16594                   or else
16595                    (Ekind_In (Typ, E_Record_Type_With_Private,
16596                                    E_Record_Subtype_With_Private)
16597                       and then Synchronized_Present (Parent (Typ))))
16598               then
16599                  null;
16600               else
16601                  Error_Pragma_Arg
16602                    ("controlling formal must be of synchronized tagged type",
16603                     Arg1);
16604                  return;
16605               end if;
16606
16607               --  Ada 2012 (AI05-0030): Cannot apply the implementation_kind
16608               --  By_Protected_Procedure to the primitive procedure of a task
16609               --  interface.
16610
16611               if Chars (Arg2) = Name_By_Protected_Procedure
16612                 and then Is_Interface (Typ)
16613                 and then Is_Task_Interface (Typ)
16614               then
16615                  Error_Pragma_Arg
16616                    ("implementation kind By_Protected_Procedure cannot be "
16617                     & "applied to a task interface primitive", Arg2);
16618                  return;
16619               end if;
16620
16621            --  Procedures declared inside a protected type must be accepted
16622
16623            elsif Ekind (Proc_Id) = E_Procedure
16624              and then Is_Protected_Type (Scope (Proc_Id))
16625            then
16626               null;
16627
16628            --  The first argument is not a primitive procedure
16629
16630            else
16631               Error_Pragma_Arg
16632                 ("pragma % must be applied to a primitive procedure", Arg1);
16633               return;
16634            end if;
16635
16636            Record_Rep_Item (Proc_Id, N);
16637         end Implemented;
16638
16639         ----------------------
16640         -- Implicit_Packing --
16641         ----------------------
16642
16643         --  pragma Implicit_Packing;
16644
16645         when Pragma_Implicit_Packing =>
16646            GNAT_Pragma;
16647            Check_Arg_Count (0);
16648            Implicit_Packing := True;
16649
16650         ------------
16651         -- Import --
16652         ------------
16653
16654         --  pragma Import (
16655         --       [Convention    =>] convention_IDENTIFIER,
16656         --       [Entity        =>] LOCAL_NAME
16657         --    [, [External_Name =>] static_string_EXPRESSION ]
16658         --    [, [Link_Name     =>] static_string_EXPRESSION ]);
16659
16660         when Pragma_Import =>
16661            Check_Ada_83_Warning;
16662            Check_Arg_Order
16663              ((Name_Convention,
16664                Name_Entity,
16665                Name_External_Name,
16666                Name_Link_Name));
16667
16668            Check_At_Least_N_Arguments (2);
16669            Check_At_Most_N_Arguments  (4);
16670            Process_Import_Or_Interface;
16671
16672         ---------------------
16673         -- Import_Function --
16674         ---------------------
16675
16676         --  pragma Import_Function (
16677         --        [Internal                 =>] LOCAL_NAME,
16678         --     [, [External                 =>] EXTERNAL_SYMBOL]
16679         --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
16680         --     [, [Result_Type              =>] SUBTYPE_MARK]
16681         --     [, [Mechanism                =>] MECHANISM]
16682         --     [, [Result_Mechanism         =>] MECHANISM_NAME]);
16683
16684         --  EXTERNAL_SYMBOL ::=
16685         --    IDENTIFIER
16686         --  | static_string_EXPRESSION
16687
16688         --  PARAMETER_TYPES ::=
16689         --    null
16690         --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
16691
16692         --  TYPE_DESIGNATOR ::=
16693         --    subtype_NAME
16694         --  | subtype_Name ' Access
16695
16696         --  MECHANISM ::=
16697         --    MECHANISM_NAME
16698         --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
16699
16700         --  MECHANISM_ASSOCIATION ::=
16701         --    [formal_parameter_NAME =>] MECHANISM_NAME
16702
16703         --  MECHANISM_NAME ::=
16704         --    Value
16705         --  | Reference
16706
16707         when Pragma_Import_Function => Import_Function : declare
16708            Args  : Args_List (1 .. 6);
16709            Names : constant Name_List (1 .. 6) := (
16710                      Name_Internal,
16711                      Name_External,
16712                      Name_Parameter_Types,
16713                      Name_Result_Type,
16714                      Name_Mechanism,
16715                      Name_Result_Mechanism);
16716
16717            Internal                 : Node_Id renames Args (1);
16718            External                 : Node_Id renames Args (2);
16719            Parameter_Types          : Node_Id renames Args (3);
16720            Result_Type              : Node_Id renames Args (4);
16721            Mechanism                : Node_Id renames Args (5);
16722            Result_Mechanism         : Node_Id renames Args (6);
16723
16724         begin
16725            GNAT_Pragma;
16726            Gather_Associations (Names, Args);
16727            Process_Extended_Import_Export_Subprogram_Pragma (
16728              Arg_Internal                 => Internal,
16729              Arg_External                 => External,
16730              Arg_Parameter_Types          => Parameter_Types,
16731              Arg_Result_Type              => Result_Type,
16732              Arg_Mechanism                => Mechanism,
16733              Arg_Result_Mechanism         => Result_Mechanism);
16734         end Import_Function;
16735
16736         -------------------
16737         -- Import_Object --
16738         -------------------
16739
16740         --  pragma Import_Object (
16741         --        [Internal =>] LOCAL_NAME
16742         --     [, [External =>] EXTERNAL_SYMBOL]
16743         --     [, [Size     =>] EXTERNAL_SYMBOL]);
16744
16745         --  EXTERNAL_SYMBOL ::=
16746         --    IDENTIFIER
16747         --  | static_string_EXPRESSION
16748
16749         when Pragma_Import_Object => Import_Object : declare
16750            Args  : Args_List (1 .. 3);
16751            Names : constant Name_List (1 .. 3) := (
16752                      Name_Internal,
16753                      Name_External,
16754                      Name_Size);
16755
16756            Internal : Node_Id renames Args (1);
16757            External : Node_Id renames Args (2);
16758            Size     : Node_Id renames Args (3);
16759
16760         begin
16761            GNAT_Pragma;
16762            Gather_Associations (Names, Args);
16763            Process_Extended_Import_Export_Object_Pragma (
16764              Arg_Internal => Internal,
16765              Arg_External => External,
16766              Arg_Size     => Size);
16767         end Import_Object;
16768
16769         ----------------------
16770         -- Import_Procedure --
16771         ----------------------
16772
16773         --  pragma Import_Procedure (
16774         --        [Internal                 =>] LOCAL_NAME
16775         --     [, [External                 =>] EXTERNAL_SYMBOL]
16776         --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
16777         --     [, [Mechanism                =>] MECHANISM]);
16778
16779         --  EXTERNAL_SYMBOL ::=
16780         --    IDENTIFIER
16781         --  | static_string_EXPRESSION
16782
16783         --  PARAMETER_TYPES ::=
16784         --    null
16785         --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
16786
16787         --  TYPE_DESIGNATOR ::=
16788         --    subtype_NAME
16789         --  | subtype_Name ' Access
16790
16791         --  MECHANISM ::=
16792         --    MECHANISM_NAME
16793         --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
16794
16795         --  MECHANISM_ASSOCIATION ::=
16796         --    [formal_parameter_NAME =>] MECHANISM_NAME
16797
16798         --  MECHANISM_NAME ::=
16799         --    Value
16800         --  | Reference
16801
16802         when Pragma_Import_Procedure => Import_Procedure : declare
16803            Args  : Args_List (1 .. 4);
16804            Names : constant Name_List (1 .. 4) := (
16805                      Name_Internal,
16806                      Name_External,
16807                      Name_Parameter_Types,
16808                      Name_Mechanism);
16809
16810            Internal                 : Node_Id renames Args (1);
16811            External                 : Node_Id renames Args (2);
16812            Parameter_Types          : Node_Id renames Args (3);
16813            Mechanism                : Node_Id renames Args (4);
16814
16815         begin
16816            GNAT_Pragma;
16817            Gather_Associations (Names, Args);
16818            Process_Extended_Import_Export_Subprogram_Pragma (
16819              Arg_Internal                 => Internal,
16820              Arg_External                 => External,
16821              Arg_Parameter_Types          => Parameter_Types,
16822              Arg_Mechanism                => Mechanism);
16823         end Import_Procedure;
16824
16825         -----------------------------
16826         -- Import_Valued_Procedure --
16827         -----------------------------
16828
16829         --  pragma Import_Valued_Procedure (
16830         --        [Internal                 =>] LOCAL_NAME
16831         --     [, [External                 =>] EXTERNAL_SYMBOL]
16832         --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
16833         --     [, [Mechanism                =>] MECHANISM]);
16834
16835         --  EXTERNAL_SYMBOL ::=
16836         --    IDENTIFIER
16837         --  | static_string_EXPRESSION
16838
16839         --  PARAMETER_TYPES ::=
16840         --    null
16841         --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
16842
16843         --  TYPE_DESIGNATOR ::=
16844         --    subtype_NAME
16845         --  | subtype_Name ' Access
16846
16847         --  MECHANISM ::=
16848         --    MECHANISM_NAME
16849         --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
16850
16851         --  MECHANISM_ASSOCIATION ::=
16852         --    [formal_parameter_NAME =>] MECHANISM_NAME
16853
16854         --  MECHANISM_NAME ::=
16855         --    Value
16856         --  | Reference
16857
16858         when Pragma_Import_Valued_Procedure =>
16859         Import_Valued_Procedure : declare
16860            Args  : Args_List (1 .. 4);
16861            Names : constant Name_List (1 .. 4) := (
16862                      Name_Internal,
16863                      Name_External,
16864                      Name_Parameter_Types,
16865                      Name_Mechanism);
16866
16867            Internal                 : Node_Id renames Args (1);
16868            External                 : Node_Id renames Args (2);
16869            Parameter_Types          : Node_Id renames Args (3);
16870            Mechanism                : Node_Id renames Args (4);
16871
16872         begin
16873            GNAT_Pragma;
16874            Gather_Associations (Names, Args);
16875            Process_Extended_Import_Export_Subprogram_Pragma (
16876              Arg_Internal                 => Internal,
16877              Arg_External                 => External,
16878              Arg_Parameter_Types          => Parameter_Types,
16879              Arg_Mechanism                => Mechanism);
16880         end Import_Valued_Procedure;
16881
16882         -----------------
16883         -- Independent --
16884         -----------------
16885
16886         --  pragma Independent (LOCAL_NAME);
16887
16888         when Pragma_Independent =>
16889            Process_Atomic_Independent_Shared_Volatile;
16890
16891         ----------------------------
16892         -- Independent_Components --
16893         ----------------------------
16894
16895         --  pragma Independent_Components (array_or_record_LOCAL_NAME);
16896
16897         when Pragma_Independent_Components => Independent_Components : declare
16898            C    : Node_Id;
16899            D    : Node_Id;
16900            E_Id : Node_Id;
16901            E    : Entity_Id;
16902            K    : Node_Kind;
16903
16904         begin
16905            Check_Ada_83_Warning;
16906            Ada_2012_Pragma;
16907            Check_No_Identifiers;
16908            Check_Arg_Count (1);
16909            Check_Arg_Is_Local_Name (Arg1);
16910            E_Id := Get_Pragma_Arg (Arg1);
16911
16912            if Etype (E_Id) = Any_Type then
16913               return;
16914            end if;
16915
16916            E := Entity (E_Id);
16917
16918            --  A pragma that applies to a Ghost entity becomes Ghost for the
16919            --  purposes of legality checks and removal of ignored Ghost code.
16920
16921            Mark_Ghost_Pragma (N, E);
16922
16923            --  Check duplicate before we chain ourselves
16924
16925            Check_Duplicate_Pragma (E);
16926
16927            --  Check appropriate entity
16928
16929            if Rep_Item_Too_Early (E, N)
16930                 or else
16931               Rep_Item_Too_Late (E, N)
16932            then
16933               return;
16934            end if;
16935
16936            D := Declaration_Node (E);
16937            K := Nkind (D);
16938
16939            --  The flag is set on the base type, or on the object
16940
16941            if K = N_Full_Type_Declaration
16942              and then (Is_Array_Type (E) or else Is_Record_Type (E))
16943            then
16944               Set_Has_Independent_Components (Base_Type (E));
16945               Record_Independence_Check (N, Base_Type (E));
16946
16947               --  For record type, set all components independent
16948
16949               if Is_Record_Type (E) then
16950                  C := First_Component (E);
16951                  while Present (C) loop
16952                     Set_Is_Independent (C);
16953                     Next_Component (C);
16954                  end loop;
16955               end if;
16956
16957            elsif (Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
16958              and then Nkind (D) = N_Object_Declaration
16959              and then Nkind (Object_Definition (D)) =
16960                                           N_Constrained_Array_Definition
16961            then
16962               Set_Has_Independent_Components (E);
16963               Record_Independence_Check (N, E);
16964
16965            else
16966               Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
16967            end if;
16968         end Independent_Components;
16969
16970         -----------------------
16971         -- Initial_Condition --
16972         -----------------------
16973
16974         --  pragma Initial_Condition (boolean_EXPRESSION);
16975
16976         --  Characteristics:
16977
16978         --    * Analysis - The annotation undergoes initial checks to verify
16979         --    the legal placement and context. Secondary checks preanalyze the
16980         --    expression in:
16981
16982         --       Analyze_Initial_Condition_In_Decl_Part
16983
16984         --    * Expansion - The annotation is expanded during the expansion of
16985         --    the package body whose declaration is subject to the annotation
16986         --    as done in:
16987
16988         --       Expand_Pragma_Initial_Condition
16989
16990         --    * Template - The annotation utilizes the generic template of the
16991         --    related package declaration.
16992
16993         --    * Globals - Capture of global references must occur after full
16994         --    analysis.
16995
16996         --    * Instance - The annotation is instantiated automatically when
16997         --    the related generic package is instantiated.
16998
16999         when Pragma_Initial_Condition => Initial_Condition : declare
17000            Pack_Decl : Node_Id;
17001            Pack_Id   : Entity_Id;
17002
17003         begin
17004            GNAT_Pragma;
17005            Check_No_Identifiers;
17006            Check_Arg_Count (1);
17007
17008            Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
17009
17010            --  Ensure the proper placement of the pragma. Initial_Condition
17011            --  must be associated with a package declaration.
17012
17013            if Nkind_In (Pack_Decl, N_Generic_Package_Declaration,
17014                                    N_Package_Declaration)
17015            then
17016               null;
17017
17018            --  Otherwise the pragma is associated with an illegal context
17019
17020            else
17021               Pragma_Misplaced;
17022               return;
17023            end if;
17024
17025            Pack_Id := Defining_Entity (Pack_Decl);
17026
17027            --  A pragma that applies to a Ghost entity becomes Ghost for the
17028            --  purposes of legality checks and removal of ignored Ghost code.
17029
17030            Mark_Ghost_Pragma (N, Pack_Id);
17031
17032            --  Chain the pragma on the contract for further processing by
17033            --  Analyze_Initial_Condition_In_Decl_Part.
17034
17035            Add_Contract_Item (N, Pack_Id);
17036
17037            --  The legality checks of pragmas Abstract_State, Initializes, and
17038            --  Initial_Condition are affected by the SPARK mode in effect. In
17039            --  addition, these three pragmas are subject to an inherent order:
17040
17041            --    1) Abstract_State
17042            --    2) Initializes
17043            --    3) Initial_Condition
17044
17045            --  Analyze all these pragmas in the order outlined above
17046
17047            Analyze_If_Present (Pragma_SPARK_Mode);
17048            Analyze_If_Present (Pragma_Abstract_State);
17049            Analyze_If_Present (Pragma_Initializes);
17050         end Initial_Condition;
17051
17052         ------------------------
17053         -- Initialize_Scalars --
17054         ------------------------
17055
17056         --  pragma Initialize_Scalars;
17057
17058         when Pragma_Initialize_Scalars =>
17059            GNAT_Pragma;
17060            Check_Arg_Count (0);
17061            Check_Valid_Configuration_Pragma;
17062            Check_Restriction (No_Initialize_Scalars, N);
17063
17064            --  Initialize_Scalars creates false positives in CodePeer, and
17065            --  incorrect negative results in GNATprove mode, so ignore this
17066            --  pragma in these modes.
17067
17068            if not Restriction_Active (No_Initialize_Scalars)
17069              and then not (CodePeer_Mode or GNATprove_Mode)
17070            then
17071               Init_Or_Norm_Scalars := True;
17072               Initialize_Scalars := True;
17073            end if;
17074
17075         -----------------
17076         -- Initializes --
17077         -----------------
17078
17079         --  pragma Initializes (INITIALIZATION_LIST);
17080
17081         --  INITIALIZATION_LIST ::=
17082         --     null
17083         --  | (INITIALIZATION_ITEM {, INITIALIZATION_ITEM})
17084
17085         --  INITIALIZATION_ITEM ::= name [=> INPUT_LIST]
17086
17087         --  INPUT_LIST ::=
17088         --     null
17089         --  |  INPUT
17090         --  | (INPUT {, INPUT})
17091
17092         --  INPUT ::= name
17093
17094         --  Characteristics:
17095
17096         --    * Analysis - The annotation undergoes initial checks to verify
17097         --    the legal placement and context. Secondary checks preanalyze the
17098         --    expression in:
17099
17100         --       Analyze_Initializes_In_Decl_Part
17101
17102         --    * Expansion - None.
17103
17104         --    * Template - The annotation utilizes the generic template of the
17105         --    related package declaration.
17106
17107         --    * Globals - Capture of global references must occur after full
17108         --    analysis.
17109
17110         --    * Instance - The annotation is instantiated automatically when
17111         --    the related generic package is instantiated.
17112
17113         when Pragma_Initializes => Initializes : declare
17114            Pack_Decl : Node_Id;
17115            Pack_Id   : Entity_Id;
17116
17117         begin
17118            GNAT_Pragma;
17119            Check_No_Identifiers;
17120            Check_Arg_Count (1);
17121
17122            Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
17123
17124            --  Ensure the proper placement of the pragma. Initializes must be
17125            --  associated with a package declaration.
17126
17127            if Nkind_In (Pack_Decl, N_Generic_Package_Declaration,
17128                                    N_Package_Declaration)
17129            then
17130               null;
17131
17132            --  Otherwise the pragma is associated with an illegal construc
17133
17134            else
17135               Pragma_Misplaced;
17136               return;
17137            end if;
17138
17139            Pack_Id := Defining_Entity (Pack_Decl);
17140
17141            --  A pragma that applies to a Ghost entity becomes Ghost for the
17142            --  purposes of legality checks and removal of ignored Ghost code.
17143
17144            Mark_Ghost_Pragma (N, Pack_Id);
17145            Ensure_Aggregate_Form (Get_Argument (N, Pack_Id));
17146
17147            --  Chain the pragma on the contract for further processing by
17148            --  Analyze_Initializes_In_Decl_Part.
17149
17150            Add_Contract_Item (N, Pack_Id);
17151
17152            --  The legality checks of pragmas Abstract_State, Initializes, and
17153            --  Initial_Condition are affected by the SPARK mode in effect. In
17154            --  addition, these three pragmas are subject to an inherent order:
17155
17156            --    1) Abstract_State
17157            --    2) Initializes
17158            --    3) Initial_Condition
17159
17160            --  Analyze all these pragmas in the order outlined above
17161
17162            Analyze_If_Present (Pragma_SPARK_Mode);
17163            Analyze_If_Present (Pragma_Abstract_State);
17164            Analyze_If_Present (Pragma_Initial_Condition);
17165         end Initializes;
17166
17167         ------------
17168         -- Inline --
17169         ------------
17170
17171         --  pragma Inline ( NAME {, NAME} );
17172
17173         when Pragma_Inline =>
17174
17175            --  Pragma always active unless in GNATprove mode. It is disabled
17176            --  in GNATprove mode because frontend inlining is applied
17177            --  independently of pragmas Inline and Inline_Always for
17178            --  formal verification, see Can_Be_Inlined_In_GNATprove_Mode
17179            --  in inline.ads.
17180
17181            if not GNATprove_Mode then
17182
17183               --  Inline status is Enabled if option -gnatn is specified.
17184               --  However this status determines only the value of the
17185               --  Is_Inlined flag on the subprogram and does not prevent
17186               --  the pragma itself from being recorded for later use,
17187               --  in particular for a later modification of Is_Inlined
17188               --  independently of the -gnatn option.
17189
17190               --  In other words, if -gnatn is specified for a unit, then
17191               --  all Inline pragmas processed for the compilation of this
17192               --  unit, including those in the spec of other units, are
17193               --  activated, so subprograms will be inlined across units.
17194
17195               --  If -gnatn is not specified, no Inline pragma is activated
17196               --  here, which means that subprograms will not be inlined
17197               --  across units. The Is_Inlined flag will nevertheless be
17198               --  set later when bodies are analyzed, so subprograms will
17199               --  be inlined within the unit.
17200
17201               if Inline_Active then
17202                  Process_Inline (Enabled);
17203               else
17204                  Process_Inline (Disabled);
17205               end if;
17206            end if;
17207
17208         -------------------
17209         -- Inline_Always --
17210         -------------------
17211
17212         --  pragma Inline_Always ( NAME {, NAME} );
17213
17214         when Pragma_Inline_Always =>
17215            GNAT_Pragma;
17216
17217            --  Pragma always active unless in CodePeer mode or GNATprove
17218            --  mode. It is disabled in CodePeer mode because inlining is
17219            --  not helpful, and enabling it caused walk order issues. It
17220            --  is disabled in GNATprove mode because frontend inlining is
17221            --  applied independently of pragmas Inline and Inline_Always for
17222            --  formal verification, see Can_Be_Inlined_In_GNATprove_Mode in
17223            --  inline.ads.
17224
17225            if not CodePeer_Mode and not GNATprove_Mode then
17226               Process_Inline (Enabled);
17227            end if;
17228
17229         --------------------
17230         -- Inline_Generic --
17231         --------------------
17232
17233         --  pragma Inline_Generic (NAME {, NAME});
17234
17235         when Pragma_Inline_Generic =>
17236            GNAT_Pragma;
17237            Process_Generic_List;
17238
17239         ----------------------
17240         -- Inspection_Point --
17241         ----------------------
17242
17243         --  pragma Inspection_Point [(object_NAME {, object_NAME})];
17244
17245         when Pragma_Inspection_Point => Inspection_Point : declare
17246            Arg : Node_Id;
17247            Exp : Node_Id;
17248
17249         begin
17250            ip;
17251
17252            if Arg_Count > 0 then
17253               Arg := Arg1;
17254               loop
17255                  Exp := Get_Pragma_Arg (Arg);
17256                  Analyze (Exp);
17257
17258                  if not Is_Entity_Name (Exp)
17259                    or else not Is_Object (Entity (Exp))
17260                  then
17261                     Error_Pragma_Arg ("object name required", Arg);
17262                  end if;
17263
17264                  Next (Arg);
17265                  exit when No (Arg);
17266               end loop;
17267            end if;
17268         end Inspection_Point;
17269
17270         ---------------
17271         -- Interface --
17272         ---------------
17273
17274         --  pragma Interface (
17275         --    [   Convention    =>] convention_IDENTIFIER,
17276         --    [   Entity        =>] LOCAL_NAME
17277         --    [, [External_Name =>] static_string_EXPRESSION ]
17278         --    [, [Link_Name     =>] static_string_EXPRESSION ]);
17279
17280         when Pragma_Interface =>
17281            GNAT_Pragma;
17282            Check_Arg_Order
17283              ((Name_Convention,
17284                Name_Entity,
17285                Name_External_Name,
17286                Name_Link_Name));
17287            Check_At_Least_N_Arguments (2);
17288            Check_At_Most_N_Arguments  (4);
17289            Process_Import_Or_Interface;
17290
17291            --  In Ada 2005, the permission to use Interface (a reserved word)
17292            --  as a pragma name is considered an obsolescent feature, and this
17293            --  pragma was already obsolescent in Ada 95.
17294
17295            if Ada_Version >= Ada_95 then
17296               Check_Restriction
17297                 (No_Obsolescent_Features, Pragma_Identifier (N));
17298
17299               if Warn_On_Obsolescent_Feature then
17300                  Error_Msg_N
17301                    ("pragma Interface is an obsolescent feature?j?", N);
17302                  Error_Msg_N
17303                    ("|use pragma Import instead?j?", N);
17304               end if;
17305            end if;
17306
17307         --------------------
17308         -- Interface_Name --
17309         --------------------
17310
17311         --  pragma Interface_Name (
17312         --    [  Entity        =>] LOCAL_NAME
17313         --    [,[External_Name =>] static_string_EXPRESSION ]
17314         --    [,[Link_Name     =>] static_string_EXPRESSION ]);
17315
17316         when Pragma_Interface_Name => Interface_Name : declare
17317            Id     : Node_Id;
17318            Def_Id : Entity_Id;
17319            Hom_Id : Entity_Id;
17320            Found  : Boolean;
17321
17322         begin
17323            GNAT_Pragma;
17324            Check_Arg_Order
17325              ((Name_Entity, Name_External_Name, Name_Link_Name));
17326            Check_At_Least_N_Arguments (2);
17327            Check_At_Most_N_Arguments  (3);
17328            Id := Get_Pragma_Arg (Arg1);
17329            Analyze (Id);
17330
17331            --  This is obsolete from Ada 95 on, but it is an implementation
17332            --  defined pragma, so we do not consider that it violates the
17333            --  restriction (No_Obsolescent_Features).
17334
17335            if Ada_Version >= Ada_95 then
17336               if Warn_On_Obsolescent_Feature then
17337                  Error_Msg_N
17338                    ("pragma Interface_Name is an obsolescent feature?j?", N);
17339                  Error_Msg_N
17340                    ("|use pragma Import instead?j?", N);
17341               end if;
17342            end if;
17343
17344            if not Is_Entity_Name (Id) then
17345               Error_Pragma_Arg
17346                 ("first argument for pragma% must be entity name", Arg1);
17347            elsif Etype (Id) = Any_Type then
17348               return;
17349            else
17350               Def_Id := Entity (Id);
17351            end if;
17352
17353            --  Special DEC-compatible processing for the object case, forces
17354            --  object to be imported.
17355
17356            if Ekind (Def_Id) = E_Variable then
17357               Kill_Size_Check_Code (Def_Id);
17358               Note_Possible_Modification (Id, Sure => False);
17359
17360               --  Initialization is not allowed for imported variable
17361
17362               if Present (Expression (Parent (Def_Id)))
17363                 and then Comes_From_Source (Expression (Parent (Def_Id)))
17364               then
17365                  Error_Msg_Sloc := Sloc (Def_Id);
17366                  Error_Pragma_Arg
17367                    ("no initialization allowed for declaration of& #",
17368                     Arg2);
17369
17370               else
17371                  --  For compatibility, support VADS usage of providing both
17372                  --  pragmas Interface and Interface_Name to obtain the effect
17373                  --  of a single Import pragma.
17374
17375                  if Is_Imported (Def_Id)
17376                    and then Present (First_Rep_Item (Def_Id))
17377                    and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
17378                    and then Pragma_Name (First_Rep_Item (Def_Id)) =
17379                      Name_Interface
17380                  then
17381                     null;
17382                  else
17383                     Set_Imported (Def_Id);
17384                  end if;
17385
17386                  Set_Is_Public (Def_Id);
17387                  Process_Interface_Name (Def_Id, Arg2, Arg3, N);
17388               end if;
17389
17390            --  Otherwise must be subprogram
17391
17392            elsif not Is_Subprogram (Def_Id) then
17393               Error_Pragma_Arg
17394                 ("argument of pragma% is not subprogram", Arg1);
17395
17396            else
17397               Check_At_Most_N_Arguments (3);
17398               Hom_Id := Def_Id;
17399               Found := False;
17400
17401               --  Loop through homonyms
17402
17403               loop
17404                  Def_Id := Get_Base_Subprogram (Hom_Id);
17405
17406                  if Is_Imported (Def_Id) then
17407                     Process_Interface_Name (Def_Id, Arg2, Arg3, N);
17408                     Found := True;
17409                  end if;
17410
17411                  exit when From_Aspect_Specification (N);
17412                  Hom_Id := Homonym (Hom_Id);
17413
17414                  exit when No (Hom_Id)
17415                    or else Scope (Hom_Id) /= Current_Scope;
17416               end loop;
17417
17418               if not Found then
17419                  Error_Pragma_Arg
17420                    ("argument of pragma% is not imported subprogram",
17421                     Arg1);
17422               end if;
17423            end if;
17424         end Interface_Name;
17425
17426         -----------------------
17427         -- Interrupt_Handler --
17428         -----------------------
17429
17430         --  pragma Interrupt_Handler (handler_NAME);
17431
17432         when Pragma_Interrupt_Handler =>
17433            Check_Ada_83_Warning;
17434            Check_Arg_Count (1);
17435            Check_No_Identifiers;
17436
17437            if No_Run_Time_Mode then
17438               Error_Msg_CRT ("Interrupt_Handler pragma", N);
17439            else
17440               Check_Interrupt_Or_Attach_Handler;
17441               Process_Interrupt_Or_Attach_Handler;
17442            end if;
17443
17444         ------------------------
17445         -- Interrupt_Priority --
17446         ------------------------
17447
17448         --  pragma Interrupt_Priority [(EXPRESSION)];
17449
17450         when Pragma_Interrupt_Priority => Interrupt_Priority : declare
17451            P   : constant Node_Id := Parent (N);
17452            Arg : Node_Id;
17453            Ent : Entity_Id;
17454
17455         begin
17456            Check_Ada_83_Warning;
17457
17458            if Arg_Count /= 0 then
17459               Arg := Get_Pragma_Arg (Arg1);
17460               Check_Arg_Count (1);
17461               Check_No_Identifiers;
17462
17463               --  The expression must be analyzed in the special manner
17464               --  described in "Handling of Default and Per-Object
17465               --  Expressions" in sem.ads.
17466
17467               Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
17468            end if;
17469
17470            if not Nkind_In (P, N_Task_Definition, N_Protected_Definition) then
17471               Pragma_Misplaced;
17472               return;
17473
17474            else
17475               Ent := Defining_Identifier (Parent (P));
17476
17477               --  Check duplicate pragma before we chain the pragma in the Rep
17478               --  Item chain of Ent.
17479
17480               Check_Duplicate_Pragma (Ent);
17481               Record_Rep_Item (Ent, N);
17482
17483               --  Check the No_Task_At_Interrupt_Priority restriction
17484
17485               if Nkind (P) = N_Task_Definition then
17486                  Check_Restriction (No_Task_At_Interrupt_Priority, N);
17487               end if;
17488            end if;
17489         end Interrupt_Priority;
17490
17491         ---------------------
17492         -- Interrupt_State --
17493         ---------------------
17494
17495         --  pragma Interrupt_State (
17496         --    [Name  =>] INTERRUPT_ID,
17497         --    [State =>] INTERRUPT_STATE);
17498
17499         --  INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
17500         --  INTERRUPT_STATE => System | Runtime | User
17501
17502         --  Note: if the interrupt id is given as an identifier, then it must
17503         --  be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
17504         --  given as a static integer expression which must be in the range of
17505         --  Ada.Interrupts.Interrupt_ID.
17506
17507         when Pragma_Interrupt_State => Interrupt_State : declare
17508            Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
17509            --  This is the entity Ada.Interrupts.Interrupt_ID;
17510
17511            State_Type : Character;
17512            --  Set to 's'/'r'/'u' for System/Runtime/User
17513
17514            IST_Num : Pos;
17515            --  Index to entry in Interrupt_States table
17516
17517            Int_Val : Uint;
17518            --  Value of interrupt
17519
17520            Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
17521            --  The first argument to the pragma
17522
17523            Int_Ent : Entity_Id;
17524            --  Interrupt entity in Ada.Interrupts.Names
17525
17526         begin
17527            GNAT_Pragma;
17528            Check_Arg_Order ((Name_Name, Name_State));
17529            Check_Arg_Count (2);
17530
17531            Check_Optional_Identifier (Arg1, Name_Name);
17532            Check_Optional_Identifier (Arg2, Name_State);
17533            Check_Arg_Is_Identifier (Arg2);
17534
17535            --  First argument is identifier
17536
17537            if Nkind (Arg1X) = N_Identifier then
17538
17539               --  Search list of names in Ada.Interrupts.Names
17540
17541               Int_Ent := First_Entity (RTE (RE_Names));
17542               loop
17543                  if No (Int_Ent) then
17544                     Error_Pragma_Arg ("invalid interrupt name", Arg1);
17545
17546                  elsif Chars (Int_Ent) = Chars (Arg1X) then
17547                     Int_Val := Expr_Value (Constant_Value (Int_Ent));
17548                     exit;
17549                  end if;
17550
17551                  Next_Entity (Int_Ent);
17552               end loop;
17553
17554            --  First argument is not an identifier, so it must be a static
17555            --  expression of type Ada.Interrupts.Interrupt_ID.
17556
17557            else
17558               Check_Arg_Is_OK_Static_Expression (Arg1, Any_Integer);
17559               Int_Val := Expr_Value (Arg1X);
17560
17561               if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
17562                    or else
17563                  Int_Val > Expr_Value (Type_High_Bound (Int_Id))
17564               then
17565                  Error_Pragma_Arg
17566                    ("value not in range of type "
17567                     & """Ada.Interrupts.Interrupt_'I'D""", Arg1);
17568               end if;
17569            end if;
17570
17571            --  Check OK state
17572
17573            case Chars (Get_Pragma_Arg (Arg2)) is
17574               when Name_Runtime => State_Type := 'r';
17575               when Name_System  => State_Type := 's';
17576               when Name_User    => State_Type := 'u';
17577
17578               when others =>
17579                  Error_Pragma_Arg ("invalid interrupt state", Arg2);
17580            end case;
17581
17582            --  Check if entry is already stored
17583
17584            IST_Num := Interrupt_States.First;
17585            loop
17586               --  If entry not found, add it
17587
17588               if IST_Num > Interrupt_States.Last then
17589                  Interrupt_States.Append
17590                    ((Interrupt_Number => UI_To_Int (Int_Val),
17591                      Interrupt_State  => State_Type,
17592                      Pragma_Loc       => Loc));
17593                  exit;
17594
17595               --  Case of entry for the same entry
17596
17597               elsif Int_Val = Interrupt_States.Table (IST_Num).
17598                                                           Interrupt_Number
17599               then
17600                  --  If state matches, done, no need to make redundant entry
17601
17602                  exit when
17603                    State_Type = Interrupt_States.Table (IST_Num).
17604                                                           Interrupt_State;
17605
17606                  --  Otherwise if state does not match, error
17607
17608                  Error_Msg_Sloc :=
17609                    Interrupt_States.Table (IST_Num).Pragma_Loc;
17610                  Error_Pragma_Arg
17611                    ("state conflicts with that given #", Arg2);
17612                  exit;
17613               end if;
17614
17615               IST_Num := IST_Num + 1;
17616            end loop;
17617         end Interrupt_State;
17618
17619         ---------------
17620         -- Invariant --
17621         ---------------
17622
17623         --  pragma Invariant
17624         --    ([Entity =>]    type_LOCAL_NAME,
17625         --     [Check  =>]    EXPRESSION
17626         --     [,[Message =>] String_Expression]);
17627
17628         when Pragma_Invariant => Invariant : declare
17629            Discard : Boolean;
17630            Typ     : Entity_Id;
17631            Typ_Arg : Node_Id;
17632
17633         begin
17634            GNAT_Pragma;
17635            Check_At_Least_N_Arguments (2);
17636            Check_At_Most_N_Arguments  (3);
17637            Check_Optional_Identifier (Arg1, Name_Entity);
17638            Check_Optional_Identifier (Arg2, Name_Check);
17639
17640            if Arg_Count = 3 then
17641               Check_Optional_Identifier (Arg3, Name_Message);
17642               Check_Arg_Is_OK_Static_Expression (Arg3, Standard_String);
17643            end if;
17644
17645            Check_Arg_Is_Local_Name (Arg1);
17646
17647            Typ_Arg := Get_Pragma_Arg (Arg1);
17648            Find_Type (Typ_Arg);
17649            Typ := Entity (Typ_Arg);
17650
17651            --  Nothing to do of the related type is erroneous in some way
17652
17653            if Typ = Any_Type then
17654               return;
17655
17656            --  AI12-0041: Invariants are allowed in interface types
17657
17658            elsif Is_Interface (Typ) then
17659               null;
17660
17661            --  An invariant must apply to a private type, or appear in the
17662            --  private part of a package spec and apply to a completion.
17663            --  a class-wide invariant can only appear on a private declaration
17664            --  or private extension, not a completion.
17665
17666            --  A [class-wide] invariant may be associated a [limited] private
17667            --  type or a private extension.
17668
17669            elsif Ekind_In (Typ, E_Limited_Private_Type,
17670                                 E_Private_Type,
17671                                 E_Record_Type_With_Private)
17672            then
17673               null;
17674
17675            --  A non-class-wide invariant may be associated with the full view
17676            --  of a [limited] private type or a private extension.
17677
17678            elsif Has_Private_Declaration (Typ)
17679              and then not Class_Present (N)
17680            then
17681               null;
17682
17683            --  A class-wide invariant may appear on the partial view only
17684
17685            elsif Class_Present (N) then
17686               Error_Pragma_Arg
17687                 ("pragma % only allowed for private type", Arg1);
17688               return;
17689
17690            --  A regular invariant may appear on both views
17691
17692            else
17693               Error_Pragma_Arg
17694                 ("pragma % only allowed for private type or corresponding "
17695                  & "full view", Arg1);
17696               return;
17697            end if;
17698
17699            --  An invariant associated with an abstract type (this includes
17700            --  interfaces) must be class-wide.
17701
17702            if Is_Abstract_Type (Typ) and then not Class_Present (N) then
17703               Error_Pragma_Arg
17704                 ("pragma % not allowed for abstract type", Arg1);
17705               return;
17706            end if;
17707
17708            --  A pragma that applies to a Ghost entity becomes Ghost for the
17709            --  purposes of legality checks and removal of ignored Ghost code.
17710
17711            Mark_Ghost_Pragma (N, Typ);
17712
17713            --  The pragma defines a type-specific invariant, the type is said
17714            --  to have invariants of its "own".
17715
17716            Set_Has_Own_Invariants (Typ);
17717
17718            --  If the invariant is class-wide, then it can be inherited by
17719            --  derived or interface implementing types. The type is said to
17720            --  have "inheritable" invariants.
17721
17722            if Class_Present (N) then
17723               Set_Has_Inheritable_Invariants (Typ);
17724            end if;
17725
17726            --  Chain the pragma on to the rep item chain, for processing when
17727            --  the type is frozen.
17728
17729            Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
17730
17731            --  Create the declaration of the invariant procedure that will
17732            --  verify the invariant at run time. Interfaces are treated as the
17733            --  partial view of a private type in order to achieve uniformity
17734            --  with the general case. As a result, an interface receives only
17735            --  a "partial" invariant procedure, which is never called.
17736
17737            Build_Invariant_Procedure_Declaration
17738              (Typ               => Typ,
17739               Partial_Invariant => Is_Interface (Typ));
17740         end Invariant;
17741
17742         ----------------
17743         -- Keep_Names --
17744         ----------------
17745
17746         --  pragma Keep_Names ([On => ] LOCAL_NAME);
17747
17748         when Pragma_Keep_Names => Keep_Names : declare
17749            Arg : Node_Id;
17750
17751         begin
17752            GNAT_Pragma;
17753            Check_Arg_Count (1);
17754            Check_Optional_Identifier (Arg1, Name_On);
17755            Check_Arg_Is_Local_Name (Arg1);
17756
17757            Arg := Get_Pragma_Arg (Arg1);
17758            Analyze (Arg);
17759
17760            if Etype (Arg) = Any_Type then
17761               return;
17762            end if;
17763
17764            if not Is_Entity_Name (Arg)
17765              or else Ekind (Entity (Arg)) /= E_Enumeration_Type
17766            then
17767               Error_Pragma_Arg
17768                 ("pragma% requires a local enumeration type", Arg1);
17769            end if;
17770
17771            Set_Discard_Names (Entity (Arg), False);
17772         end Keep_Names;
17773
17774         -------------
17775         -- License --
17776         -------------
17777
17778         --  pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
17779
17780         when Pragma_License =>
17781            GNAT_Pragma;
17782
17783            --  Do not analyze pragma any further in CodePeer mode, to avoid
17784            --  extraneous errors in this implementation-dependent pragma,
17785            --  which has a different profile on other compilers.
17786
17787            if CodePeer_Mode then
17788               return;
17789            end if;
17790
17791            Check_Arg_Count (1);
17792            Check_No_Identifiers;
17793            Check_Valid_Configuration_Pragma;
17794            Check_Arg_Is_Identifier (Arg1);
17795
17796            declare
17797               Sind : constant Source_File_Index :=
17798                        Source_Index (Current_Sem_Unit);
17799
17800            begin
17801               case Chars (Get_Pragma_Arg (Arg1)) is
17802                  when Name_GPL =>
17803                     Set_License (Sind, GPL);
17804
17805                  when Name_Modified_GPL =>
17806                     Set_License (Sind, Modified_GPL);
17807
17808                  when Name_Restricted =>
17809                     Set_License (Sind, Restricted);
17810
17811                  when Name_Unrestricted =>
17812                     Set_License (Sind, Unrestricted);
17813
17814                  when others =>
17815                     Error_Pragma_Arg ("invalid license name", Arg1);
17816               end case;
17817            end;
17818
17819         ---------------
17820         -- Link_With --
17821         ---------------
17822
17823         --  pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
17824
17825         when Pragma_Link_With => Link_With : declare
17826            Arg : Node_Id;
17827
17828         begin
17829            GNAT_Pragma;
17830
17831            if Operating_Mode = Generate_Code
17832              and then In_Extended_Main_Source_Unit (N)
17833            then
17834               Check_At_Least_N_Arguments (1);
17835               Check_No_Identifiers;
17836               Check_Is_In_Decl_Part_Or_Package_Spec;
17837               Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
17838               Start_String;
17839
17840               Arg := Arg1;
17841               while Present (Arg) loop
17842                  Check_Arg_Is_OK_Static_Expression (Arg, Standard_String);
17843
17844                  --  Store argument, converting sequences of spaces to a
17845                  --  single null character (this is one of the differences
17846                  --  in processing between Link_With and Linker_Options).
17847
17848                  Arg_Store : declare
17849                     C : constant Char_Code := Get_Char_Code (' ');
17850                     S : constant String_Id :=
17851                           Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
17852                     L : constant Nat := String_Length (S);
17853                     F : Nat := 1;
17854
17855                     procedure Skip_Spaces;
17856                     --  Advance F past any spaces
17857
17858                     -----------------
17859                     -- Skip_Spaces --
17860                     -----------------
17861
17862                     procedure Skip_Spaces is
17863                     begin
17864                        while F <= L and then Get_String_Char (S, F) = C loop
17865                           F := F + 1;
17866                        end loop;
17867                     end Skip_Spaces;
17868
17869                  --  Start of processing for Arg_Store
17870
17871                  begin
17872                     Skip_Spaces; -- skip leading spaces
17873
17874                     --  Loop through characters, changing any embedded
17875                     --  sequence of spaces to a single null character (this
17876                     --  is how Link_With/Linker_Options differ)
17877
17878                     while F <= L loop
17879                        if Get_String_Char (S, F) = C then
17880                           Skip_Spaces;
17881                           exit when F > L;
17882                           Store_String_Char (ASCII.NUL);
17883
17884                        else
17885                           Store_String_Char (Get_String_Char (S, F));
17886                           F := F + 1;
17887                        end if;
17888                     end loop;
17889                  end Arg_Store;
17890
17891                  Arg := Next (Arg);
17892
17893                  if Present (Arg) then
17894                     Store_String_Char (ASCII.NUL);
17895                  end if;
17896               end loop;
17897
17898               Store_Linker_Option_String (End_String);
17899            end if;
17900         end Link_With;
17901
17902         ------------------
17903         -- Linker_Alias --
17904         ------------------
17905
17906         --  pragma Linker_Alias (
17907         --      [Entity =>]  LOCAL_NAME
17908         --      [Target =>]  static_string_EXPRESSION);
17909
17910         when Pragma_Linker_Alias =>
17911            GNAT_Pragma;
17912            Check_Arg_Order ((Name_Entity, Name_Target));
17913            Check_Arg_Count (2);
17914            Check_Optional_Identifier (Arg1, Name_Entity);
17915            Check_Optional_Identifier (Arg2, Name_Target);
17916            Check_Arg_Is_Library_Level_Local_Name (Arg1);
17917            Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
17918
17919            --  The only processing required is to link this item on to the
17920            --  list of rep items for the given entity. This is accomplished
17921            --  by the call to Rep_Item_Too_Late (when no error is detected
17922            --  and False is returned).
17923
17924            if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
17925               return;
17926            else
17927               Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
17928            end if;
17929
17930         ------------------------
17931         -- Linker_Constructor --
17932         ------------------------
17933
17934         --  pragma Linker_Constructor (procedure_LOCAL_NAME);
17935
17936         --  Code is shared with Linker_Destructor
17937
17938         -----------------------
17939         -- Linker_Destructor --
17940         -----------------------
17941
17942         --  pragma Linker_Destructor (procedure_LOCAL_NAME);
17943
17944         when Pragma_Linker_Constructor
17945            | Pragma_Linker_Destructor
17946         =>
17947         Linker_Constructor : declare
17948            Arg1_X : Node_Id;
17949            Proc   : Entity_Id;
17950
17951         begin
17952            GNAT_Pragma;
17953            Check_Arg_Count (1);
17954            Check_No_Identifiers;
17955            Check_Arg_Is_Local_Name (Arg1);
17956            Arg1_X := Get_Pragma_Arg (Arg1);
17957            Analyze (Arg1_X);
17958            Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
17959
17960            if not Is_Library_Level_Entity (Proc) then
17961               Error_Pragma_Arg
17962                ("argument for pragma% must be library level entity", Arg1);
17963            end if;
17964
17965            --  The only processing required is to link this item on to the
17966            --  list of rep items for the given entity. This is accomplished
17967            --  by the call to Rep_Item_Too_Late (when no error is detected
17968            --  and False is returned).
17969
17970            if Rep_Item_Too_Late (Proc, N) then
17971               return;
17972            else
17973               Set_Has_Gigi_Rep_Item (Proc);
17974            end if;
17975         end Linker_Constructor;
17976
17977         --------------------
17978         -- Linker_Options --
17979         --------------------
17980
17981         --  pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
17982
17983         when Pragma_Linker_Options => Linker_Options : declare
17984            Arg : Node_Id;
17985
17986         begin
17987            Check_Ada_83_Warning;
17988            Check_No_Identifiers;
17989            Check_Arg_Count (1);
17990            Check_Is_In_Decl_Part_Or_Package_Spec;
17991            Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
17992            Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
17993
17994            Arg := Arg2;
17995            while Present (Arg) loop
17996               Check_Arg_Is_OK_Static_Expression (Arg, Standard_String);
17997               Store_String_Char (ASCII.NUL);
17998               Store_String_Chars
17999                 (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
18000               Arg := Next (Arg);
18001            end loop;
18002
18003            if Operating_Mode = Generate_Code
18004              and then In_Extended_Main_Source_Unit (N)
18005            then
18006               Store_Linker_Option_String (End_String);
18007            end if;
18008         end Linker_Options;
18009
18010         --------------------
18011         -- Linker_Section --
18012         --------------------
18013
18014         --  pragma Linker_Section (
18015         --      [Entity  =>] LOCAL_NAME
18016         --      [Section =>] static_string_EXPRESSION);
18017
18018         when Pragma_Linker_Section => Linker_Section : declare
18019            Arg : Node_Id;
18020            Ent : Entity_Id;
18021            LPE : Node_Id;
18022
18023            Ghost_Error_Posted : Boolean := False;
18024            --  Flag set when an error concerning the illegal mix of Ghost and
18025            --  non-Ghost subprograms is emitted.
18026
18027            Ghost_Id : Entity_Id := Empty;
18028            --  The entity of the first Ghost subprogram encountered while
18029            --  processing the arguments of the pragma.
18030
18031         begin
18032            GNAT_Pragma;
18033            Check_Arg_Order ((Name_Entity, Name_Section));
18034            Check_Arg_Count (2);
18035            Check_Optional_Identifier (Arg1, Name_Entity);
18036            Check_Optional_Identifier (Arg2, Name_Section);
18037            Check_Arg_Is_Library_Level_Local_Name (Arg1);
18038            Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
18039
18040            --  Check kind of entity
18041
18042            Arg := Get_Pragma_Arg (Arg1);
18043            Ent := Entity (Arg);
18044
18045            case Ekind (Ent) is
18046
18047               --  Objects (constants and variables) and types. For these cases
18048               --  all we need to do is to set the Linker_Section_pragma field,
18049               --  checking that we do not have a duplicate.
18050
18051               when Type_Kind
18052                  | E_Constant
18053                  | E_Variable
18054               =>
18055                  LPE := Linker_Section_Pragma (Ent);
18056
18057                  if Present (LPE) then
18058                     Error_Msg_Sloc := Sloc (LPE);
18059                     Error_Msg_NE
18060                       ("Linker_Section already specified for &#", Arg1, Ent);
18061                  end if;
18062
18063                  Set_Linker_Section_Pragma (Ent, N);
18064
18065                  --  A pragma that applies to a Ghost entity becomes Ghost for
18066                  --  the purposes of legality checks and removal of ignored
18067                  --  Ghost code.
18068
18069                  Mark_Ghost_Pragma (N, Ent);
18070
18071               --  Subprograms
18072
18073               when Subprogram_Kind =>
18074
18075                  --  Aspect case, entity already set
18076
18077                  if From_Aspect_Specification (N) then
18078                     Set_Linker_Section_Pragma
18079                       (Entity (Corresponding_Aspect (N)), N);
18080
18081                  --  Pragma case, we must climb the homonym chain, but skip
18082                  --  any for which the linker section is already set.
18083
18084                  else
18085                     loop
18086                        if No (Linker_Section_Pragma (Ent)) then
18087                           Set_Linker_Section_Pragma (Ent, N);
18088
18089                           --  A pragma that applies to a Ghost entity becomes
18090                           --  Ghost for the purposes of legality checks and
18091                           --  removal of ignored Ghost code.
18092
18093                           Mark_Ghost_Pragma (N, Ent);
18094
18095                           --  Capture the entity of the first Ghost subprogram
18096                           --  being processed for error detection purposes.
18097
18098                           if Is_Ghost_Entity (Ent) then
18099                              if No (Ghost_Id) then
18100                                 Ghost_Id := Ent;
18101                              end if;
18102
18103                           --  Otherwise the subprogram is non-Ghost. It is
18104                           --  illegal to mix references to Ghost and non-Ghost
18105                           --  entities (SPARK RM 6.9).
18106
18107                           elsif Present (Ghost_Id)
18108                             and then not Ghost_Error_Posted
18109                           then
18110                              Ghost_Error_Posted := True;
18111
18112                              Error_Msg_Name_1 := Pname;
18113                              Error_Msg_N
18114                                ("pragma % cannot mention ghost and "
18115                                 & "non-ghost subprograms", N);
18116
18117                              Error_Msg_Sloc := Sloc (Ghost_Id);
18118                              Error_Msg_NE
18119                                ("\& # declared as ghost", N, Ghost_Id);
18120
18121                              Error_Msg_Sloc := Sloc (Ent);
18122                              Error_Msg_NE
18123                                ("\& # declared as non-ghost", N, Ent);
18124                           end if;
18125                        end if;
18126
18127                        Ent := Homonym (Ent);
18128                        exit when No (Ent)
18129                          or else Scope (Ent) /= Current_Scope;
18130                     end loop;
18131                  end if;
18132
18133               --  All other cases are illegal
18134
18135               when others =>
18136                  Error_Pragma_Arg
18137                    ("pragma% applies only to objects, subprograms, and types",
18138                     Arg1);
18139            end case;
18140         end Linker_Section;
18141
18142         ----------
18143         -- List --
18144         ----------
18145
18146         --  pragma List (On | Off)
18147
18148         --  There is nothing to do here, since we did all the processing for
18149         --  this pragma in Par.Prag (so that it works properly even in syntax
18150         --  only mode).
18151
18152         when Pragma_List =>
18153            null;
18154
18155         ---------------
18156         -- Lock_Free --
18157         ---------------
18158
18159         --  pragma Lock_Free [(Boolean_EXPRESSION)];
18160
18161         when Pragma_Lock_Free => Lock_Free : declare
18162            P   : constant Node_Id := Parent (N);
18163            Arg : Node_Id;
18164            Ent : Entity_Id;
18165            Val : Boolean;
18166
18167         begin
18168            Check_No_Identifiers;
18169            Check_At_Most_N_Arguments (1);
18170
18171            --  Protected definition case
18172
18173            if Nkind (P) = N_Protected_Definition then
18174               Ent := Defining_Identifier (Parent (P));
18175
18176               --  One argument
18177
18178               if Arg_Count = 1 then
18179                  Arg := Get_Pragma_Arg (Arg1);
18180                  Val := Is_True (Static_Boolean (Arg));
18181
18182               --  No arguments (expression is considered to be True)
18183
18184               else
18185                  Val := True;
18186               end if;
18187
18188               --  Check duplicate pragma before we chain the pragma in the Rep
18189               --  Item chain of Ent.
18190
18191               Check_Duplicate_Pragma (Ent);
18192               Record_Rep_Item        (Ent, N);
18193               Set_Uses_Lock_Free     (Ent, Val);
18194
18195            --  Anything else is incorrect placement
18196
18197            else
18198               Pragma_Misplaced;
18199            end if;
18200         end Lock_Free;
18201
18202         --------------------
18203         -- Locking_Policy --
18204         --------------------
18205
18206         --  pragma Locking_Policy (policy_IDENTIFIER);
18207
18208         when Pragma_Locking_Policy => declare
18209            subtype LP_Range is Name_Id
18210              range First_Locking_Policy_Name .. Last_Locking_Policy_Name;
18211            LP_Val : LP_Range;
18212            LP     : Character;
18213
18214         begin
18215            Check_Ada_83_Warning;
18216            Check_Arg_Count (1);
18217            Check_No_Identifiers;
18218            Check_Arg_Is_Locking_Policy (Arg1);
18219            Check_Valid_Configuration_Pragma;
18220            LP_Val := Chars (Get_Pragma_Arg (Arg1));
18221
18222            case LP_Val is
18223               when Name_Ceiling_Locking            => LP := 'C';
18224               when Name_Concurrent_Readers_Locking => LP := 'R';
18225               when Name_Inheritance_Locking        => LP := 'I';
18226            end case;
18227
18228            if Locking_Policy /= ' '
18229              and then Locking_Policy /= LP
18230            then
18231               Error_Msg_Sloc := Locking_Policy_Sloc;
18232               Error_Pragma ("locking policy incompatible with policy#");
18233
18234            --  Set new policy, but always preserve System_Location since we
18235            --  like the error message with the run time name.
18236
18237            else
18238               Locking_Policy := LP;
18239
18240               if Locking_Policy_Sloc /= System_Location then
18241                  Locking_Policy_Sloc := Loc;
18242               end if;
18243            end if;
18244         end;
18245
18246         -------------------
18247         -- Loop_Optimize --
18248         -------------------
18249
18250         --  pragma Loop_Optimize ( OPTIMIZATION_HINT {, OPTIMIZATION_HINT } );
18251
18252         --  OPTIMIZATION_HINT ::=
18253         --    Ivdep | No_Unroll | Unroll | No_Vector | Vector
18254
18255         when Pragma_Loop_Optimize => Loop_Optimize : declare
18256            Hint : Node_Id;
18257
18258         begin
18259            GNAT_Pragma;
18260            Check_At_Least_N_Arguments (1);
18261            Check_No_Identifiers;
18262
18263            Hint := First (Pragma_Argument_Associations (N));
18264            while Present (Hint) loop
18265               Check_Arg_Is_One_Of (Hint, Name_Ivdep,
18266                                          Name_No_Unroll,
18267                                          Name_Unroll,
18268                                          Name_No_Vector,
18269                                          Name_Vector);
18270               Next (Hint);
18271            end loop;
18272
18273            Check_Loop_Pragma_Placement;
18274         end Loop_Optimize;
18275
18276         ------------------
18277         -- Loop_Variant --
18278         ------------------
18279
18280         --  pragma Loop_Variant
18281         --         ( LOOP_VARIANT_ITEM {, LOOP_VARIANT_ITEM } );
18282
18283         --  LOOP_VARIANT_ITEM ::= CHANGE_DIRECTION => discrete_EXPRESSION
18284
18285         --  CHANGE_DIRECTION ::= Increases | Decreases
18286
18287         when Pragma_Loop_Variant => Loop_Variant : declare
18288            Variant : Node_Id;
18289
18290         begin
18291            GNAT_Pragma;
18292            Check_At_Least_N_Arguments (1);
18293            Check_Loop_Pragma_Placement;
18294
18295            --  Process all increasing / decreasing expressions
18296
18297            Variant := First (Pragma_Argument_Associations (N));
18298            while Present (Variant) loop
18299               if Chars (Variant) = No_Name then
18300                  Error_Pragma_Arg_Ident ("expect name `Increases`", Variant);
18301
18302               elsif not Nam_In (Chars (Variant), Name_Decreases,
18303                                                  Name_Increases)
18304               then
18305                  declare
18306                     Name : String := Get_Name_String (Chars (Variant));
18307
18308                  begin
18309                     --  It is a common mistake to write "Increasing" for
18310                     --  "Increases" or "Decreasing" for "Decreases". Recognize
18311                     --  specially names starting with "incr" or "decr" to
18312                     --  suggest the corresponding name.
18313
18314                     System.Case_Util.To_Lower (Name);
18315
18316                     if Name'Length >= 4
18317                       and then Name (1 .. 4) = "incr"
18318                     then
18319                        Error_Pragma_Arg_Ident
18320                          ("expect name `Increases`", Variant);
18321
18322                     elsif Name'Length >= 4
18323                       and then Name (1 .. 4) = "decr"
18324                     then
18325                        Error_Pragma_Arg_Ident
18326                          ("expect name `Decreases`", Variant);
18327
18328                     else
18329                        Error_Pragma_Arg_Ident
18330                          ("expect name `Increases` or `Decreases`", Variant);
18331                     end if;
18332                  end;
18333               end if;
18334
18335               Preanalyze_Assert_Expression
18336                 (Expression (Variant), Any_Discrete);
18337
18338               Next (Variant);
18339            end loop;
18340         end Loop_Variant;
18341
18342         -----------------------
18343         -- Machine_Attribute --
18344         -----------------------
18345
18346         --  pragma Machine_Attribute (
18347         --       [Entity         =>] LOCAL_NAME,
18348         --       [Attribute_Name =>] static_string_EXPRESSION
18349         --    [, [Info           =>] static_EXPRESSION] );
18350
18351         when Pragma_Machine_Attribute => Machine_Attribute : declare
18352            Def_Id : Entity_Id;
18353
18354         begin
18355            GNAT_Pragma;
18356            Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
18357
18358            if Arg_Count = 3 then
18359               Check_Optional_Identifier (Arg3, Name_Info);
18360               Check_Arg_Is_OK_Static_Expression (Arg3);
18361            else
18362               Check_Arg_Count (2);
18363            end if;
18364
18365            Check_Optional_Identifier (Arg1, Name_Entity);
18366            Check_Optional_Identifier (Arg2, Name_Attribute_Name);
18367            Check_Arg_Is_Local_Name (Arg1);
18368            Check_Arg_Is_OK_Static_Expression (Arg2, Standard_String);
18369            Def_Id := Entity (Get_Pragma_Arg (Arg1));
18370
18371            if Is_Access_Type (Def_Id) then
18372               Def_Id := Designated_Type (Def_Id);
18373            end if;
18374
18375            if Rep_Item_Too_Early (Def_Id, N) then
18376               return;
18377            end if;
18378
18379            Def_Id := Underlying_Type (Def_Id);
18380
18381            --  The only processing required is to link this item on to the
18382            --  list of rep items for the given entity. This is accomplished
18383            --  by the call to Rep_Item_Too_Late (when no error is detected
18384            --  and False is returned).
18385
18386            if Rep_Item_Too_Late (Def_Id, N) then
18387               return;
18388            else
18389               Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
18390            end if;
18391         end Machine_Attribute;
18392
18393         ----------
18394         -- Main --
18395         ----------
18396
18397         --  pragma Main
18398         --   (MAIN_OPTION [, MAIN_OPTION]);
18399
18400         --  MAIN_OPTION ::=
18401         --    [STACK_SIZE              =>] static_integer_EXPRESSION
18402         --  | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
18403         --  | [TIME_SLICING_ENABLED    =>] static_boolean_EXPRESSION
18404
18405         when Pragma_Main => Main : declare
18406            Args  : Args_List (1 .. 3);
18407            Names : constant Name_List (1 .. 3) := (
18408                      Name_Stack_Size,
18409                      Name_Task_Stack_Size_Default,
18410                      Name_Time_Slicing_Enabled);
18411
18412            Nod : Node_Id;
18413
18414         begin
18415            GNAT_Pragma;
18416            Gather_Associations (Names, Args);
18417
18418            for J in 1 .. 2 loop
18419               if Present (Args (J)) then
18420                  Check_Arg_Is_OK_Static_Expression (Args (J), Any_Integer);
18421               end if;
18422            end loop;
18423
18424            if Present (Args (3)) then
18425               Check_Arg_Is_OK_Static_Expression (Args (3), Standard_Boolean);
18426            end if;
18427
18428            Nod := Next (N);
18429            while Present (Nod) loop
18430               if Nkind (Nod) = N_Pragma
18431                 and then Pragma_Name (Nod) = Name_Main
18432               then
18433                  Error_Msg_Name_1 := Pname;
18434                  Error_Msg_N ("duplicate pragma% not permitted", Nod);
18435               end if;
18436
18437               Next (Nod);
18438            end loop;
18439         end Main;
18440
18441         ------------------
18442         -- Main_Storage --
18443         ------------------
18444
18445         --  pragma Main_Storage
18446         --   (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
18447
18448         --  MAIN_STORAGE_OPTION ::=
18449         --    [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
18450         --  | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
18451
18452         when Pragma_Main_Storage => Main_Storage : declare
18453            Args  : Args_List (1 .. 2);
18454            Names : constant Name_List (1 .. 2) := (
18455                      Name_Working_Storage,
18456                      Name_Top_Guard);
18457
18458            Nod : Node_Id;
18459
18460         begin
18461            GNAT_Pragma;
18462            Gather_Associations (Names, Args);
18463
18464            for J in 1 .. 2 loop
18465               if Present (Args (J)) then
18466                  Check_Arg_Is_OK_Static_Expression (Args (J), Any_Integer);
18467               end if;
18468            end loop;
18469
18470            Check_In_Main_Program;
18471
18472            Nod := Next (N);
18473            while Present (Nod) loop
18474               if Nkind (Nod) = N_Pragma
18475                 and then Pragma_Name (Nod) = Name_Main_Storage
18476               then
18477                  Error_Msg_Name_1 := Pname;
18478                  Error_Msg_N ("duplicate pragma% not permitted", Nod);
18479               end if;
18480
18481               Next (Nod);
18482            end loop;
18483         end Main_Storage;
18484
18485         ----------------------
18486         -- Max_Queue_Length --
18487         ----------------------
18488
18489         --  pragma Max_Queue_Length (static_integer_EXPRESSION);
18490
18491         when Pragma_Max_Queue_Length => Max_Queue_Length : declare
18492            Arg        : Node_Id;
18493            Entry_Decl : Node_Id;
18494            Entry_Id   : Entity_Id;
18495            Val        : Uint;
18496
18497         begin
18498            GNAT_Pragma;
18499            Check_Arg_Count (1);
18500
18501            Entry_Decl :=
18502              Find_Related_Declaration_Or_Body (N, Do_Checks => True);
18503
18504            --  Entry declaration
18505
18506            if Nkind (Entry_Decl) = N_Entry_Declaration then
18507
18508               --  Entry illegally within a task
18509
18510               if Nkind (Parent (N)) = N_Task_Definition then
18511                  Error_Pragma ("pragma % cannot apply to task entries");
18512                  return;
18513               end if;
18514
18515               Entry_Id := Unique_Defining_Entity (Entry_Decl);
18516
18517            --  Otherwise the pragma is associated with an illegal construct
18518
18519            else
18520               Error_Pragma ("pragma % must apply to a protected entry");
18521               return;
18522            end if;
18523
18524            --  Mark the pragma as Ghost if the related subprogram is also
18525            --  Ghost. This also ensures that any expansion performed further
18526            --  below will produce Ghost nodes.
18527
18528            Mark_Ghost_Pragma (N, Entry_Id);
18529
18530            --  Analyze the Integer expression
18531
18532            Arg := Get_Pragma_Arg (Arg1);
18533            Check_Arg_Is_OK_Static_Expression (Arg, Any_Integer);
18534
18535            Val := Expr_Value (Arg);
18536
18537            if Val <= 0 then
18538               Error_Pragma_Arg
18539                 ("argument for pragma% must be positive", Arg1);
18540
18541            elsif not UI_Is_In_Int_Range (Val) then
18542               Error_Pragma_Arg
18543                 ("argument for pragma% out of range of Integer", Arg1);
18544
18545            end if;
18546
18547            --  Manually substitute the expression value of the pragma argument
18548            --  if it's not an integer literal because this is not taken care
18549            --  of automatically elsewhere.
18550
18551            if Nkind (Arg) /= N_Integer_Literal then
18552               Rewrite (Arg, Make_Integer_Literal (Sloc (Arg), Val));
18553            end if;
18554
18555            Record_Rep_Item (Entry_Id, N);
18556         end Max_Queue_Length;
18557
18558         -----------------
18559         -- Memory_Size --
18560         -----------------
18561
18562         --  pragma Memory_Size (NUMERIC_LITERAL)
18563
18564         when Pragma_Memory_Size =>
18565            GNAT_Pragma;
18566
18567            --  Memory size is simply ignored
18568
18569            Check_No_Identifiers;
18570            Check_Arg_Count (1);
18571            Check_Arg_Is_Integer_Literal (Arg1);
18572
18573         -------------
18574         -- No_Body --
18575         -------------
18576
18577         --  pragma No_Body;
18578
18579         --  The only correct use of this pragma is on its own in a file, in
18580         --  which case it is specially processed (see Gnat1drv.Check_Bad_Body
18581         --  and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
18582         --  check for a file containing nothing but a No_Body pragma). If we
18583         --  attempt to process it during normal semantics processing, it means
18584         --  it was misplaced.
18585
18586         when Pragma_No_Body =>
18587            GNAT_Pragma;
18588            Pragma_Misplaced;
18589
18590         -----------------------------
18591         -- No_Elaboration_Code_All --
18592         -----------------------------
18593
18594         --  pragma No_Elaboration_Code_All;
18595
18596         when Pragma_No_Elaboration_Code_All =>
18597            GNAT_Pragma;
18598            Check_Valid_Library_Unit_Pragma;
18599
18600            if Nkind (N) = N_Null_Statement then
18601               return;
18602            end if;
18603
18604            --  Must appear for a spec or generic spec
18605
18606            if not Nkind_In (Unit (Cunit (Current_Sem_Unit)),
18607                             N_Generic_Package_Declaration,
18608                             N_Generic_Subprogram_Declaration,
18609                             N_Package_Declaration,
18610                             N_Subprogram_Declaration)
18611            then
18612               Error_Pragma
18613                 (Fix_Error
18614                    ("pragma% can only occur for package "
18615                     & "or subprogram spec"));
18616            end if;
18617
18618            --  Set flag in unit table
18619
18620            Set_No_Elab_Code_All (Current_Sem_Unit);
18621
18622            --  Set restriction No_Elaboration_Code if this is the main unit
18623
18624            if Current_Sem_Unit = Main_Unit then
18625               Set_Restriction (No_Elaboration_Code, N);
18626            end if;
18627
18628            --  If we are in the main unit or in an extended main source unit,
18629            --  then we also add it to the configuration restrictions so that
18630            --  it will apply to all units in the extended main source.
18631
18632            if Current_Sem_Unit = Main_Unit
18633              or else In_Extended_Main_Source_Unit (N)
18634            then
18635               Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
18636            end if;
18637
18638            --  If in main extended unit, activate transitive with test
18639
18640            if In_Extended_Main_Source_Unit (N) then
18641               Opt.No_Elab_Code_All_Pragma := N;
18642            end if;
18643
18644         -----------------------------
18645         -- No_Component_Reordering --
18646         -----------------------------
18647
18648         --  pragma No_Component_Reordering [([Entity =>] type_LOCAL_NAME)];
18649
18650         when Pragma_No_Component_Reordering => No_Comp_Reordering : declare
18651            E    : Entity_Id;
18652            E_Id : Node_Id;
18653
18654         begin
18655            GNAT_Pragma;
18656            Check_At_Most_N_Arguments (1);
18657
18658            if Arg_Count = 0 then
18659               Check_Valid_Configuration_Pragma;
18660               Opt.No_Component_Reordering := True;
18661
18662            else
18663               Check_Optional_Identifier (Arg2, Name_Entity);
18664               Check_Arg_Is_Local_Name (Arg1);
18665               E_Id := Get_Pragma_Arg (Arg1);
18666
18667               if Etype (E_Id) = Any_Type then
18668                  return;
18669               end if;
18670
18671               E := Entity (E_Id);
18672
18673               if not Is_Record_Type (E) then
18674                  Error_Pragma_Arg ("pragma% requires record type", Arg1);
18675               end if;
18676
18677               Set_No_Reordering (Base_Type (E));
18678            end if;
18679         end No_Comp_Reordering;
18680
18681         --------------------------
18682         -- No_Heap_Finalization --
18683         --------------------------
18684
18685         --  pragma No_Heap_Finalization [ (first_subtype_LOCAL_NAME) ];
18686
18687         when Pragma_No_Heap_Finalization => No_Heap_Finalization : declare
18688            Context : constant Node_Id := Parent (N);
18689            Typ_Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
18690            Prev    : Node_Id;
18691            Typ     : Entity_Id;
18692
18693         begin
18694            GNAT_Pragma;
18695            Check_No_Identifiers;
18696
18697            --  The pragma appears in a configuration file
18698
18699            if No (Context) then
18700               Check_Arg_Count (0);
18701               Check_Valid_Configuration_Pragma;
18702
18703               --  Detect a duplicate pragma
18704
18705               if Present (No_Heap_Finalization_Pragma) then
18706                  Duplication_Error
18707                    (Prag => N,
18708                     Prev => No_Heap_Finalization_Pragma);
18709                  raise Pragma_Exit;
18710               end if;
18711
18712               No_Heap_Finalization_Pragma := N;
18713
18714            --  Otherwise the pragma should be associated with a library-level
18715            --  named access-to-object type.
18716
18717            else
18718               Check_Arg_Count (1);
18719               Check_Arg_Is_Local_Name (Arg1);
18720
18721               Find_Type (Typ_Arg);
18722               Typ := Entity (Typ_Arg);
18723
18724               --  The type being subjected to the pragma is erroneous
18725
18726               if Typ = Any_Type then
18727                  Error_Pragma ("cannot find type referenced by pragma %");
18728
18729               --  The pragma is applied to an incomplete or generic formal
18730               --  type way too early.
18731
18732               elsif Rep_Item_Too_Early (Typ, N) then
18733                  return;
18734
18735               else
18736                  Typ := Underlying_Type (Typ);
18737               end if;
18738
18739               --  The pragma must apply to an access-to-object type
18740
18741               if Ekind_In (Typ, E_Access_Type, E_General_Access_Type) then
18742                  null;
18743
18744               --  Give a detailed error message on all other access type kinds
18745
18746               elsif Ekind (Typ) = E_Access_Protected_Subprogram_Type then
18747                  Error_Pragma
18748                    ("pragma % cannot apply to access protected subprogram "
18749                     & "type");
18750
18751               elsif Ekind (Typ) = E_Access_Subprogram_Type then
18752                  Error_Pragma
18753                    ("pragma % cannot apply to access subprogram type");
18754
18755               elsif Is_Anonymous_Access_Type (Typ) then
18756                  Error_Pragma
18757                    ("pragma % cannot apply to anonymous access type");
18758
18759               --  Give a general error message in case the pragma applies to a
18760               --  non-access type.
18761
18762               else
18763                  Error_Pragma
18764                    ("pragma % must apply to library level access type");
18765               end if;
18766
18767               --  At this point the argument denotes an access-to-object type.
18768               --  Ensure that the type is declared at the library level.
18769
18770               if Is_Library_Level_Entity (Typ) then
18771                  null;
18772
18773               --  Quietly ignore an access-to-object type originally declared
18774               --  at the library level within a generic, but instantiated at
18775               --  a non-library level. As a result the access-to-object type
18776               --  "loses" its No_Heap_Finalization property.
18777
18778               elsif In_Instance then
18779                  raise Pragma_Exit;
18780
18781               else
18782                  Error_Pragma
18783                    ("pragma % must apply to library level access type");
18784               end if;
18785
18786               --  Detect a duplicate pragma
18787
18788               if Present (No_Heap_Finalization_Pragma) then
18789                  Duplication_Error
18790                    (Prag => N,
18791                     Prev => No_Heap_Finalization_Pragma);
18792                  raise Pragma_Exit;
18793
18794               else
18795                  Prev := Get_Pragma (Typ, Pragma_No_Heap_Finalization);
18796
18797                  if Present (Prev) then
18798                     Duplication_Error
18799                       (Prag => N,
18800                        Prev => Prev);
18801                     raise Pragma_Exit;
18802                  end if;
18803               end if;
18804
18805               Record_Rep_Item (Typ, N);
18806            end if;
18807         end No_Heap_Finalization;
18808
18809         ---------------
18810         -- No_Inline --
18811         ---------------
18812
18813         --  pragma No_Inline ( NAME {, NAME} );
18814
18815         when Pragma_No_Inline =>
18816            GNAT_Pragma;
18817            Process_Inline (Suppressed);
18818
18819         ---------------
18820         -- No_Return --
18821         ---------------
18822
18823         --  pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
18824
18825         when Pragma_No_Return => No_Return : declare
18826            Arg   : Node_Id;
18827            E     : Entity_Id;
18828            Found : Boolean;
18829            Id    : Node_Id;
18830
18831            Ghost_Error_Posted : Boolean := False;
18832            --  Flag set when an error concerning the illegal mix of Ghost and
18833            --  non-Ghost subprograms is emitted.
18834
18835            Ghost_Id : Entity_Id := Empty;
18836            --  The entity of the first Ghost procedure encountered while
18837            --  processing the arguments of the pragma.
18838
18839         begin
18840            Ada_2005_Pragma;
18841            Check_At_Least_N_Arguments (1);
18842
18843            --  Loop through arguments of pragma
18844
18845            Arg := Arg1;
18846            while Present (Arg) loop
18847               Check_Arg_Is_Local_Name (Arg);
18848               Id := Get_Pragma_Arg (Arg);
18849               Analyze (Id);
18850
18851               if not Is_Entity_Name (Id) then
18852                  Error_Pragma_Arg ("entity name required", Arg);
18853               end if;
18854
18855               if Etype (Id) = Any_Type then
18856                  raise Pragma_Exit;
18857               end if;
18858
18859               --  Loop to find matching procedures
18860
18861               E := Entity (Id);
18862
18863               Found := False;
18864               while Present (E)
18865                 and then Scope (E) = Current_Scope
18866               loop
18867                  if Ekind_In (E, E_Generic_Procedure, E_Procedure) then
18868
18869                     --  Check that the pragma is not applied to a body.
18870                     --  First check the specless body case, to give a
18871                     --  different error message. These checks do not apply
18872                     --  if Relaxed_RM_Semantics, to accommodate other Ada
18873                     --  compilers. Disable these checks under -gnatd.J.
18874
18875                     if not Debug_Flag_Dot_JJ then
18876                        if Nkind (Parent (Declaration_Node (E))) =
18877                            N_Subprogram_Body
18878                          and then not Relaxed_RM_Semantics
18879                        then
18880                           Error_Pragma
18881                             ("pragma% requires separate spec and must come "
18882                              & "before body");
18883                        end if;
18884
18885                        --  Now the "specful" body case
18886
18887                        if Rep_Item_Too_Late (E, N) then
18888                           raise Pragma_Exit;
18889                        end if;
18890                     end if;
18891
18892                     Set_No_Return (E);
18893
18894                     --  A pragma that applies to a Ghost entity becomes Ghost
18895                     --  for the purposes of legality checks and removal of
18896                     --  ignored Ghost code.
18897
18898                     Mark_Ghost_Pragma (N, E);
18899
18900                     --  Capture the entity of the first Ghost procedure being
18901                     --  processed for error detection purposes.
18902
18903                     if Is_Ghost_Entity (E) then
18904                        if No (Ghost_Id) then
18905                           Ghost_Id := E;
18906                        end if;
18907
18908                     --  Otherwise the subprogram is non-Ghost. It is illegal
18909                     --  to mix references to Ghost and non-Ghost entities
18910                     --  (SPARK RM 6.9).
18911
18912                     elsif Present (Ghost_Id)
18913                       and then not Ghost_Error_Posted
18914                     then
18915                        Ghost_Error_Posted := True;
18916
18917                        Error_Msg_Name_1 := Pname;
18918                        Error_Msg_N
18919                          ("pragma % cannot mention ghost and non-ghost "
18920                           & "procedures", N);
18921
18922                        Error_Msg_Sloc := Sloc (Ghost_Id);
18923                        Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
18924
18925                        Error_Msg_Sloc := Sloc (E);
18926                        Error_Msg_NE ("\& # declared as non-ghost", N, E);
18927                     end if;
18928
18929                     --  Set flag on any alias as well
18930
18931                     if Is_Overloadable (E) and then Present (Alias (E)) then
18932                        Set_No_Return (Alias (E));
18933                     end if;
18934
18935                     Found := True;
18936                  end if;
18937
18938                  exit when From_Aspect_Specification (N);
18939                  E := Homonym (E);
18940               end loop;
18941
18942               --  If entity in not in current scope it may be the enclosing
18943               --  suprogram body to which the aspect applies.
18944
18945               if not Found then
18946                  if Entity (Id) = Current_Scope
18947                    and then From_Aspect_Specification (N)
18948                  then
18949                     Set_No_Return (Entity (Id));
18950                  else
18951                     Error_Pragma_Arg ("no procedure& found for pragma%", Arg);
18952                  end if;
18953               end if;
18954
18955               Next (Arg);
18956            end loop;
18957         end No_Return;
18958
18959         -----------------
18960         -- No_Run_Time --
18961         -----------------
18962
18963         --  pragma No_Run_Time;
18964
18965         --  Note: this pragma is retained for backwards compatibility. See
18966         --  body of Rtsfind for full details on its handling.
18967
18968         when Pragma_No_Run_Time =>
18969            GNAT_Pragma;
18970            Check_Valid_Configuration_Pragma;
18971            Check_Arg_Count (0);
18972
18973            --  Remove backward compatibility if Build_Type is FSF or GPL and
18974            --  generate a warning.
18975
18976            declare
18977               Ignore : constant Boolean := Build_Type in FSF .. GPL;
18978            begin
18979               if Ignore then
18980                  Error_Pragma ("pragma% is ignored, has no effect??");
18981               else
18982                  No_Run_Time_Mode           := True;
18983                  Configurable_Run_Time_Mode := True;
18984
18985                  --  Set Duration to 32 bits if word size is 32
18986
18987                  if Ttypes.System_Word_Size = 32 then
18988                     Duration_32_Bits_On_Target := True;
18989                  end if;
18990
18991                  --  Set appropriate restrictions
18992
18993                  Set_Restriction (No_Finalization, N);
18994                  Set_Restriction (No_Exception_Handlers, N);
18995                  Set_Restriction (Max_Tasks, N, 0);
18996                  Set_Restriction (No_Tasking, N);
18997               end if;
18998            end;
18999
19000         -----------------------
19001         -- No_Tagged_Streams --
19002         -----------------------
19003
19004         --  pragma No_Tagged_Streams [([Entity => ]tagged_type_local_NAME)];
19005
19006         when Pragma_No_Tagged_Streams => No_Tagged_Strms : declare
19007            E    : Entity_Id;
19008            E_Id : Node_Id;
19009
19010         begin
19011            GNAT_Pragma;
19012            Check_At_Most_N_Arguments (1);
19013
19014            --  One argument case
19015
19016            if Arg_Count = 1 then
19017               Check_Optional_Identifier (Arg1, Name_Entity);
19018               Check_Arg_Is_Local_Name (Arg1);
19019               E_Id := Get_Pragma_Arg (Arg1);
19020
19021               if Etype (E_Id) = Any_Type then
19022                  return;
19023               end if;
19024
19025               E := Entity (E_Id);
19026
19027               Check_Duplicate_Pragma (E);
19028
19029               if not Is_Tagged_Type (E) or else Is_Derived_Type (E) then
19030                  Error_Pragma_Arg
19031                    ("argument for pragma% must be root tagged type", Arg1);
19032               end if;
19033
19034               if Rep_Item_Too_Early (E, N)
19035                    or else
19036                  Rep_Item_Too_Late (E, N)
19037               then
19038                  return;
19039               else
19040                  Set_No_Tagged_Streams_Pragma (E, N);
19041               end if;
19042
19043            --  Zero argument case
19044
19045            else
19046               Check_Is_In_Decl_Part_Or_Package_Spec;
19047               No_Tagged_Streams := N;
19048            end if;
19049         end No_Tagged_Strms;
19050
19051         ------------------------
19052         -- No_Strict_Aliasing --
19053         ------------------------
19054
19055         --  pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
19056
19057         when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
19058            E    : Entity_Id;
19059            E_Id : Node_Id;
19060
19061         begin
19062            GNAT_Pragma;
19063            Check_At_Most_N_Arguments (1);
19064
19065            if Arg_Count = 0 then
19066               Check_Valid_Configuration_Pragma;
19067               Opt.No_Strict_Aliasing := True;
19068
19069            else
19070               Check_Optional_Identifier (Arg2, Name_Entity);
19071               Check_Arg_Is_Local_Name (Arg1);
19072               E_Id := Get_Pragma_Arg (Arg1);
19073
19074               if Etype (E_Id) = Any_Type then
19075                  return;
19076               end if;
19077
19078               E := Entity (E_Id);
19079
19080               if not Is_Access_Type (E) then
19081                  Error_Pragma_Arg ("pragma% requires access type", Arg1);
19082               end if;
19083
19084               Set_No_Strict_Aliasing (Base_Type (E));
19085            end if;
19086         end No_Strict_Aliasing;
19087
19088         -----------------------
19089         -- Normalize_Scalars --
19090         -----------------------
19091
19092         --  pragma Normalize_Scalars;
19093
19094         when Pragma_Normalize_Scalars =>
19095            Check_Ada_83_Warning;
19096            Check_Arg_Count (0);
19097            Check_Valid_Configuration_Pragma;
19098
19099            --  Normalize_Scalars creates false positives in CodePeer, and
19100            --  incorrect negative results in GNATprove mode, so ignore this
19101            --  pragma in these modes.
19102
19103            if not (CodePeer_Mode or GNATprove_Mode) then
19104               Normalize_Scalars := True;
19105               Init_Or_Norm_Scalars := True;
19106            end if;
19107
19108         -----------------
19109         -- Obsolescent --
19110         -----------------
19111
19112         --  pragma Obsolescent;
19113
19114         --  pragma Obsolescent (
19115         --    [Message =>] static_string_EXPRESSION
19116         --  [,[Version =>] Ada_05]]);
19117
19118         --  pragma Obsolescent (
19119         --    [Entity  =>] NAME
19120         --  [,[Message =>] static_string_EXPRESSION
19121         --  [,[Version =>] Ada_05]] );
19122
19123         when Pragma_Obsolescent => Obsolescent : declare
19124            Decl  : Node_Id;
19125            Ename : Node_Id;
19126
19127            procedure Set_Obsolescent (E : Entity_Id);
19128            --  Given an entity Ent, mark it as obsolescent if appropriate
19129
19130            ---------------------
19131            -- Set_Obsolescent --
19132            ---------------------
19133
19134            procedure Set_Obsolescent (E : Entity_Id) is
19135               Active : Boolean;
19136               Ent    : Entity_Id;
19137               S      : String_Id;
19138
19139            begin
19140               Active := True;
19141               Ent    := E;
19142
19143               --  A pragma that applies to a Ghost entity becomes Ghost for
19144               --  the purposes of legality checks and removal of ignored Ghost
19145               --  code.
19146
19147               Mark_Ghost_Pragma (N, E);
19148
19149               --  Entity name was given
19150
19151               if Present (Ename) then
19152
19153                  --  If entity name matches, we are fine. Save entity in
19154                  --  pragma argument, for ASIS use.
19155
19156                  if Chars (Ename) = Chars (Ent) then
19157                     Set_Entity (Ename, Ent);
19158                     Generate_Reference (Ent, Ename);
19159
19160                  --  If entity name does not match, only possibility is an
19161                  --  enumeration literal from an enumeration type declaration.
19162
19163                  elsif Ekind (Ent) /= E_Enumeration_Type then
19164                     Error_Pragma
19165                       ("pragma % entity name does not match declaration");
19166
19167                  else
19168                     Ent := First_Literal (E);
19169                     loop
19170                        if No (Ent) then
19171                           Error_Pragma
19172                             ("pragma % entity name does not match any "
19173                              & "enumeration literal");
19174
19175                        elsif Chars (Ent) = Chars (Ename) then
19176                           Set_Entity (Ename, Ent);
19177                           Generate_Reference (Ent, Ename);
19178                           exit;
19179
19180                        else
19181                           Ent := Next_Literal (Ent);
19182                        end if;
19183                     end loop;
19184                  end if;
19185               end if;
19186
19187               --  Ent points to entity to be marked
19188
19189               if Arg_Count >= 1 then
19190
19191                  --  Deal with static string argument
19192
19193                  Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
19194                  S := Strval (Get_Pragma_Arg (Arg1));
19195
19196                  for J in 1 .. String_Length (S) loop
19197                     if not In_Character_Range (Get_String_Char (S, J)) then
19198                        Error_Pragma_Arg
19199                          ("pragma% argument does not allow wide characters",
19200                           Arg1);
19201                     end if;
19202                  end loop;
19203
19204                  Obsolescent_Warnings.Append
19205                    ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
19206
19207                  --  Check for Ada_05 parameter
19208
19209                  if Arg_Count /= 1 then
19210                     Check_Arg_Count (2);
19211
19212                     declare
19213                        Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
19214
19215                     begin
19216                        Check_Arg_Is_Identifier (Argx);
19217
19218                        if Chars (Argx) /= Name_Ada_05 then
19219                           Error_Msg_Name_2 := Name_Ada_05;
19220                           Error_Pragma_Arg
19221                             ("only allowed argument for pragma% is %", Argx);
19222                        end if;
19223
19224                        if Ada_Version_Explicit < Ada_2005
19225                          or else not Warn_On_Ada_2005_Compatibility
19226                        then
19227                           Active := False;
19228                        end if;
19229                     end;
19230                  end if;
19231               end if;
19232
19233               --  Set flag if pragma active
19234
19235               if Active then
19236                  Set_Is_Obsolescent (Ent);
19237               end if;
19238
19239               return;
19240            end Set_Obsolescent;
19241
19242         --  Start of processing for pragma Obsolescent
19243
19244         begin
19245            GNAT_Pragma;
19246
19247            Check_At_Most_N_Arguments (3);
19248
19249            --  See if first argument specifies an entity name
19250
19251            if Arg_Count >= 1
19252              and then
19253                (Chars (Arg1) = Name_Entity
19254                   or else
19255                     Nkind_In (Get_Pragma_Arg (Arg1), N_Character_Literal,
19256                                                      N_Identifier,
19257                                                      N_Operator_Symbol))
19258            then
19259               Ename := Get_Pragma_Arg (Arg1);
19260
19261               --  Eliminate first argument, so we can share processing
19262
19263               Arg1 := Arg2;
19264               Arg2 := Arg3;
19265               Arg_Count := Arg_Count - 1;
19266
19267            --  No Entity name argument given
19268
19269            else
19270               Ename := Empty;
19271            end if;
19272
19273            if Arg_Count >= 1 then
19274               Check_Optional_Identifier (Arg1, Name_Message);
19275
19276               if Arg_Count = 2 then
19277                  Check_Optional_Identifier (Arg2, Name_Version);
19278               end if;
19279            end if;
19280
19281            --  Get immediately preceding declaration
19282
19283            Decl := Prev (N);
19284            while Present (Decl) and then Nkind (Decl) = N_Pragma loop
19285               Prev (Decl);
19286            end loop;
19287
19288            --  Cases where we do not follow anything other than another pragma
19289
19290            if No (Decl) then
19291
19292               --  First case: library level compilation unit declaration with
19293               --  the pragma immediately following the declaration.
19294
19295               if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
19296                  Set_Obsolescent
19297                    (Defining_Entity (Unit (Parent (Parent (N)))));
19298                  return;
19299
19300               --  Case 2: library unit placement for package
19301
19302               else
19303                  declare
19304                     Ent : constant Entity_Id := Find_Lib_Unit_Name;
19305                  begin
19306                     if Is_Package_Or_Generic_Package (Ent) then
19307                        Set_Obsolescent (Ent);
19308                        return;
19309                     end if;
19310                  end;
19311               end if;
19312
19313            --  Cases where we must follow a declaration, including an
19314            --  abstract subprogram declaration, which is not in the
19315            --  other node subtypes.
19316
19317            else
19318               if         Nkind (Decl) not in N_Declaration
19319                 and then Nkind (Decl) not in N_Later_Decl_Item
19320                 and then Nkind (Decl) not in N_Generic_Declaration
19321                 and then Nkind (Decl) not in N_Renaming_Declaration
19322                 and then Nkind (Decl) /= N_Abstract_Subprogram_Declaration
19323               then
19324                  Error_Pragma
19325                    ("pragma% misplaced, "
19326                     & "must immediately follow a declaration");
19327
19328               else
19329                  Set_Obsolescent (Defining_Entity (Decl));
19330                  return;
19331               end if;
19332            end if;
19333         end Obsolescent;
19334
19335         --------------
19336         -- Optimize --
19337         --------------
19338
19339         --  pragma Optimize (Time | Space | Off);
19340
19341         --  The actual check for optimize is done in Gigi. Note that this
19342         --  pragma does not actually change the optimization setting, it
19343         --  simply checks that it is consistent with the pragma.
19344
19345         when Pragma_Optimize =>
19346            Check_No_Identifiers;
19347            Check_Arg_Count (1);
19348            Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
19349
19350         ------------------------
19351         -- Optimize_Alignment --
19352         ------------------------
19353
19354         --  pragma Optimize_Alignment (Time | Space | Off);
19355
19356         when Pragma_Optimize_Alignment => Optimize_Alignment : begin
19357            GNAT_Pragma;
19358            Check_No_Identifiers;
19359            Check_Arg_Count (1);
19360            Check_Valid_Configuration_Pragma;
19361
19362            declare
19363               Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
19364            begin
19365               case Nam is
19366                  when Name_Off   => Opt.Optimize_Alignment := 'O';
19367                  when Name_Space => Opt.Optimize_Alignment := 'S';
19368                  when Name_Time  => Opt.Optimize_Alignment := 'T';
19369
19370                  when others =>
19371                     Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
19372               end case;
19373            end;
19374
19375            --  Set indication that mode is set locally. If we are in fact in a
19376            --  configuration pragma file, this setting is harmless since the
19377            --  switch will get reset anyway at the start of each unit.
19378
19379            Optimize_Alignment_Local := True;
19380         end Optimize_Alignment;
19381
19382         -------------
19383         -- Ordered --
19384         -------------
19385
19386         --  pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
19387
19388         when Pragma_Ordered => Ordered : declare
19389            Assoc   : constant Node_Id := Arg1;
19390            Type_Id : Node_Id;
19391            Typ     : Entity_Id;
19392
19393         begin
19394            GNAT_Pragma;
19395            Check_No_Identifiers;
19396            Check_Arg_Count (1);
19397            Check_Arg_Is_Local_Name (Arg1);
19398
19399            Type_Id := Get_Pragma_Arg (Assoc);
19400            Find_Type (Type_Id);
19401            Typ := Entity (Type_Id);
19402
19403            if Typ = Any_Type then
19404               return;
19405            else
19406               Typ := Underlying_Type (Typ);
19407            end if;
19408
19409            if not Is_Enumeration_Type (Typ) then
19410               Error_Pragma ("pragma% must specify enumeration type");
19411            end if;
19412
19413            Check_First_Subtype (Arg1);
19414            Set_Has_Pragma_Ordered (Base_Type (Typ));
19415         end Ordered;
19416
19417         -------------------
19418         -- Overflow_Mode --
19419         -------------------
19420
19421         --  pragma Overflow_Mode
19422         --    ([General => ] MODE [, [Assertions => ] MODE]);
19423
19424         --  MODE := STRICT | MINIMIZED | ELIMINATED
19425
19426         --  Note: ELIMINATED is allowed only if Long_Long_Integer'Size is 64
19427         --  since System.Bignums makes this assumption. This is true of nearly
19428         --  all (all?) targets.
19429
19430         when Pragma_Overflow_Mode => Overflow_Mode : declare
19431            function Get_Overflow_Mode
19432              (Name : Name_Id;
19433               Arg  : Node_Id) return Overflow_Mode_Type;
19434            --  Function to process one pragma argument, Arg. If an identifier
19435            --  is present, it must be Name. Mode type is returned if a valid
19436            --  argument exists, otherwise an error is signalled.
19437
19438            -----------------------
19439            -- Get_Overflow_Mode --
19440            -----------------------
19441
19442            function Get_Overflow_Mode
19443              (Name : Name_Id;
19444               Arg  : Node_Id) return Overflow_Mode_Type
19445            is
19446               Argx : constant Node_Id := Get_Pragma_Arg (Arg);
19447
19448            begin
19449               Check_Optional_Identifier (Arg, Name);
19450               Check_Arg_Is_Identifier (Argx);
19451
19452               if Chars (Argx) = Name_Strict then
19453                  return Strict;
19454
19455               elsif Chars (Argx) = Name_Minimized then
19456                  return Minimized;
19457
19458               elsif Chars (Argx) = Name_Eliminated then
19459                  if Ttypes.Standard_Long_Long_Integer_Size /= 64 then
19460                     Error_Pragma_Arg
19461                       ("Eliminated not implemented on this target", Argx);
19462                  else
19463                     return Eliminated;
19464                  end if;
19465
19466               else
19467                  Error_Pragma_Arg ("invalid argument for pragma%", Argx);
19468               end if;
19469            end Get_Overflow_Mode;
19470
19471         --  Start of processing for Overflow_Mode
19472
19473         begin
19474            GNAT_Pragma;
19475            Check_At_Least_N_Arguments (1);
19476            Check_At_Most_N_Arguments  (2);
19477
19478            --  Process first argument
19479
19480            Scope_Suppress.Overflow_Mode_General :=
19481              Get_Overflow_Mode (Name_General, Arg1);
19482
19483            --  Case of only one argument
19484
19485            if Arg_Count = 1 then
19486               Scope_Suppress.Overflow_Mode_Assertions :=
19487                 Scope_Suppress.Overflow_Mode_General;
19488
19489            --  Case of two arguments present
19490
19491            else
19492               Scope_Suppress.Overflow_Mode_Assertions  :=
19493                 Get_Overflow_Mode (Name_Assertions, Arg2);
19494            end if;
19495         end Overflow_Mode;
19496
19497         --------------------------
19498         -- Overriding Renamings --
19499         --------------------------
19500
19501         --  pragma Overriding_Renamings;
19502
19503         when Pragma_Overriding_Renamings =>
19504            GNAT_Pragma;
19505            Check_Arg_Count (0);
19506            Check_Valid_Configuration_Pragma;
19507            Overriding_Renamings := True;
19508
19509         ----------
19510         -- Pack --
19511         ----------
19512
19513         --  pragma Pack (first_subtype_LOCAL_NAME);
19514
19515         when Pragma_Pack => Pack : declare
19516            Assoc   : constant Node_Id := Arg1;
19517            Ctyp    : Entity_Id;
19518            Ignore  : Boolean := False;
19519            Typ     : Entity_Id;
19520            Type_Id : Node_Id;
19521
19522         begin
19523            Check_No_Identifiers;
19524            Check_Arg_Count (1);
19525            Check_Arg_Is_Local_Name (Arg1);
19526            Type_Id := Get_Pragma_Arg (Assoc);
19527
19528            if not Is_Entity_Name (Type_Id)
19529              or else not Is_Type (Entity (Type_Id))
19530            then
19531               Error_Pragma_Arg
19532                 ("argument for pragma% must be type or subtype", Arg1);
19533            end if;
19534
19535            Find_Type (Type_Id);
19536            Typ := Entity (Type_Id);
19537
19538            if Typ = Any_Type
19539              or else Rep_Item_Too_Early (Typ, N)
19540            then
19541               return;
19542            else
19543               Typ := Underlying_Type (Typ);
19544            end if;
19545
19546            --  A pragma that applies to a Ghost entity becomes Ghost for the
19547            --  purposes of legality checks and removal of ignored Ghost code.
19548
19549            Mark_Ghost_Pragma (N, Typ);
19550
19551            if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
19552               Error_Pragma ("pragma% must specify array or record type");
19553            end if;
19554
19555            Check_First_Subtype (Arg1);
19556            Check_Duplicate_Pragma (Typ);
19557
19558            --  Array type
19559
19560            if Is_Array_Type (Typ) then
19561               Ctyp := Component_Type (Typ);
19562
19563               --  Ignore pack that does nothing
19564
19565               if Known_Static_Esize (Ctyp)
19566                 and then Known_Static_RM_Size (Ctyp)
19567                 and then Esize (Ctyp) = RM_Size (Ctyp)
19568                 and then Addressable (Esize (Ctyp))
19569               then
19570                  Ignore := True;
19571               end if;
19572
19573               --  Process OK pragma Pack. Note that if there is a separate
19574               --  component clause present, the Pack will be cancelled. This
19575               --  processing is in Freeze.
19576
19577               if not Rep_Item_Too_Late (Typ, N) then
19578
19579                  --  In CodePeer mode, we do not need complex front-end
19580                  --  expansions related to pragma Pack, so disable handling
19581                  --  of pragma Pack.
19582
19583                  if CodePeer_Mode then
19584                     null;
19585
19586                  --  Normal case where we do the pack action
19587
19588                  else
19589                     if not Ignore then
19590                        Set_Is_Packed            (Base_Type (Typ));
19591                        Set_Has_Non_Standard_Rep (Base_Type (Typ));
19592                     end if;
19593
19594                     Set_Has_Pragma_Pack (Base_Type (Typ));
19595                  end if;
19596               end if;
19597
19598            --  For record types, the pack is always effective
19599
19600            else pragma Assert (Is_Record_Type (Typ));
19601               if not Rep_Item_Too_Late (Typ, N) then
19602                  Set_Is_Packed            (Base_Type (Typ));
19603                  Set_Has_Pragma_Pack      (Base_Type (Typ));
19604                  Set_Has_Non_Standard_Rep (Base_Type (Typ));
19605               end if;
19606            end if;
19607         end Pack;
19608
19609         ----------
19610         -- Page --
19611         ----------
19612
19613         --  pragma Page;
19614
19615         --  There is nothing to do here, since we did all the processing for
19616         --  this pragma in Par.Prag (so that it works properly even in syntax
19617         --  only mode).
19618
19619         when Pragma_Page =>
19620            null;
19621
19622         -------------
19623         -- Part_Of --
19624         -------------
19625
19626         --  pragma Part_Of (ABSTRACT_STATE);
19627
19628         --  ABSTRACT_STATE ::= NAME
19629
19630         when Pragma_Part_Of => Part_Of : declare
19631            procedure Propagate_Part_Of
19632              (Pack_Id  : Entity_Id;
19633               State_Id : Entity_Id;
19634               Instance : Node_Id);
19635            --  Propagate the Part_Of indicator to all abstract states and
19636            --  objects declared in the visible state space of a package
19637            --  denoted by Pack_Id. State_Id is the encapsulating state.
19638            --  Instance is the package instantiation node.
19639
19640            -----------------------
19641            -- Propagate_Part_Of --
19642            -----------------------
19643
19644            procedure Propagate_Part_Of
19645              (Pack_Id  : Entity_Id;
19646               State_Id : Entity_Id;
19647               Instance : Node_Id)
19648            is
19649               Has_Item : Boolean := False;
19650               --  Flag set when the visible state space contains at least one
19651               --  abstract state or variable.
19652
19653               procedure Propagate_Part_Of (Pack_Id : Entity_Id);
19654               --  Propagate the Part_Of indicator to all abstract states and
19655               --  objects declared in the visible state space of a package
19656               --  denoted by Pack_Id.
19657
19658               -----------------------
19659               -- Propagate_Part_Of --
19660               -----------------------
19661
19662               procedure Propagate_Part_Of (Pack_Id : Entity_Id) is
19663                  Constits : Elist_Id;
19664                  Item_Id  : Entity_Id;
19665
19666               begin
19667                  --  Traverse the entity chain of the package and set relevant
19668                  --  attributes of abstract states and objects declared in the
19669                  --  visible state space of the package.
19670
19671                  Item_Id := First_Entity (Pack_Id);
19672                  while Present (Item_Id)
19673                    and then not In_Private_Part (Item_Id)
19674                  loop
19675                     --  Do not consider internally generated items
19676
19677                     if not Comes_From_Source (Item_Id) then
19678                        null;
19679
19680                     --  The Part_Of indicator turns an abstract state or an
19681                     --  object into a constituent of the encapsulating state.
19682
19683                     elsif Ekind_In (Item_Id, E_Abstract_State,
19684                                              E_Constant,
19685                                              E_Variable)
19686                     then
19687                        Has_Item := True;
19688                        Constits := Part_Of_Constituents (State_Id);
19689
19690                        if No (Constits) then
19691                           Constits := New_Elmt_List;
19692                           Set_Part_Of_Constituents (State_Id, Constits);
19693                        end if;
19694
19695                        Append_Elmt (Item_Id, Constits);
19696                        Set_Encapsulating_State (Item_Id, State_Id);
19697
19698                     --  Recursively handle nested packages and instantiations
19699
19700                     elsif Ekind (Item_Id) = E_Package then
19701                        Propagate_Part_Of (Item_Id);
19702                     end if;
19703
19704                     Next_Entity (Item_Id);
19705                  end loop;
19706               end Propagate_Part_Of;
19707
19708            --  Start of processing for Propagate_Part_Of
19709
19710            begin
19711               Propagate_Part_Of (Pack_Id);
19712
19713               --  Detect a package instantiation that is subject to a Part_Of
19714               --  indicator, but has no visible state.
19715
19716               if not Has_Item then
19717                  SPARK_Msg_NE
19718                    ("package instantiation & has Part_Of indicator but "
19719                     & "lacks visible state", Instance, Pack_Id);
19720               end if;
19721            end Propagate_Part_Of;
19722
19723            --  Local variables
19724
19725            Constits : Elist_Id;
19726            Encap    : Node_Id;
19727            Encap_Id : Entity_Id;
19728            Item_Id  : Entity_Id;
19729            Legal    : Boolean;
19730            Stmt     : Node_Id;
19731
19732         --  Start of processing for Part_Of
19733
19734         begin
19735            GNAT_Pragma;
19736            Check_No_Identifiers;
19737            Check_Arg_Count (1);
19738
19739            Stmt := Find_Related_Context (N, Do_Checks => True);
19740
19741            --  Object declaration
19742
19743            if Nkind (Stmt) = N_Object_Declaration then
19744               null;
19745
19746            --  Package instantiation
19747
19748            elsif Nkind (Stmt) = N_Package_Instantiation then
19749               null;
19750
19751            --  Single concurrent type declaration
19752
19753            elsif Is_Single_Concurrent_Type_Declaration (Stmt) then
19754               null;
19755
19756            --  Otherwise the pragma is associated with an illegal construct
19757
19758            else
19759               Pragma_Misplaced;
19760               return;
19761            end if;
19762
19763            --  Extract the entity of the related object declaration or package
19764            --  instantiation. In the case of the instantiation, use the entity
19765            --  of the instance spec.
19766
19767            if Nkind (Stmt) = N_Package_Instantiation then
19768               Stmt := Instance_Spec (Stmt);
19769            end if;
19770
19771            Item_Id := Defining_Entity (Stmt);
19772
19773            --  A pragma that applies to a Ghost entity becomes Ghost for the
19774            --  purposes of legality checks and removal of ignored Ghost code.
19775
19776            Mark_Ghost_Pragma (N, Item_Id);
19777
19778            --  Chain the pragma on the contract for further processing by
19779            --  Analyze_Part_Of_In_Decl_Part or for completeness.
19780
19781            Add_Contract_Item (N, Item_Id);
19782
19783            --  A variable may act as constituent of a single concurrent type
19784            --  which in turn could be declared after the variable. Due to this
19785            --  discrepancy, the full analysis of indicator Part_Of is delayed
19786            --  until the end of the enclosing declarative region (see routine
19787            --  Analyze_Part_Of_In_Decl_Part).
19788
19789            if Ekind (Item_Id) = E_Variable then
19790               null;
19791
19792            --  Otherwise indicator Part_Of applies to a constant or a package
19793            --  instantiation.
19794
19795            else
19796               Encap := Get_Pragma_Arg (Arg1);
19797
19798               --  Detect any discrepancies between the placement of the
19799               --  constant or package instantiation with respect to state
19800               --  space and the encapsulating state.
19801
19802               Analyze_Part_Of
19803                 (Indic    => N,
19804                  Item_Id  => Item_Id,
19805                  Encap    => Encap,
19806                  Encap_Id => Encap_Id,
19807                  Legal    => Legal);
19808
19809               if Legal then
19810                  pragma Assert (Present (Encap_Id));
19811
19812                  if Ekind (Item_Id) = E_Constant then
19813                     Constits := Part_Of_Constituents (Encap_Id);
19814
19815                     if No (Constits) then
19816                        Constits := New_Elmt_List;
19817                        Set_Part_Of_Constituents (Encap_Id, Constits);
19818                     end if;
19819
19820                     Append_Elmt (Item_Id, Constits);
19821                     Set_Encapsulating_State (Item_Id, Encap_Id);
19822
19823                  --  Propagate the Part_Of indicator to the visible state
19824                  --  space of the package instantiation.
19825
19826                  else
19827                     Propagate_Part_Of
19828                       (Pack_Id  => Item_Id,
19829                        State_Id => Encap_Id,
19830                        Instance => Stmt);
19831                  end if;
19832               end if;
19833            end if;
19834         end Part_Of;
19835
19836         ----------------------------------
19837         -- Partition_Elaboration_Policy --
19838         ----------------------------------
19839
19840         --  pragma Partition_Elaboration_Policy (policy_IDENTIFIER);
19841
19842         when Pragma_Partition_Elaboration_Policy => PEP : declare
19843            subtype PEP_Range is Name_Id
19844              range First_Partition_Elaboration_Policy_Name
19845                 .. Last_Partition_Elaboration_Policy_Name;
19846            PEP_Val : PEP_Range;
19847            PEP     : Character;
19848
19849         begin
19850            Ada_2005_Pragma;
19851            Check_Arg_Count (1);
19852            Check_No_Identifiers;
19853            Check_Arg_Is_Partition_Elaboration_Policy (Arg1);
19854            Check_Valid_Configuration_Pragma;
19855            PEP_Val := Chars (Get_Pragma_Arg (Arg1));
19856
19857            case PEP_Val is
19858               when Name_Concurrent => PEP := 'C';
19859               when Name_Sequential => PEP := 'S';
19860            end case;
19861
19862            if Partition_Elaboration_Policy /= ' '
19863              and then Partition_Elaboration_Policy /= PEP
19864            then
19865               Error_Msg_Sloc := Partition_Elaboration_Policy_Sloc;
19866               Error_Pragma
19867                 ("partition elaboration policy incompatible with policy#");
19868
19869            --  Set new policy, but always preserve System_Location since we
19870            --  like the error message with the run time name.
19871
19872            else
19873               Partition_Elaboration_Policy := PEP;
19874
19875               if Partition_Elaboration_Policy_Sloc /= System_Location then
19876                  Partition_Elaboration_Policy_Sloc := Loc;
19877               end if;
19878            end if;
19879         end PEP;
19880
19881         -------------
19882         -- Passive --
19883         -------------
19884
19885         --  pragma Passive [(PASSIVE_FORM)];
19886
19887         --  PASSIVE_FORM ::= Semaphore | No
19888
19889         when Pragma_Passive =>
19890            GNAT_Pragma;
19891
19892            if Nkind (Parent (N)) /= N_Task_Definition then
19893               Error_Pragma ("pragma% must be within task definition");
19894            end if;
19895
19896            if Arg_Count /= 0 then
19897               Check_Arg_Count (1);
19898               Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
19899            end if;
19900
19901         ----------------------------------
19902         -- Preelaborable_Initialization --
19903         ----------------------------------
19904
19905         --  pragma Preelaborable_Initialization (DIRECT_NAME);
19906
19907         when Pragma_Preelaborable_Initialization => Preelab_Init : declare
19908            Ent : Entity_Id;
19909
19910         begin
19911            Ada_2005_Pragma;
19912            Check_Arg_Count (1);
19913            Check_No_Identifiers;
19914            Check_Arg_Is_Identifier (Arg1);
19915            Check_Arg_Is_Local_Name (Arg1);
19916            Check_First_Subtype (Arg1);
19917            Ent := Entity (Get_Pragma_Arg (Arg1));
19918
19919            --  A pragma that applies to a Ghost entity becomes Ghost for the
19920            --  purposes of legality checks and removal of ignored Ghost code.
19921
19922            Mark_Ghost_Pragma (N, Ent);
19923
19924            --  The pragma may come from an aspect on a private declaration,
19925            --  even if the freeze point at which this is analyzed in the
19926            --  private part after the full view.
19927
19928            if Has_Private_Declaration (Ent)
19929              and then From_Aspect_Specification (N)
19930            then
19931               null;
19932
19933            --  Check appropriate type argument
19934
19935            elsif Is_Private_Type (Ent)
19936              or else Is_Protected_Type (Ent)
19937              or else (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent))
19938
19939              --  AI05-0028: The pragma applies to all composite types. Note
19940              --  that we apply this binding interpretation to earlier versions
19941              --  of Ada, so there is no Ada 2012 guard. Seems a reasonable
19942              --  choice since there are other compilers that do the same.
19943
19944              or else Is_Composite_Type (Ent)
19945            then
19946               null;
19947
19948            else
19949               Error_Pragma_Arg
19950                 ("pragma % can only be applied to private, formal derived, "
19951                  & "protected, or composite type", Arg1);
19952            end if;
19953
19954            --  Give an error if the pragma is applied to a protected type that
19955            --  does not qualify (due to having entries, or due to components
19956            --  that do not qualify).
19957
19958            if Is_Protected_Type (Ent)
19959              and then not Has_Preelaborable_Initialization (Ent)
19960            then
19961               Error_Msg_N
19962                 ("protected type & does not have preelaborable "
19963                  & "initialization", Ent);
19964
19965            --  Otherwise mark the type as definitely having preelaborable
19966            --  initialization.
19967
19968            else
19969               Set_Known_To_Have_Preelab_Init (Ent);
19970            end if;
19971
19972            if Has_Pragma_Preelab_Init (Ent)
19973              and then Warn_On_Redundant_Constructs
19974            then
19975               Error_Pragma ("?r?duplicate pragma%!");
19976            else
19977               Set_Has_Pragma_Preelab_Init (Ent);
19978            end if;
19979         end Preelab_Init;
19980
19981         --------------------
19982         -- Persistent_BSS --
19983         --------------------
19984
19985         --  pragma Persistent_BSS [(object_NAME)];
19986
19987         when Pragma_Persistent_BSS => Persistent_BSS :  declare
19988            Decl : Node_Id;
19989            Ent  : Entity_Id;
19990            Prag : Node_Id;
19991
19992         begin
19993            GNAT_Pragma;
19994            Check_At_Most_N_Arguments (1);
19995
19996            --  Case of application to specific object (one argument)
19997
19998            if Arg_Count = 1 then
19999               Check_Arg_Is_Library_Level_Local_Name (Arg1);
20000
20001               if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
20002                 or else not
20003                   Ekind_In (Entity (Get_Pragma_Arg (Arg1)), E_Variable,
20004                                                             E_Constant)
20005               then
20006                  Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
20007               end if;
20008
20009               Ent := Entity (Get_Pragma_Arg (Arg1));
20010
20011               --  A pragma that applies to a Ghost entity becomes Ghost for
20012               --  the purposes of legality checks and removal of ignored Ghost
20013               --  code.
20014
20015               Mark_Ghost_Pragma (N, Ent);
20016
20017               --  Check for duplication before inserting in list of
20018               --  representation items.
20019
20020               Check_Duplicate_Pragma (Ent);
20021
20022               if Rep_Item_Too_Late (Ent, N) then
20023                  return;
20024               end if;
20025
20026               Decl := Parent (Ent);
20027
20028               if Present (Expression (Decl)) then
20029                  Error_Pragma_Arg
20030                    ("object for pragma% cannot have initialization", Arg1);
20031               end if;
20032
20033               if not Is_Potentially_Persistent_Type (Etype (Ent)) then
20034                  Error_Pragma_Arg
20035                    ("object type for pragma% is not potentially persistent",
20036                     Arg1);
20037               end if;
20038
20039               Prag :=
20040                 Make_Linker_Section_Pragma
20041                   (Ent, Sloc (N), ".persistent.bss");
20042               Insert_After (N, Prag);
20043               Analyze (Prag);
20044
20045            --  Case of use as configuration pragma with no arguments
20046
20047            else
20048               Check_Valid_Configuration_Pragma;
20049               Persistent_BSS_Mode := True;
20050            end if;
20051         end Persistent_BSS;
20052
20053         --------------------
20054         -- Rename_Pragma --
20055         --------------------
20056
20057         --  pragma Rename_Pragma (
20058         --           [New_Name =>] IDENTIFIER,
20059         --           [Renamed  =>] pragma_IDENTIFIER);
20060
20061         when Pragma_Rename_Pragma => Rename_Pragma : declare
20062            New_Name : constant Node_Id := Get_Pragma_Arg (Arg1);
20063            Old_Name : constant Node_Id := Get_Pragma_Arg (Arg2);
20064
20065         begin
20066            GNAT_Pragma;
20067            Check_Valid_Configuration_Pragma;
20068            Check_Arg_Count (2);
20069            Check_Optional_Identifier (Arg1, Name_New_Name);
20070            Check_Optional_Identifier (Arg2, Name_Renamed);
20071
20072            if Nkind (New_Name) /= N_Identifier then
20073               Error_Pragma_Arg ("identifier expected", Arg1);
20074            end if;
20075
20076            if Nkind (Old_Name) /= N_Identifier then
20077               Error_Pragma_Arg ("identifier expected", Arg2);
20078            end if;
20079
20080            --  The New_Name arg should not be an existing pragma (but we allow
20081            --  it; it's just a warning). The Old_Name arg must be an existing
20082            --  pragma.
20083
20084            if Is_Pragma_Name (Chars (New_Name)) then
20085               Error_Pragma_Arg ("??pragma is already defined", Arg1);
20086            end if;
20087
20088            if not Is_Pragma_Name (Chars (Old_Name)) then
20089               Error_Pragma_Arg ("existing pragma name expected", Arg1);
20090            end if;
20091
20092            Map_Pragma_Name (From => Chars (New_Name), To => Chars (Old_Name));
20093         end Rename_Pragma;
20094
20095         -------------
20096         -- Polling --
20097         -------------
20098
20099         --  pragma Polling (ON | OFF);
20100
20101         when Pragma_Polling =>
20102            GNAT_Pragma;
20103            Check_Arg_Count (1);
20104            Check_No_Identifiers;
20105            Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
20106            Polling_Required := (Chars (Get_Pragma_Arg (Arg1)) = Name_On);
20107
20108         -----------------------------------
20109         -- Post/Post_Class/Postcondition --
20110         -----------------------------------
20111
20112         --  pragma Post (Boolean_EXPRESSION);
20113         --  pragma Post_Class (Boolean_EXPRESSION);
20114         --  pragma Postcondition ([Check   =>] Boolean_EXPRESSION
20115         --                      [,[Message =>] String_EXPRESSION]);
20116
20117         --  Characteristics:
20118
20119         --    * Analysis - The annotation undergoes initial checks to verify
20120         --    the legal placement and context. Secondary checks preanalyze the
20121         --    expression in:
20122
20123         --       Analyze_Pre_Post_Condition_In_Decl_Part
20124
20125         --    * Expansion - The annotation is expanded during the expansion of
20126         --    the related subprogram [body] contract as performed in:
20127
20128         --       Expand_Subprogram_Contract
20129
20130         --    * Template - The annotation utilizes the generic template of the
20131         --    related subprogram [body] when it is:
20132
20133         --       aspect on subprogram declaration
20134         --       aspect on stand-alone subprogram body
20135         --       pragma on stand-alone subprogram body
20136
20137         --    The annotation must prepare its own template when it is:
20138
20139         --       pragma on subprogram declaration
20140
20141         --    * Globals - Capture of global references must occur after full
20142         --    analysis.
20143
20144         --    * Instance - The annotation is instantiated automatically when
20145         --    the related generic subprogram [body] is instantiated except for
20146         --    the "pragma on subprogram declaration" case. In that scenario
20147         --    the annotation must instantiate itself.
20148
20149         when Pragma_Post
20150            | Pragma_Post_Class
20151            | Pragma_Postcondition
20152         =>
20153            Analyze_Pre_Post_Condition;
20154
20155         --------------------------------
20156         -- Pre/Pre_Class/Precondition --
20157         --------------------------------
20158
20159         --  pragma Pre (Boolean_EXPRESSION);
20160         --  pragma Pre_Class (Boolean_EXPRESSION);
20161         --  pragma Precondition ([Check   =>] Boolean_EXPRESSION
20162         --                     [,[Message =>] String_EXPRESSION]);
20163
20164         --  Characteristics:
20165
20166         --    * Analysis - The annotation undergoes initial checks to verify
20167         --    the legal placement and context. Secondary checks preanalyze the
20168         --    expression in:
20169
20170         --       Analyze_Pre_Post_Condition_In_Decl_Part
20171
20172         --    * Expansion - The annotation is expanded during the expansion of
20173         --    the related subprogram [body] contract as performed in:
20174
20175         --       Expand_Subprogram_Contract
20176
20177         --    * Template - The annotation utilizes the generic template of the
20178         --    related subprogram [body] when it is:
20179
20180         --       aspect on subprogram declaration
20181         --       aspect on stand-alone subprogram body
20182         --       pragma on stand-alone subprogram body
20183
20184         --    The annotation must prepare its own template when it is:
20185
20186         --       pragma on subprogram declaration
20187
20188         --    * Globals - Capture of global references must occur after full
20189         --    analysis.
20190
20191         --    * Instance - The annotation is instantiated automatically when
20192         --    the related generic subprogram [body] is instantiated except for
20193         --    the "pragma on subprogram declaration" case. In that scenario
20194         --    the annotation must instantiate itself.
20195
20196         when Pragma_Pre
20197            | Pragma_Pre_Class
20198            | Pragma_Precondition
20199         =>
20200            Analyze_Pre_Post_Condition;
20201
20202         ---------------
20203         -- Predicate --
20204         ---------------
20205
20206         --  pragma Predicate
20207         --    ([Entity =>] type_LOCAL_NAME,
20208         --     [Check  =>] boolean_EXPRESSION);
20209
20210         when Pragma_Predicate => Predicate : declare
20211            Discard : Boolean;
20212            Typ     : Entity_Id;
20213            Type_Id : Node_Id;
20214
20215         begin
20216            GNAT_Pragma;
20217            Check_Arg_Count (2);
20218            Check_Optional_Identifier (Arg1, Name_Entity);
20219            Check_Optional_Identifier (Arg2, Name_Check);
20220
20221            Check_Arg_Is_Local_Name (Arg1);
20222
20223            Type_Id := Get_Pragma_Arg (Arg1);
20224            Find_Type (Type_Id);
20225            Typ := Entity (Type_Id);
20226
20227            if Typ = Any_Type then
20228               return;
20229            end if;
20230
20231            --  A pragma that applies to a Ghost entity becomes Ghost for the
20232            --  purposes of legality checks and removal of ignored Ghost code.
20233
20234            Mark_Ghost_Pragma (N, Typ);
20235
20236            --  The remaining processing is simply to link the pragma on to
20237            --  the rep item chain, for processing when the type is frozen.
20238            --  This is accomplished by a call to Rep_Item_Too_Late. We also
20239            --  mark the type as having predicates.
20240
20241            --  If the current policy for predicate checking is Ignore mark the
20242            --  subtype accordingly. In the case of predicates we consider them
20243            --  enabled unless Ignore is specified (either directly or with a
20244            --  general Assertion_Policy pragma) to preserve existing warnings.
20245
20246            Set_Has_Predicates (Typ);
20247
20248            --  Indicate that the pragma must be processed at the point the
20249            --  type is frozen, as is done for the corresponding aspect.
20250
20251            Set_Has_Delayed_Aspects (Typ);
20252            Set_Has_Delayed_Freeze (Typ);
20253
20254            Set_Predicates_Ignored (Typ,
20255              Present (Check_Policy_List)
20256                and then
20257                  Policy_In_Effect (Name_Dynamic_Predicate) = Name_Ignore);
20258            Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
20259         end Predicate;
20260
20261         -----------------------
20262         -- Predicate_Failure --
20263         -----------------------
20264
20265         --  pragma Predicate_Failure
20266         --    ([Entity  =>] type_LOCAL_NAME,
20267         --     [Message =>] string_EXPRESSION);
20268
20269         when Pragma_Predicate_Failure => Predicate_Failure : declare
20270            Discard : Boolean;
20271            Typ     : Entity_Id;
20272            Type_Id : Node_Id;
20273
20274         begin
20275            GNAT_Pragma;
20276            Check_Arg_Count (2);
20277            Check_Optional_Identifier (Arg1, Name_Entity);
20278            Check_Optional_Identifier (Arg2, Name_Message);
20279
20280            Check_Arg_Is_Local_Name (Arg1);
20281
20282            Type_Id := Get_Pragma_Arg (Arg1);
20283            Find_Type (Type_Id);
20284            Typ := Entity (Type_Id);
20285
20286            if Typ = Any_Type then
20287               return;
20288            end if;
20289
20290            --  A pragma that applies to a Ghost entity becomes Ghost for the
20291            --  purposes of legality checks and removal of ignored Ghost code.
20292
20293            Mark_Ghost_Pragma (N, Typ);
20294
20295            --  The remaining processing is simply to link the pragma on to
20296            --  the rep item chain, for processing when the type is frozen.
20297            --  This is accomplished by a call to Rep_Item_Too_Late.
20298
20299            Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
20300         end Predicate_Failure;
20301
20302         ------------------
20303         -- Preelaborate --
20304         ------------------
20305
20306         --  pragma Preelaborate [(library_unit_NAME)];
20307
20308         --  Set the flag Is_Preelaborated of program unit name entity
20309
20310         when Pragma_Preelaborate => Preelaborate : declare
20311            Pa  : constant Node_Id   := Parent (N);
20312            Pk  : constant Node_Kind := Nkind (Pa);
20313            Ent : Entity_Id;
20314
20315         begin
20316            Check_Ada_83_Warning;
20317            Check_Valid_Library_Unit_Pragma;
20318
20319            if Nkind (N) = N_Null_Statement then
20320               return;
20321            end if;
20322
20323            Ent := Find_Lib_Unit_Name;
20324
20325            --  A pragma that applies to a Ghost entity becomes Ghost for the
20326            --  purposes of legality checks and removal of ignored Ghost code.
20327
20328            Mark_Ghost_Pragma (N, Ent);
20329            Check_Duplicate_Pragma (Ent);
20330
20331            --  This filters out pragmas inside generic parents that show up
20332            --  inside instantiations. Pragmas that come from aspects in the
20333            --  unit are not ignored.
20334
20335            if Present (Ent) then
20336               if Pk = N_Package_Specification
20337                 and then Present (Generic_Parent (Pa))
20338                 and then not From_Aspect_Specification (N)
20339               then
20340                  null;
20341
20342               else
20343                  if not Debug_Flag_U then
20344                     Set_Is_Preelaborated (Ent);
20345
20346                     if Legacy_Elaboration_Checks then
20347                        Set_Suppress_Elaboration_Warnings (Ent);
20348                     end if;
20349                  end if;
20350               end if;
20351            end if;
20352         end Preelaborate;
20353
20354         -------------------------------
20355         -- Prefix_Exception_Messages --
20356         -------------------------------
20357
20358         --  pragma Prefix_Exception_Messages;
20359
20360         when Pragma_Prefix_Exception_Messages =>
20361            GNAT_Pragma;
20362            Check_Valid_Configuration_Pragma;
20363            Check_Arg_Count (0);
20364            Prefix_Exception_Messages := True;
20365
20366         --------------
20367         -- Priority --
20368         --------------
20369
20370         --  pragma Priority (EXPRESSION);
20371
20372         when Pragma_Priority => Priority : declare
20373            P   : constant Node_Id := Parent (N);
20374            Arg : Node_Id;
20375            Ent : Entity_Id;
20376
20377         begin
20378            Check_No_Identifiers;
20379            Check_Arg_Count (1);
20380
20381            --  Subprogram case
20382
20383            if Nkind (P) = N_Subprogram_Body then
20384               Check_In_Main_Program;
20385
20386               Ent := Defining_Unit_Name (Specification (P));
20387
20388               if Nkind (Ent) = N_Defining_Program_Unit_Name then
20389                  Ent := Defining_Identifier (Ent);
20390               end if;
20391
20392               Arg := Get_Pragma_Arg (Arg1);
20393               Analyze_And_Resolve (Arg, Standard_Integer);
20394
20395               --  Must be static
20396
20397               if not Is_OK_Static_Expression (Arg) then
20398                  Flag_Non_Static_Expr
20399                    ("main subprogram priority is not static!", Arg);
20400                  raise Pragma_Exit;
20401
20402               --  If constraint error, then we already signalled an error
20403
20404               elsif Raises_Constraint_Error (Arg) then
20405                  null;
20406
20407               --  Otherwise check in range except if Relaxed_RM_Semantics
20408               --  where we ignore the value if out of range.
20409
20410               else
20411                  if not Relaxed_RM_Semantics
20412                    and then not Is_In_Range (Arg, RTE (RE_Priority))
20413                  then
20414                     Error_Pragma_Arg
20415                       ("main subprogram priority is out of range", Arg1);
20416                  else
20417                     Set_Main_Priority
20418                       (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
20419                  end if;
20420               end if;
20421
20422               --  Load an arbitrary entity from System.Tasking.Stages or
20423               --  System.Tasking.Restricted.Stages (depending on the
20424               --  supported profile) to make sure that one of these packages
20425               --  is implicitly with'ed, since we need to have the tasking
20426               --  run time active for the pragma Priority to have any effect.
20427               --  Previously we with'ed the package System.Tasking, but this
20428               --  package does not trigger the required initialization of the
20429               --  run-time library.
20430
20431               declare
20432                  Discard : Entity_Id;
20433                  pragma Warnings (Off, Discard);
20434               begin
20435                  if Restricted_Profile then
20436                     Discard := RTE (RE_Activate_Restricted_Tasks);
20437                  else
20438                     Discard := RTE (RE_Activate_Tasks);
20439                  end if;
20440               end;
20441
20442            --  Task or Protected, must be of type Integer
20443
20444            elsif Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
20445               Arg := Get_Pragma_Arg (Arg1);
20446               Ent := Defining_Identifier (Parent (P));
20447
20448               --  The expression must be analyzed in the special manner
20449               --  described in "Handling of Default and Per-Object
20450               --  Expressions" in sem.ads.
20451
20452               Preanalyze_Spec_Expression (Arg, RTE (RE_Any_Priority));
20453
20454               if not Is_OK_Static_Expression (Arg) then
20455                  Check_Restriction (Static_Priorities, Arg);
20456               end if;
20457
20458            --  Anything else is incorrect
20459
20460            else
20461               Pragma_Misplaced;
20462            end if;
20463
20464            --  Check duplicate pragma before we chain the pragma in the Rep
20465            --  Item chain of Ent.
20466
20467            Check_Duplicate_Pragma (Ent);
20468            Record_Rep_Item (Ent, N);
20469         end Priority;
20470
20471         -----------------------------------
20472         -- Priority_Specific_Dispatching --
20473         -----------------------------------
20474
20475         --  pragma Priority_Specific_Dispatching (
20476         --    policy_IDENTIFIER,
20477         --    first_priority_EXPRESSION,
20478         --    last_priority_EXPRESSION);
20479
20480         when Pragma_Priority_Specific_Dispatching =>
20481         Priority_Specific_Dispatching : declare
20482            Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
20483            --  This is the entity System.Any_Priority;
20484
20485            DP          : Character;
20486            Lower_Bound : Node_Id;
20487            Upper_Bound : Node_Id;
20488            Lower_Val   : Uint;
20489            Upper_Val   : Uint;
20490
20491         begin
20492            Ada_2005_Pragma;
20493            Check_Arg_Count (3);
20494            Check_No_Identifiers;
20495            Check_Arg_Is_Task_Dispatching_Policy (Arg1);
20496            Check_Valid_Configuration_Pragma;
20497            Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
20498            DP := Fold_Upper (Name_Buffer (1));
20499
20500            Lower_Bound := Get_Pragma_Arg (Arg2);
20501            Check_Arg_Is_OK_Static_Expression (Lower_Bound, Standard_Integer);
20502            Lower_Val := Expr_Value (Lower_Bound);
20503
20504            Upper_Bound := Get_Pragma_Arg (Arg3);
20505            Check_Arg_Is_OK_Static_Expression (Upper_Bound, Standard_Integer);
20506            Upper_Val := Expr_Value (Upper_Bound);
20507
20508            --  It is not allowed to use Task_Dispatching_Policy and
20509            --  Priority_Specific_Dispatching in the same partition.
20510
20511            if Task_Dispatching_Policy /= ' ' then
20512               Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
20513               Error_Pragma
20514                 ("pragma% incompatible with Task_Dispatching_Policy#");
20515
20516            --  Check lower bound in range
20517
20518            elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
20519                    or else
20520                  Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
20521            then
20522               Error_Pragma_Arg
20523                 ("first_priority is out of range", Arg2);
20524
20525            --  Check upper bound in range
20526
20527            elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
20528                    or else
20529                  Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
20530            then
20531               Error_Pragma_Arg
20532                 ("last_priority is out of range", Arg3);
20533
20534            --  Check that the priority range is valid
20535
20536            elsif Lower_Val > Upper_Val then
20537               Error_Pragma
20538                 ("last_priority_expression must be greater than or equal to "
20539                  & "first_priority_expression");
20540
20541            --  Store the new policy, but always preserve System_Location since
20542            --  we like the error message with the run-time name.
20543
20544            else
20545               --  Check overlapping in the priority ranges specified in other
20546               --  Priority_Specific_Dispatching pragmas within the same
20547               --  partition. We can only check those we know about.
20548
20549               for J in
20550                  Specific_Dispatching.First .. Specific_Dispatching.Last
20551               loop
20552                  if Specific_Dispatching.Table (J).First_Priority in
20553                    UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
20554                  or else Specific_Dispatching.Table (J).Last_Priority in
20555                    UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
20556                  then
20557                     Error_Msg_Sloc :=
20558                       Specific_Dispatching.Table (J).Pragma_Loc;
20559                        Error_Pragma
20560                          ("priority range overlaps with "
20561                           & "Priority_Specific_Dispatching#");
20562                  end if;
20563               end loop;
20564
20565               --  The use of Priority_Specific_Dispatching is incompatible
20566               --  with Task_Dispatching_Policy.
20567
20568               if Task_Dispatching_Policy /= ' ' then
20569                  Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
20570                     Error_Pragma
20571                       ("Priority_Specific_Dispatching incompatible "
20572                        & "with Task_Dispatching_Policy#");
20573               end if;
20574
20575               --  The use of Priority_Specific_Dispatching forces ceiling
20576               --  locking policy.
20577
20578               if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
20579                  Error_Msg_Sloc := Locking_Policy_Sloc;
20580                     Error_Pragma
20581                       ("Priority_Specific_Dispatching incompatible "
20582                        & "with Locking_Policy#");
20583
20584               --  Set the Ceiling_Locking policy, but preserve System_Location
20585               --  since we like the error message with the run time name.
20586
20587               else
20588                  Locking_Policy := 'C';
20589
20590                  if Locking_Policy_Sloc /= System_Location then
20591                     Locking_Policy_Sloc := Loc;
20592                  end if;
20593               end if;
20594
20595               --  Add entry in the table
20596
20597               Specific_Dispatching.Append
20598                    ((Dispatching_Policy => DP,
20599                      First_Priority     => UI_To_Int (Lower_Val),
20600                      Last_Priority      => UI_To_Int (Upper_Val),
20601                      Pragma_Loc         => Loc));
20602            end if;
20603         end Priority_Specific_Dispatching;
20604
20605         -------------
20606         -- Profile --
20607         -------------
20608
20609         --  pragma Profile (profile_IDENTIFIER);
20610
20611         --  profile_IDENTIFIER => Restricted | Ravenscar | Rational
20612
20613         when Pragma_Profile =>
20614            Ada_2005_Pragma;
20615            Check_Arg_Count (1);
20616            Check_Valid_Configuration_Pragma;
20617            Check_No_Identifiers;
20618
20619            declare
20620               Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
20621
20622            begin
20623               if Chars (Argx) = Name_Ravenscar then
20624                  Set_Ravenscar_Profile (Ravenscar, N);
20625
20626               elsif Chars (Argx) = Name_Gnat_Extended_Ravenscar then
20627                  Set_Ravenscar_Profile (GNAT_Extended_Ravenscar, N);
20628
20629               elsif Chars (Argx) = Name_Gnat_Ravenscar_EDF then
20630                  Set_Ravenscar_Profile (GNAT_Ravenscar_EDF, N);
20631
20632               elsif Chars (Argx) = Name_Restricted then
20633                  Set_Profile_Restrictions
20634                    (Restricted,
20635                     N, Warn => Treat_Restrictions_As_Warnings);
20636
20637               elsif Chars (Argx) = Name_Rational then
20638                  Set_Rational_Profile;
20639
20640               elsif Chars (Argx) = Name_No_Implementation_Extensions then
20641                  Set_Profile_Restrictions
20642                    (No_Implementation_Extensions,
20643                     N, Warn => Treat_Restrictions_As_Warnings);
20644
20645               else
20646                  Error_Pragma_Arg ("& is not a valid profile", Argx);
20647               end if;
20648            end;
20649
20650         ----------------------
20651         -- Profile_Warnings --
20652         ----------------------
20653
20654         --  pragma Profile_Warnings (profile_IDENTIFIER);
20655
20656         --  profile_IDENTIFIER => Restricted | Ravenscar
20657
20658         when Pragma_Profile_Warnings =>
20659            GNAT_Pragma;
20660            Check_Arg_Count (1);
20661            Check_Valid_Configuration_Pragma;
20662            Check_No_Identifiers;
20663
20664            declare
20665               Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
20666
20667            begin
20668               if Chars (Argx) = Name_Ravenscar then
20669                  Set_Profile_Restrictions (Ravenscar, N, Warn => True);
20670
20671               elsif Chars (Argx) = Name_Restricted then
20672                  Set_Profile_Restrictions (Restricted, N, Warn => True);
20673
20674               elsif Chars (Argx) = Name_No_Implementation_Extensions then
20675                  Set_Profile_Restrictions
20676                    (No_Implementation_Extensions, N, Warn => True);
20677
20678               else
20679                  Error_Pragma_Arg ("& is not a valid profile", Argx);
20680               end if;
20681            end;
20682
20683         --------------------------
20684         -- Propagate_Exceptions --
20685         --------------------------
20686
20687         --  pragma Propagate_Exceptions;
20688
20689         --  Note: this pragma is obsolete and has no effect
20690
20691         when Pragma_Propagate_Exceptions =>
20692            GNAT_Pragma;
20693            Check_Arg_Count (0);
20694
20695            if Warn_On_Obsolescent_Feature then
20696               Error_Msg_N
20697                 ("'G'N'A'T pragma Propagate'_Exceptions is now obsolete " &
20698                  "and has no effect?j?", N);
20699            end if;
20700
20701         -----------------------------
20702         -- Provide_Shift_Operators --
20703         -----------------------------
20704
20705         --  pragma Provide_Shift_Operators (integer_subtype_LOCAL_NAME);
20706
20707         when Pragma_Provide_Shift_Operators =>
20708         Provide_Shift_Operators : declare
20709            Ent : Entity_Id;
20710
20711            procedure Declare_Shift_Operator (Nam : Name_Id);
20712            --  Insert declaration and pragma Instrinsic for named shift op
20713
20714            ----------------------------
20715            -- Declare_Shift_Operator --
20716            ----------------------------
20717
20718            procedure Declare_Shift_Operator (Nam : Name_Id) is
20719               Func   : Node_Id;
20720               Import : Node_Id;
20721
20722            begin
20723               Func :=
20724                 Make_Subprogram_Declaration (Loc,
20725                   Make_Function_Specification (Loc,
20726                     Defining_Unit_Name       =>
20727                       Make_Defining_Identifier (Loc, Chars => Nam),
20728
20729                     Result_Definition        =>
20730                       Make_Identifier (Loc, Chars => Chars (Ent)),
20731
20732                     Parameter_Specifications => New_List (
20733                       Make_Parameter_Specification (Loc,
20734                         Defining_Identifier  =>
20735                           Make_Defining_Identifier (Loc, Name_Value),
20736                         Parameter_Type       =>
20737                           Make_Identifier (Loc, Chars => Chars (Ent))),
20738
20739                       Make_Parameter_Specification (Loc,
20740                         Defining_Identifier  =>
20741                           Make_Defining_Identifier (Loc, Name_Amount),
20742                         Parameter_Type       =>
20743                           New_Occurrence_Of (Standard_Natural, Loc)))));
20744
20745               Import :=
20746                 Make_Pragma (Loc,
20747                   Chars => Name_Import,
20748                   Pragma_Argument_Associations => New_List (
20749                     Make_Pragma_Argument_Association (Loc,
20750                       Expression => Make_Identifier (Loc, Name_Intrinsic)),
20751                     Make_Pragma_Argument_Association (Loc,
20752                       Expression => Make_Identifier (Loc, Nam))));
20753
20754               Insert_After (N, Import);
20755               Insert_After (N, Func);
20756            end Declare_Shift_Operator;
20757
20758         --  Start of processing for Provide_Shift_Operators
20759
20760         begin
20761            GNAT_Pragma;
20762            Check_Arg_Count (1);
20763            Check_Arg_Is_Local_Name (Arg1);
20764
20765            Arg1 := Get_Pragma_Arg (Arg1);
20766
20767            --  We must have an entity name
20768
20769            if not Is_Entity_Name (Arg1) then
20770               Error_Pragma_Arg
20771                 ("pragma % must apply to integer first subtype", Arg1);
20772            end if;
20773
20774            --  If no Entity, means there was a prior error so ignore
20775
20776            if Present (Entity (Arg1)) then
20777               Ent := Entity (Arg1);
20778
20779               --  Apply error checks
20780
20781               if not Is_First_Subtype (Ent) then
20782                  Error_Pragma_Arg
20783                    ("cannot apply pragma %",
20784                     "\& is not a first subtype",
20785                     Arg1);
20786
20787               elsif not Is_Integer_Type (Ent) then
20788                  Error_Pragma_Arg
20789                    ("cannot apply pragma %",
20790                     "\& is not an integer type",
20791                     Arg1);
20792
20793               elsif Has_Shift_Operator (Ent) then
20794                  Error_Pragma_Arg
20795                    ("cannot apply pragma %",
20796                     "\& already has declared shift operators",
20797                     Arg1);
20798
20799               elsif Is_Frozen (Ent) then
20800                  Error_Pragma_Arg
20801                    ("pragma % appears too late",
20802                     "\& is already frozen",
20803                     Arg1);
20804               end if;
20805
20806               --  Now declare the operators. We do this during analysis rather
20807               --  than expansion, since we want the operators available if we
20808               --  are operating in -gnatc or ASIS mode.
20809
20810               Declare_Shift_Operator (Name_Rotate_Left);
20811               Declare_Shift_Operator (Name_Rotate_Right);
20812               Declare_Shift_Operator (Name_Shift_Left);
20813               Declare_Shift_Operator (Name_Shift_Right);
20814               Declare_Shift_Operator (Name_Shift_Right_Arithmetic);
20815            end if;
20816         end Provide_Shift_Operators;
20817
20818         ------------------
20819         -- Psect_Object --
20820         ------------------
20821
20822         --  pragma Psect_Object (
20823         --        [Internal =>] LOCAL_NAME,
20824         --     [, [External =>] EXTERNAL_SYMBOL]
20825         --     [, [Size     =>] EXTERNAL_SYMBOL]);
20826
20827         when Pragma_Common_Object
20828            | Pragma_Psect_Object
20829         =>
20830         Psect_Object : declare
20831            Args  : Args_List (1 .. 3);
20832            Names : constant Name_List (1 .. 3) := (
20833                      Name_Internal,
20834                      Name_External,
20835                      Name_Size);
20836
20837            Internal : Node_Id renames Args (1);
20838            External : Node_Id renames Args (2);
20839            Size     : Node_Id renames Args (3);
20840
20841            Def_Id : Entity_Id;
20842
20843            procedure Check_Arg (Arg : Node_Id);
20844            --  Checks that argument is either a string literal or an
20845            --  identifier, and posts error message if not.
20846
20847            ---------------
20848            -- Check_Arg --
20849            ---------------
20850
20851            procedure Check_Arg (Arg : Node_Id) is
20852            begin
20853               if not Nkind_In (Original_Node (Arg),
20854                                N_String_Literal,
20855                                N_Identifier)
20856               then
20857                  Error_Pragma_Arg
20858                    ("inappropriate argument for pragma %", Arg);
20859               end if;
20860            end Check_Arg;
20861
20862         --  Start of processing for Common_Object/Psect_Object
20863
20864         begin
20865            GNAT_Pragma;
20866            Gather_Associations (Names, Args);
20867            Process_Extended_Import_Export_Internal_Arg (Internal);
20868
20869            Def_Id := Entity (Internal);
20870
20871            if not Ekind_In (Def_Id, E_Constant, E_Variable) then
20872               Error_Pragma_Arg
20873                 ("pragma% must designate an object", Internal);
20874            end if;
20875
20876            Check_Arg (Internal);
20877
20878            if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
20879               Error_Pragma_Arg
20880                 ("cannot use pragma% for imported/exported object",
20881                  Internal);
20882            end if;
20883
20884            if Is_Concurrent_Type (Etype (Internal)) then
20885               Error_Pragma_Arg
20886                 ("cannot specify pragma % for task/protected object",
20887                  Internal);
20888            end if;
20889
20890            if Has_Rep_Pragma (Def_Id, Name_Common_Object)
20891                 or else
20892               Has_Rep_Pragma (Def_Id, Name_Psect_Object)
20893            then
20894               Error_Msg_N ("??duplicate Common/Psect_Object pragma", N);
20895            end if;
20896
20897            if Ekind (Def_Id) = E_Constant then
20898               Error_Pragma_Arg
20899                 ("cannot specify pragma % for a constant", Internal);
20900            end if;
20901
20902            if Is_Record_Type (Etype (Internal)) then
20903               declare
20904                  Ent  : Entity_Id;
20905                  Decl : Entity_Id;
20906
20907               begin
20908                  Ent := First_Entity (Etype (Internal));
20909                  while Present (Ent) loop
20910                     Decl := Declaration_Node (Ent);
20911
20912                     if Ekind (Ent) = E_Component
20913                       and then Nkind (Decl) = N_Component_Declaration
20914                       and then Present (Expression (Decl))
20915                       and then Warn_On_Export_Import
20916                     then
20917                        Error_Msg_N
20918                          ("?x?object for pragma % has defaults", Internal);
20919                        exit;
20920
20921                     else
20922                        Next_Entity (Ent);
20923                     end if;
20924                  end loop;
20925               end;
20926            end if;
20927
20928            if Present (Size) then
20929               Check_Arg (Size);
20930            end if;
20931
20932            if Present (External) then
20933               Check_Arg_Is_External_Name (External);
20934            end if;
20935
20936            --  If all error tests pass, link pragma on to the rep item chain
20937
20938            Record_Rep_Item (Def_Id, N);
20939         end Psect_Object;
20940
20941         ----------
20942         -- Pure --
20943         ----------
20944
20945         --  pragma Pure [(library_unit_NAME)];
20946
20947         when Pragma_Pure => Pure : declare
20948            Ent : Entity_Id;
20949
20950         begin
20951            Check_Ada_83_Warning;
20952
20953            --  If the pragma comes from a subprogram instantiation, nothing to
20954            --  check, this can happen at any level of nesting.
20955
20956            if Is_Wrapper_Package (Current_Scope) then
20957               return;
20958            else
20959               Check_Valid_Library_Unit_Pragma;
20960            end if;
20961
20962            if Nkind (N) = N_Null_Statement then
20963               return;
20964            end if;
20965
20966            Ent := Find_Lib_Unit_Name;
20967
20968            --  A pragma that applies to a Ghost entity becomes Ghost for the
20969            --  purposes of legality checks and removal of ignored Ghost code.
20970
20971            Mark_Ghost_Pragma (N, Ent);
20972
20973            if not Debug_Flag_U then
20974               Set_Is_Pure (Ent);
20975               Set_Has_Pragma_Pure (Ent);
20976
20977               if Legacy_Elaboration_Checks then
20978                  Set_Suppress_Elaboration_Warnings (Ent);
20979               end if;
20980            end if;
20981         end Pure;
20982
20983         -------------------
20984         -- Pure_Function --
20985         -------------------
20986
20987         --  pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
20988
20989         when Pragma_Pure_Function => Pure_Function : declare
20990            Def_Id    : Entity_Id;
20991            E         : Entity_Id;
20992            E_Id      : Node_Id;
20993            Effective : Boolean := False;
20994
20995         begin
20996            GNAT_Pragma;
20997            Check_Arg_Count (1);
20998            Check_Optional_Identifier (Arg1, Name_Entity);
20999            Check_Arg_Is_Local_Name (Arg1);
21000            E_Id := Get_Pragma_Arg (Arg1);
21001
21002            if Etype (E_Id) = Any_Type then
21003               return;
21004            end if;
21005
21006            --  Loop through homonyms (overloadings) of referenced entity
21007
21008            E := Entity (E_Id);
21009
21010            --  A pragma that applies to a Ghost entity becomes Ghost for the
21011            --  purposes of legality checks and removal of ignored Ghost code.
21012
21013            Mark_Ghost_Pragma (N, E);
21014
21015            if Present (E) then
21016               loop
21017                  Def_Id := Get_Base_Subprogram (E);
21018
21019                  if not Ekind_In (Def_Id, E_Function,
21020                                           E_Generic_Function,
21021                                           E_Operator)
21022                  then
21023                     Error_Pragma_Arg
21024                       ("pragma% requires a function name", Arg1);
21025                  end if;
21026
21027                  Set_Is_Pure (Def_Id);
21028
21029                  if not Has_Pragma_Pure_Function (Def_Id) then
21030                     Set_Has_Pragma_Pure_Function (Def_Id);
21031                     Effective := True;
21032                  end if;
21033
21034                  exit when From_Aspect_Specification (N);
21035                  E := Homonym (E);
21036                  exit when No (E) or else Scope (E) /= Current_Scope;
21037               end loop;
21038
21039               if not Effective
21040                 and then Warn_On_Redundant_Constructs
21041               then
21042                  Error_Msg_NE
21043                    ("pragma Pure_Function on& is redundant?r?",
21044                     N, Entity (E_Id));
21045               end if;
21046            end if;
21047         end Pure_Function;
21048
21049         --------------------
21050         -- Queuing_Policy --
21051         --------------------
21052
21053         --  pragma Queuing_Policy (policy_IDENTIFIER);
21054
21055         when Pragma_Queuing_Policy => declare
21056            QP : Character;
21057
21058         begin
21059            Check_Ada_83_Warning;
21060            Check_Arg_Count (1);
21061            Check_No_Identifiers;
21062            Check_Arg_Is_Queuing_Policy (Arg1);
21063            Check_Valid_Configuration_Pragma;
21064            Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
21065            QP := Fold_Upper (Name_Buffer (1));
21066
21067            if Queuing_Policy /= ' '
21068              and then Queuing_Policy /= QP
21069            then
21070               Error_Msg_Sloc := Queuing_Policy_Sloc;
21071               Error_Pragma ("queuing policy incompatible with policy#");
21072
21073            --  Set new policy, but always preserve System_Location since we
21074            --  like the error message with the run time name.
21075
21076            else
21077               Queuing_Policy := QP;
21078
21079               if Queuing_Policy_Sloc /= System_Location then
21080                  Queuing_Policy_Sloc := Loc;
21081               end if;
21082            end if;
21083         end;
21084
21085         --------------
21086         -- Rational --
21087         --------------
21088
21089         --  pragma Rational, for compatibility with foreign compiler
21090
21091         when Pragma_Rational =>
21092            Set_Rational_Profile;
21093
21094         ---------------------
21095         -- Refined_Depends --
21096         ---------------------
21097
21098         --  pragma Refined_Depends (DEPENDENCY_RELATION);
21099
21100         --  DEPENDENCY_RELATION ::=
21101         --     null
21102         --  | (DEPENDENCY_CLAUSE {, DEPENDENCY_CLAUSE})
21103
21104         --  DEPENDENCY_CLAUSE ::=
21105         --    OUTPUT_LIST =>[+] INPUT_LIST
21106         --  | NULL_DEPENDENCY_CLAUSE
21107
21108         --  NULL_DEPENDENCY_CLAUSE ::= null => INPUT_LIST
21109
21110         --  OUTPUT_LIST ::= OUTPUT | (OUTPUT {, OUTPUT})
21111
21112         --  INPUT_LIST ::= null | INPUT | (INPUT {, INPUT})
21113
21114         --  OUTPUT ::= NAME | FUNCTION_RESULT
21115         --  INPUT  ::= NAME
21116
21117         --  where FUNCTION_RESULT is a function Result attribute_reference
21118
21119         --  Characteristics:
21120
21121         --    * Analysis - The annotation undergoes initial checks to verify
21122         --    the legal placement and context. Secondary checks fully analyze
21123         --    the dependency clauses/global list in:
21124
21125         --       Analyze_Refined_Depends_In_Decl_Part
21126
21127         --    * Expansion - None.
21128
21129         --    * Template - The annotation utilizes the generic template of the
21130         --    related subprogram body.
21131
21132         --    * Globals - Capture of global references must occur after full
21133         --    analysis.
21134
21135         --    * Instance - The annotation is instantiated automatically when
21136         --    the related generic subprogram body is instantiated.
21137
21138         when Pragma_Refined_Depends => Refined_Depends : declare
21139            Body_Id : Entity_Id;
21140            Legal   : Boolean;
21141            Spec_Id : Entity_Id;
21142
21143         begin
21144            Analyze_Refined_Depends_Global_Post (Spec_Id, Body_Id, Legal);
21145
21146            if Legal then
21147
21148               --  Chain the pragma on the contract for further processing by
21149               --  Analyze_Refined_Depends_In_Decl_Part.
21150
21151               Add_Contract_Item (N, Body_Id);
21152
21153               --  The legality checks of pragmas Refined_Depends and
21154               --  Refined_Global are affected by the SPARK mode in effect and
21155               --  the volatility of the context. In addition these two pragmas
21156               --  are subject to an inherent order:
21157
21158               --    1) Refined_Global
21159               --    2) Refined_Depends
21160
21161               --  Analyze all these pragmas in the order outlined above
21162
21163               Analyze_If_Present (Pragma_SPARK_Mode);
21164               Analyze_If_Present (Pragma_Volatile_Function);
21165               Analyze_If_Present (Pragma_Refined_Global);
21166               Analyze_Refined_Depends_In_Decl_Part (N);
21167            end if;
21168         end Refined_Depends;
21169
21170         --------------------
21171         -- Refined_Global --
21172         --------------------
21173
21174         --  pragma Refined_Global (GLOBAL_SPECIFICATION);
21175
21176         --  GLOBAL_SPECIFICATION ::=
21177         --     null
21178         --  | (GLOBAL_LIST)
21179         --  | (MODED_GLOBAL_LIST {, MODED_GLOBAL_LIST})
21180
21181         --  MODED_GLOBAL_LIST ::= MODE_SELECTOR => GLOBAL_LIST
21182
21183         --  MODE_SELECTOR ::= In_Out | Input | Output | Proof_In
21184         --  GLOBAL_LIST   ::= GLOBAL_ITEM | (GLOBAL_ITEM {, GLOBAL_ITEM})
21185         --  GLOBAL_ITEM   ::= NAME
21186
21187         --  Characteristics:
21188
21189         --    * Analysis - The annotation undergoes initial checks to verify
21190         --    the legal placement and context. Secondary checks fully analyze
21191         --    the dependency clauses/global list in:
21192
21193         --       Analyze_Refined_Global_In_Decl_Part
21194
21195         --    * Expansion - None.
21196
21197         --    * Template - The annotation utilizes the generic template of the
21198         --    related subprogram body.
21199
21200         --    * Globals - Capture of global references must occur after full
21201         --    analysis.
21202
21203         --    * Instance - The annotation is instantiated automatically when
21204         --    the related generic subprogram body is instantiated.
21205
21206         when Pragma_Refined_Global => Refined_Global : declare
21207            Body_Id : Entity_Id;
21208            Legal   : Boolean;
21209            Spec_Id : Entity_Id;
21210
21211         begin
21212            Analyze_Refined_Depends_Global_Post (Spec_Id, Body_Id, Legal);
21213
21214            if Legal then
21215
21216               --  Chain the pragma on the contract for further processing by
21217               --  Analyze_Refined_Global_In_Decl_Part.
21218
21219               Add_Contract_Item (N, Body_Id);
21220
21221               --  The legality checks of pragmas Refined_Depends and
21222               --  Refined_Global are affected by the SPARK mode in effect and
21223               --  the volatility of the context. In addition these two pragmas
21224               --  are subject to an inherent order:
21225
21226               --    1) Refined_Global
21227               --    2) Refined_Depends
21228
21229               --  Analyze all these pragmas in the order outlined above
21230
21231               Analyze_If_Present (Pragma_SPARK_Mode);
21232               Analyze_If_Present (Pragma_Volatile_Function);
21233               Analyze_Refined_Global_In_Decl_Part (N);
21234               Analyze_If_Present (Pragma_Refined_Depends);
21235            end if;
21236         end Refined_Global;
21237
21238         ------------------
21239         -- Refined_Post --
21240         ------------------
21241
21242         --  pragma Refined_Post (boolean_EXPRESSION);
21243
21244         --  Characteristics:
21245
21246         --    * Analysis - The annotation is fully analyzed immediately upon
21247         --    elaboration as it cannot forward reference entities.
21248
21249         --    * Expansion - The annotation is expanded during the expansion of
21250         --    the related subprogram body contract as performed in:
21251
21252         --       Expand_Subprogram_Contract
21253
21254         --    * Template - The annotation utilizes the generic template of the
21255         --    related subprogram body.
21256
21257         --    * Globals - Capture of global references must occur after full
21258         --    analysis.
21259
21260         --    * Instance - The annotation is instantiated automatically when
21261         --    the related generic subprogram body is instantiated.
21262
21263         when Pragma_Refined_Post => Refined_Post : declare
21264            Body_Id : Entity_Id;
21265            Legal   : Boolean;
21266            Spec_Id : Entity_Id;
21267
21268         begin
21269            Analyze_Refined_Depends_Global_Post (Spec_Id, Body_Id, Legal);
21270
21271            --  Fully analyze the pragma when it appears inside a subprogram
21272            --  body because it cannot benefit from forward references.
21273
21274            if Legal then
21275
21276               --  Chain the pragma on the contract for completeness
21277
21278               Add_Contract_Item (N, Body_Id);
21279
21280               --  The legality checks of pragma Refined_Post are affected by
21281               --  the SPARK mode in effect and the volatility of the context.
21282               --  Analyze all pragmas in a specific order.
21283
21284               Analyze_If_Present (Pragma_SPARK_Mode);
21285               Analyze_If_Present (Pragma_Volatile_Function);
21286               Analyze_Pre_Post_Condition_In_Decl_Part (N);
21287
21288               --  Currently it is not possible to inline pre/postconditions on
21289               --  a subprogram subject to pragma Inline_Always.
21290
21291               Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
21292            end if;
21293         end Refined_Post;
21294
21295         -------------------
21296         -- Refined_State --
21297         -------------------
21298
21299         --  pragma Refined_State (REFINEMENT_LIST);
21300
21301         --  REFINEMENT_LIST ::=
21302         --    (REFINEMENT_CLAUSE {, REFINEMENT_CLAUSE})
21303
21304         --  REFINEMENT_CLAUSE ::= state_NAME => CONSTITUENT_LIST
21305
21306         --  CONSTITUENT_LIST ::=
21307         --     null
21308         --  |  CONSTITUENT
21309         --  | (CONSTITUENT {, CONSTITUENT})
21310
21311         --  CONSTITUENT ::= object_NAME | state_NAME
21312
21313         --  Characteristics:
21314
21315         --    * Analysis - The annotation undergoes initial checks to verify
21316         --    the legal placement and context. Secondary checks preanalyze the
21317         --    refinement clauses in:
21318
21319         --       Analyze_Refined_State_In_Decl_Part
21320
21321         --    * Expansion - None.
21322
21323         --    * Template - The annotation utilizes the template of the related
21324         --    package body.
21325
21326         --    * Globals - Capture of global references must occur after full
21327         --    analysis.
21328
21329         --    * Instance - The annotation is instantiated automatically when
21330         --    the related generic package body is instantiated.
21331
21332         when Pragma_Refined_State => Refined_State : declare
21333            Pack_Decl : Node_Id;
21334            Spec_Id   : Entity_Id;
21335
21336         begin
21337            GNAT_Pragma;
21338            Check_No_Identifiers;
21339            Check_Arg_Count (1);
21340
21341            Pack_Decl := Find_Related_Package_Or_Body (N, Do_Checks => True);
21342
21343            --  Ensure the proper placement of the pragma. Refined states must
21344            --  be associated with a package body.
21345
21346            if Nkind (Pack_Decl) = N_Package_Body then
21347               null;
21348
21349            --  Otherwise the pragma is associated with an illegal construct
21350
21351            else
21352               Pragma_Misplaced;
21353               return;
21354            end if;
21355
21356            Spec_Id := Corresponding_Spec (Pack_Decl);
21357
21358            --  A pragma that applies to a Ghost entity becomes Ghost for the
21359            --  purposes of legality checks and removal of ignored Ghost code.
21360
21361            Mark_Ghost_Pragma (N, Spec_Id);
21362
21363            --  Chain the pragma on the contract for further processing by
21364            --  Analyze_Refined_State_In_Decl_Part.
21365
21366            Add_Contract_Item (N, Defining_Entity (Pack_Decl));
21367
21368            --  The legality checks of pragma Refined_State are affected by the
21369            --  SPARK mode in effect. Analyze all pragmas in a specific order.
21370
21371            Analyze_If_Present (Pragma_SPARK_Mode);
21372
21373            --  State refinement is allowed only when the corresponding package
21374            --  declaration has non-null pragma Abstract_State. Refinement not
21375            --  enforced when SPARK checks are suppressed (SPARK RM 7.2.2(3)).
21376
21377            if SPARK_Mode /= Off
21378              and then
21379                (No (Abstract_States (Spec_Id))
21380                  or else Has_Null_Abstract_State (Spec_Id))
21381            then
21382               Error_Msg_NE
21383                 ("useless refinement, package & does not define abstract "
21384                  & "states", N, Spec_Id);
21385               return;
21386            end if;
21387         end Refined_State;
21388
21389         -----------------------
21390         -- Relative_Deadline --
21391         -----------------------
21392
21393         --  pragma Relative_Deadline (time_span_EXPRESSION);
21394
21395         when Pragma_Relative_Deadline => Relative_Deadline : declare
21396            P   : constant Node_Id := Parent (N);
21397            Arg : Node_Id;
21398
21399         begin
21400            Ada_2005_Pragma;
21401            Check_No_Identifiers;
21402            Check_Arg_Count (1);
21403
21404            Arg := Get_Pragma_Arg (Arg1);
21405
21406            --  The expression must be analyzed in the special manner described
21407            --  in "Handling of Default and Per-Object Expressions" in sem.ads.
21408
21409            Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
21410
21411            --  Subprogram case
21412
21413            if Nkind (P) = N_Subprogram_Body then
21414               Check_In_Main_Program;
21415
21416            --  Only Task and subprogram cases allowed
21417
21418            elsif Nkind (P) /= N_Task_Definition then
21419               Pragma_Misplaced;
21420            end if;
21421
21422            --  Check duplicate pragma before we set the corresponding flag
21423
21424            if Has_Relative_Deadline_Pragma (P) then
21425               Error_Pragma ("duplicate pragma% not allowed");
21426            end if;
21427
21428            --  Set Has_Relative_Deadline_Pragma only for tasks. Note that
21429            --  Relative_Deadline pragma node cannot be inserted in the Rep
21430            --  Item chain of Ent since it is rewritten by the expander as a
21431            --  procedure call statement that will break the chain.
21432
21433            Set_Has_Relative_Deadline_Pragma (P);
21434         end Relative_Deadline;
21435
21436         ------------------------
21437         -- Remote_Access_Type --
21438         ------------------------
21439
21440         --  pragma Remote_Access_Type ([Entity =>] formal_type_LOCAL_NAME);
21441
21442         when Pragma_Remote_Access_Type => Remote_Access_Type : declare
21443            E : Entity_Id;
21444
21445         begin
21446            GNAT_Pragma;
21447            Check_Arg_Count (1);
21448            Check_Optional_Identifier (Arg1, Name_Entity);
21449            Check_Arg_Is_Local_Name (Arg1);
21450
21451            E := Entity (Get_Pragma_Arg (Arg1));
21452
21453            --  A pragma that applies to a Ghost entity becomes Ghost for the
21454            --  purposes of legality checks and removal of ignored Ghost code.
21455
21456            Mark_Ghost_Pragma (N, E);
21457
21458            if Nkind (Parent (E)) = N_Formal_Type_Declaration
21459              and then Ekind (E) = E_General_Access_Type
21460              and then Is_Class_Wide_Type (Directly_Designated_Type (E))
21461              and then Scope (Root_Type (Directly_Designated_Type (E)))
21462                         = Scope (E)
21463              and then Is_Valid_Remote_Object_Type
21464                         (Root_Type (Directly_Designated_Type (E)))
21465            then
21466               Set_Is_Remote_Types (E);
21467
21468            else
21469               Error_Pragma_Arg
21470                 ("pragma% applies only to formal access-to-class-wide types",
21471                  Arg1);
21472            end if;
21473         end Remote_Access_Type;
21474
21475         ---------------------------
21476         -- Remote_Call_Interface --
21477         ---------------------------
21478
21479         --  pragma Remote_Call_Interface [(library_unit_NAME)];
21480
21481         when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
21482            Cunit_Node : Node_Id;
21483            Cunit_Ent  : Entity_Id;
21484            K          : Node_Kind;
21485
21486         begin
21487            Check_Ada_83_Warning;
21488            Check_Valid_Library_Unit_Pragma;
21489
21490            if Nkind (N) = N_Null_Statement then
21491               return;
21492            end if;
21493
21494            Cunit_Node := Cunit (Current_Sem_Unit);
21495            K          := Nkind (Unit (Cunit_Node));
21496            Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
21497
21498            --  A pragma that applies to a Ghost entity becomes Ghost for the
21499            --  purposes of legality checks and removal of ignored Ghost code.
21500
21501            Mark_Ghost_Pragma (N, Cunit_Ent);
21502
21503            if K = N_Package_Declaration
21504              or else K = N_Generic_Package_Declaration
21505              or else K = N_Subprogram_Declaration
21506              or else K = N_Generic_Subprogram_Declaration
21507              or else (K = N_Subprogram_Body
21508                         and then Acts_As_Spec (Unit (Cunit_Node)))
21509            then
21510               null;
21511            else
21512               Error_Pragma (
21513                 "pragma% must apply to package or subprogram declaration");
21514            end if;
21515
21516            Set_Is_Remote_Call_Interface (Cunit_Ent);
21517         end Remote_Call_Interface;
21518
21519         ------------------
21520         -- Remote_Types --
21521         ------------------
21522
21523         --  pragma Remote_Types [(library_unit_NAME)];
21524
21525         when Pragma_Remote_Types => Remote_Types : declare
21526            Cunit_Node : Node_Id;
21527            Cunit_Ent  : Entity_Id;
21528
21529         begin
21530            Check_Ada_83_Warning;
21531            Check_Valid_Library_Unit_Pragma;
21532
21533            if Nkind (N) = N_Null_Statement then
21534               return;
21535            end if;
21536
21537            Cunit_Node := Cunit (Current_Sem_Unit);
21538            Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
21539
21540            --  A pragma that applies to a Ghost entity becomes Ghost for the
21541            --  purposes of legality checks and removal of ignored Ghost code.
21542
21543            Mark_Ghost_Pragma (N, Cunit_Ent);
21544
21545            if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
21546                                                N_Generic_Package_Declaration)
21547            then
21548               Error_Pragma
21549                 ("pragma% can only apply to a package declaration");
21550            end if;
21551
21552            Set_Is_Remote_Types (Cunit_Ent);
21553         end Remote_Types;
21554
21555         ---------------
21556         -- Ravenscar --
21557         ---------------
21558
21559         --  pragma Ravenscar;
21560
21561         when Pragma_Ravenscar =>
21562            GNAT_Pragma;
21563            Check_Arg_Count (0);
21564            Check_Valid_Configuration_Pragma;
21565            Set_Ravenscar_Profile (Ravenscar, N);
21566
21567            if Warn_On_Obsolescent_Feature then
21568               Error_Msg_N
21569                 ("pragma Ravenscar is an obsolescent feature?j?", N);
21570               Error_Msg_N
21571                 ("|use pragma Profile (Ravenscar) instead?j?", N);
21572            end if;
21573
21574         -------------------------
21575         -- Restricted_Run_Time --
21576         -------------------------
21577
21578         --  pragma Restricted_Run_Time;
21579
21580         when Pragma_Restricted_Run_Time =>
21581            GNAT_Pragma;
21582            Check_Arg_Count (0);
21583            Check_Valid_Configuration_Pragma;
21584            Set_Profile_Restrictions
21585              (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
21586
21587            if Warn_On_Obsolescent_Feature then
21588               Error_Msg_N
21589                 ("pragma Restricted_Run_Time is an obsolescent feature?j?",
21590                  N);
21591               Error_Msg_N
21592                 ("|use pragma Profile (Restricted) instead?j?", N);
21593            end if;
21594
21595         ------------------
21596         -- Restrictions --
21597         ------------------
21598
21599         --  pragma Restrictions (RESTRICTION {, RESTRICTION});
21600
21601         --  RESTRICTION ::=
21602         --    restriction_IDENTIFIER
21603         --  | restriction_parameter_IDENTIFIER => EXPRESSION
21604
21605         when Pragma_Restrictions =>
21606            Process_Restrictions_Or_Restriction_Warnings
21607              (Warn => Treat_Restrictions_As_Warnings);
21608
21609         --------------------------
21610         -- Restriction_Warnings --
21611         --------------------------
21612
21613         --  pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
21614
21615         --  RESTRICTION ::=
21616         --    restriction_IDENTIFIER
21617         --  | restriction_parameter_IDENTIFIER => EXPRESSION
21618
21619         when Pragma_Restriction_Warnings =>
21620            GNAT_Pragma;
21621            Process_Restrictions_Or_Restriction_Warnings (Warn => True);
21622
21623         ----------------
21624         -- Reviewable --
21625         ----------------
21626
21627         --  pragma Reviewable;
21628
21629         when Pragma_Reviewable =>
21630            Check_Ada_83_Warning;
21631            Check_Arg_Count (0);
21632
21633            --  Call dummy debugging function rv. This is done to assist front
21634            --  end debugging. By placing a Reviewable pragma in the source
21635            --  program, a breakpoint on rv catches this place in the source,
21636            --  allowing convenient stepping to the point of interest.
21637
21638            rv;
21639
21640         --------------------------
21641         -- Secondary_Stack_Size --
21642         --------------------------
21643
21644         --  pragma Secondary_Stack_Size (EXPRESSION);
21645
21646         when Pragma_Secondary_Stack_Size => Secondary_Stack_Size : declare
21647            P   : constant Node_Id := Parent (N);
21648            Arg : Node_Id;
21649            Ent : Entity_Id;
21650
21651         begin
21652            GNAT_Pragma;
21653            Check_No_Identifiers;
21654            Check_Arg_Count (1);
21655
21656            if Nkind (P) = N_Task_Definition then
21657               Arg := Get_Pragma_Arg (Arg1);
21658               Ent := Defining_Identifier (Parent (P));
21659
21660               --  The expression must be analyzed in the special manner
21661               --  described in "Handling of Default Expressions" in sem.ads.
21662
21663               Preanalyze_Spec_Expression (Arg, Any_Integer);
21664
21665               --  The pragma cannot appear if the No_Secondary_Stack
21666               --  restriction is in effect.
21667
21668               Check_Restriction (No_Secondary_Stack, Arg);
21669
21670            --  Anything else is incorrect
21671
21672            else
21673               Pragma_Misplaced;
21674            end if;
21675
21676            --  Check duplicate pragma before we chain the pragma in the Rep
21677            --  Item chain of Ent.
21678
21679            Check_Duplicate_Pragma (Ent);
21680            Record_Rep_Item (Ent, N);
21681         end Secondary_Stack_Size;
21682
21683         --------------------------
21684         -- Short_Circuit_And_Or --
21685         --------------------------
21686
21687         --  pragma Short_Circuit_And_Or;
21688
21689         when Pragma_Short_Circuit_And_Or =>
21690            GNAT_Pragma;
21691            Check_Arg_Count (0);
21692            Check_Valid_Configuration_Pragma;
21693            Short_Circuit_And_Or := True;
21694
21695         -------------------
21696         -- Share_Generic --
21697         -------------------
21698
21699         --  pragma Share_Generic (GNAME {, GNAME});
21700
21701         --  GNAME ::= generic_unit_NAME | generic_instance_NAME
21702
21703         when Pragma_Share_Generic =>
21704            GNAT_Pragma;
21705            Process_Generic_List;
21706
21707         ------------
21708         -- Shared --
21709         ------------
21710
21711         --  pragma Shared (LOCAL_NAME);
21712
21713         when Pragma_Shared =>
21714            GNAT_Pragma;
21715            Process_Atomic_Independent_Shared_Volatile;
21716
21717         --------------------
21718         -- Shared_Passive --
21719         --------------------
21720
21721         --  pragma Shared_Passive [(library_unit_NAME)];
21722
21723         --  Set the flag Is_Shared_Passive of program unit name entity
21724
21725         when Pragma_Shared_Passive => Shared_Passive : declare
21726            Cunit_Node : Node_Id;
21727            Cunit_Ent  : Entity_Id;
21728
21729         begin
21730            Check_Ada_83_Warning;
21731            Check_Valid_Library_Unit_Pragma;
21732
21733            if Nkind (N) = N_Null_Statement then
21734               return;
21735            end if;
21736
21737            Cunit_Node := Cunit (Current_Sem_Unit);
21738            Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
21739
21740            --  A pragma that applies to a Ghost entity becomes Ghost for the
21741            --  purposes of legality checks and removal of ignored Ghost code.
21742
21743            Mark_Ghost_Pragma (N, Cunit_Ent);
21744
21745            if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
21746                                                N_Generic_Package_Declaration)
21747            then
21748               Error_Pragma
21749                 ("pragma% can only apply to a package declaration");
21750            end if;
21751
21752            Set_Is_Shared_Passive (Cunit_Ent);
21753         end Shared_Passive;
21754
21755         -----------------------
21756         -- Short_Descriptors --
21757         -----------------------
21758
21759         --  pragma Short_Descriptors;
21760
21761         --  Recognize and validate, but otherwise ignore
21762
21763         when Pragma_Short_Descriptors =>
21764            GNAT_Pragma;
21765            Check_Arg_Count (0);
21766            Check_Valid_Configuration_Pragma;
21767
21768         ------------------------------
21769         -- Simple_Storage_Pool_Type --
21770         ------------------------------
21771
21772         --  pragma Simple_Storage_Pool_Type (type_LOCAL_NAME);
21773
21774         when Pragma_Simple_Storage_Pool_Type =>
21775         Simple_Storage_Pool_Type : declare
21776            Typ     : Entity_Id;
21777            Type_Id : Node_Id;
21778
21779         begin
21780            GNAT_Pragma;
21781            Check_Arg_Count (1);
21782            Check_Arg_Is_Library_Level_Local_Name (Arg1);
21783
21784            Type_Id := Get_Pragma_Arg (Arg1);
21785            Find_Type (Type_Id);
21786            Typ := Entity (Type_Id);
21787
21788            if Typ = Any_Type then
21789               return;
21790            end if;
21791
21792            --  A pragma that applies to a Ghost entity becomes Ghost for the
21793            --  purposes of legality checks and removal of ignored Ghost code.
21794
21795            Mark_Ghost_Pragma (N, Typ);
21796
21797            --  We require the pragma to apply to a type declared in a package
21798            --  declaration, but not (immediately) within a package body.
21799
21800            if Ekind (Current_Scope) /= E_Package
21801              or else In_Package_Body (Current_Scope)
21802            then
21803               Error_Pragma
21804                 ("pragma% can only apply to type declared immediately "
21805                  & "within a package declaration");
21806            end if;
21807
21808            --  A simple storage pool type must be an immutably limited record
21809            --  or private type. If the pragma is given for a private type,
21810            --  the full type is similarly restricted (which is checked later
21811            --  in Freeze_Entity).
21812
21813            if Is_Record_Type (Typ)
21814              and then not Is_Limited_View (Typ)
21815            then
21816               Error_Pragma
21817                 ("pragma% can only apply to explicitly limited record type");
21818
21819            elsif Is_Private_Type (Typ) and then not Is_Limited_Type (Typ) then
21820               Error_Pragma
21821                 ("pragma% can only apply to a private type that is limited");
21822
21823            elsif not Is_Record_Type (Typ)
21824              and then not Is_Private_Type (Typ)
21825            then
21826               Error_Pragma
21827                 ("pragma% can only apply to limited record or private type");
21828            end if;
21829
21830            Record_Rep_Item (Typ, N);
21831         end Simple_Storage_Pool_Type;
21832
21833         ----------------------
21834         -- Source_File_Name --
21835         ----------------------
21836
21837         --  There are five forms for this pragma:
21838
21839         --  pragma Source_File_Name (
21840         --    [UNIT_NAME      =>] unit_NAME,
21841         --     BODY_FILE_NAME =>  STRING_LITERAL
21842         --    [, [INDEX =>] INTEGER_LITERAL]);
21843
21844         --  pragma Source_File_Name (
21845         --    [UNIT_NAME      =>] unit_NAME,
21846         --     SPEC_FILE_NAME =>  STRING_LITERAL
21847         --    [, [INDEX =>] INTEGER_LITERAL]);
21848
21849         --  pragma Source_File_Name (
21850         --     BODY_FILE_NAME  => STRING_LITERAL
21851         --  [, DOT_REPLACEMENT => STRING_LITERAL]
21852         --  [, CASING          => CASING_SPEC]);
21853
21854         --  pragma Source_File_Name (
21855         --     SPEC_FILE_NAME  => STRING_LITERAL
21856         --  [, DOT_REPLACEMENT => STRING_LITERAL]
21857         --  [, CASING          => CASING_SPEC]);
21858
21859         --  pragma Source_File_Name (
21860         --     SUBUNIT_FILE_NAME  => STRING_LITERAL
21861         --  [, DOT_REPLACEMENT    => STRING_LITERAL]
21862         --  [, CASING             => CASING_SPEC]);
21863
21864         --  CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
21865
21866         --  Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
21867         --  Source_File_Name (SFN), however their usage is exclusive: SFN can
21868         --  only be used when no project file is used, while SFNP can only be
21869         --  used when a project file is used.
21870
21871         --  No processing here. Processing was completed during parsing, since
21872         --  we need to have file names set as early as possible. Units are
21873         --  loaded well before semantic processing starts.
21874
21875         --  The only processing we defer to this point is the check for
21876         --  correct placement.
21877
21878         when Pragma_Source_File_Name =>
21879            GNAT_Pragma;
21880            Check_Valid_Configuration_Pragma;
21881
21882         ------------------------------
21883         -- Source_File_Name_Project --
21884         ------------------------------
21885
21886         --  See Source_File_Name for syntax
21887
21888         --  No processing here. Processing was completed during parsing, since
21889         --  we need to have file names set as early as possible. Units are
21890         --  loaded well before semantic processing starts.
21891
21892         --  The only processing we defer to this point is the check for
21893         --  correct placement.
21894
21895         when Pragma_Source_File_Name_Project =>
21896            GNAT_Pragma;
21897            Check_Valid_Configuration_Pragma;
21898
21899            --  Check that a pragma Source_File_Name_Project is used only in a
21900            --  configuration pragmas file.
21901
21902            --  Pragmas Source_File_Name_Project should only be generated by
21903            --  the Project Manager in configuration pragmas files.
21904
21905            --  This is really an ugly test. It seems to depend on some
21906            --  accidental and undocumented property. At the very least it
21907            --  needs to be documented, but it would be better to have a
21908            --  clean way of testing if we are in a configuration file???
21909
21910            if Present (Parent (N)) then
21911               Error_Pragma
21912                 ("pragma% can only appear in a configuration pragmas file");
21913            end if;
21914
21915         ----------------------
21916         -- Source_Reference --
21917         ----------------------
21918
21919         --  pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
21920
21921         --  Nothing to do, all processing completed in Par.Prag, since we need
21922         --  the information for possible parser messages that are output.
21923
21924         when Pragma_Source_Reference =>
21925            GNAT_Pragma;
21926
21927         ----------------
21928         -- SPARK_Mode --
21929         ----------------
21930
21931         --  pragma SPARK_Mode [(On | Off)];
21932
21933         when Pragma_SPARK_Mode => Do_SPARK_Mode : declare
21934            Mode_Id : SPARK_Mode_Type;
21935
21936            procedure Check_Pragma_Conformance
21937              (Context_Pragma : Node_Id;
21938               Entity         : Entity_Id;
21939               Entity_Pragma  : Node_Id);
21940            --  Subsidiary to routines Process_xxx. Verify the SPARK_Mode
21941            --  conformance of pragma N depending the following scenarios:
21942            --
21943            --  If pragma Context_Pragma is not Empty, verify that pragma N is
21944            --  compatible with the pragma Context_Pragma that was inherited
21945            --  from the context:
21946            --    * If the mode of Context_Pragma is ON, then the new mode can
21947            --      be anything.
21948            --    * If the mode of Context_Pragma is OFF, then the only allowed
21949            --      new mode is also OFF. Emit error if this is not the case.
21950            --
21951            --  If Entity is not Empty, verify that pragma N is compatible with
21952            --  pragma Entity_Pragma that belongs to Entity.
21953            --    * If Entity_Pragma is Empty, always issue an error as this
21954            --      corresponds to the case where a previous section of Entity
21955            --      has no SPARK_Mode set.
21956            --    * If the mode of Entity_Pragma is ON, then the new mode can
21957            --      be anything.
21958            --    * If the mode of Entity_Pragma is OFF, then the only allowed
21959            --      new mode is also OFF. Emit error if this is not the case.
21960
21961            procedure Check_Library_Level_Entity (E : Entity_Id);
21962            --  Subsidiary to routines Process_xxx. Verify that the related
21963            --  entity E subject to pragma SPARK_Mode is library-level.
21964
21965            procedure Process_Body (Decl : Node_Id);
21966            --  Verify the legality of pragma SPARK_Mode when it appears as the
21967            --  top of the body declarations of entry, package, protected unit,
21968            --  subprogram or task unit body denoted by Decl.
21969
21970            procedure Process_Overloadable (Decl : Node_Id);
21971            --  Verify the legality of pragma SPARK_Mode when it applies to an
21972            --  entry or [generic] subprogram declaration denoted by Decl.
21973
21974            procedure Process_Private_Part (Decl : Node_Id);
21975            --  Verify the legality of pragma SPARK_Mode when it appears at the
21976            --  top of the private declarations of a package spec, protected or
21977            --  task unit declaration denoted by Decl.
21978
21979            procedure Process_Statement_Part (Decl : Node_Id);
21980            --  Verify the legality of pragma SPARK_Mode when it appears at the
21981            --  top of the statement sequence of a package body denoted by node
21982            --  Decl.
21983
21984            procedure Process_Visible_Part (Decl : Node_Id);
21985            --  Verify the legality of pragma SPARK_Mode when it appears at the
21986            --  top of the visible declarations of a package spec, protected or
21987            --  task unit declaration denoted by Decl. The routine is also used
21988            --  on protected or task units declared without a definition.
21989
21990            procedure Set_SPARK_Context;
21991            --  Subsidiary to routines Process_xxx. Set the global variables
21992            --  which represent the mode of the context from pragma N. Ensure
21993            --  that Dynamic_Elaboration_Checks are off if the new mode is On.
21994
21995            ------------------------------
21996            -- Check_Pragma_Conformance --
21997            ------------------------------
21998
21999            procedure Check_Pragma_Conformance
22000              (Context_Pragma : Node_Id;
22001               Entity         : Entity_Id;
22002               Entity_Pragma  : Node_Id)
22003            is
22004               Err_Id : Entity_Id;
22005               Err_N  : Node_Id;
22006
22007            begin
22008               --  The current pragma may appear without an argument. If this
22009               --  is the case, associate all error messages with the pragma
22010               --  itself.
22011
22012               if Present (Arg1) then
22013                  Err_N := Arg1;
22014               else
22015                  Err_N := N;
22016               end if;
22017
22018               --  The mode of the current pragma is compared against that of
22019               --  an enclosing context.
22020
22021               if Present (Context_Pragma) then
22022                  pragma Assert (Nkind (Context_Pragma) = N_Pragma);
22023
22024                  --  Issue an error if the new mode is less restrictive than
22025                  --  that of the context.
22026
22027                  if Get_SPARK_Mode_From_Annotation (Context_Pragma) = Off
22028                    and then Get_SPARK_Mode_From_Annotation (N) = On
22029                  then
22030                     Error_Msg_N
22031                       ("cannot change SPARK_Mode from Off to On", Err_N);
22032                     Error_Msg_Sloc := Sloc (SPARK_Mode_Pragma);
22033                     Error_Msg_N ("\SPARK_Mode was set to Off#", Err_N);
22034                     raise Pragma_Exit;
22035                  end if;
22036               end if;
22037
22038               --  The mode of the current pragma is compared against that of
22039               --  an initial package, protected type, subprogram or task type
22040               --  declaration.
22041
22042               if Present (Entity) then
22043
22044                  --  A simple protected or task type is transformed into an
22045                  --  anonymous type whose name cannot be used to issue error
22046                  --  messages. Recover the original entity of the type.
22047
22048                  if Ekind_In (Entity, E_Protected_Type, E_Task_Type) then
22049                     Err_Id :=
22050                       Defining_Entity
22051                         (Original_Node (Unit_Declaration_Node (Entity)));
22052                  else
22053                     Err_Id := Entity;
22054                  end if;
22055
22056                  --  Both the initial declaration and the completion carry
22057                  --  SPARK_Mode pragmas.
22058
22059                  if Present (Entity_Pragma) then
22060                     pragma Assert (Nkind (Entity_Pragma) = N_Pragma);
22061
22062                     --  Issue an error if the new mode is less restrictive
22063                     --  than that of the initial declaration.
22064
22065                     if Get_SPARK_Mode_From_Annotation (Entity_Pragma) = Off
22066                       and then Get_SPARK_Mode_From_Annotation (N) = On
22067                     then
22068                        Error_Msg_N ("incorrect use of SPARK_Mode", Err_N);
22069                        Error_Msg_Sloc := Sloc (Entity_Pragma);
22070                        Error_Msg_NE
22071                          ("\value Off was set for SPARK_Mode on&#",
22072                           Err_N, Err_Id);
22073                        raise Pragma_Exit;
22074                     end if;
22075
22076                  --  Otherwise the initial declaration lacks a SPARK_Mode
22077                  --  pragma in which case the current pragma is illegal as
22078                  --  it cannot "complete".
22079
22080                  else
22081                     Error_Msg_N ("incorrect use of SPARK_Mode", Err_N);
22082                     Error_Msg_Sloc := Sloc (Err_Id);
22083                     Error_Msg_NE
22084                       ("\no value was set for SPARK_Mode on&#",
22085                        Err_N, Err_Id);
22086                     raise Pragma_Exit;
22087                  end if;
22088               end if;
22089            end Check_Pragma_Conformance;
22090
22091            --------------------------------
22092            -- Check_Library_Level_Entity --
22093            --------------------------------
22094
22095            procedure Check_Library_Level_Entity (E : Entity_Id) is
22096               procedure Add_Entity_To_Name_Buffer;
22097               --  Add the E_Kind of entity E to the name buffer
22098
22099               -------------------------------
22100               -- Add_Entity_To_Name_Buffer --
22101               -------------------------------
22102
22103               procedure Add_Entity_To_Name_Buffer is
22104               begin
22105                  if Ekind_In (E, E_Entry, E_Entry_Family) then
22106                     Add_Str_To_Name_Buffer ("entry");
22107
22108                  elsif Ekind_In (E, E_Generic_Package,
22109                                     E_Package,
22110                                     E_Package_Body)
22111                  then
22112                     Add_Str_To_Name_Buffer ("package");
22113
22114                  elsif Ekind_In (E, E_Protected_Body, E_Protected_Type) then
22115                     Add_Str_To_Name_Buffer ("protected type");
22116
22117                  elsif Ekind_In (E, E_Function,
22118                                     E_Generic_Function,
22119                                     E_Generic_Procedure,
22120                                     E_Procedure,
22121                                     E_Subprogram_Body)
22122                  then
22123                     Add_Str_To_Name_Buffer ("subprogram");
22124
22125                  else
22126                     pragma Assert (Ekind_In (E, E_Task_Body, E_Task_Type));
22127                     Add_Str_To_Name_Buffer ("task type");
22128                  end if;
22129               end Add_Entity_To_Name_Buffer;
22130
22131               --  Local variables
22132
22133               Msg_1 : constant String := "incorrect placement of pragma%";
22134               Msg_2 : Name_Id;
22135
22136            --  Start of processing for Check_Library_Level_Entity
22137
22138            begin
22139               if not Is_Library_Level_Entity (E) then
22140                  Error_Msg_Name_1 := Pname;
22141                  Error_Msg_N (Fix_Error (Msg_1), N);
22142
22143                  Name_Len := 0;
22144                  Add_Str_To_Name_Buffer ("\& is not a library-level ");
22145                  Add_Entity_To_Name_Buffer;
22146
22147                  Msg_2 := Name_Find;
22148                  Error_Msg_NE (Get_Name_String (Msg_2), N, E);
22149
22150                  raise Pragma_Exit;
22151               end if;
22152            end Check_Library_Level_Entity;
22153
22154            ------------------
22155            -- Process_Body --
22156            ------------------
22157
22158            procedure Process_Body (Decl : Node_Id) is
22159               Body_Id : constant Entity_Id := Defining_Entity (Decl);
22160               Spec_Id : constant Entity_Id := Unique_Defining_Entity (Decl);
22161
22162            begin
22163               --  Ignore pragma when applied to the special body created for
22164               --  inlining, recognized by its internal name _Parent.
22165
22166               if Chars (Body_Id) = Name_uParent then
22167                  return;
22168               end if;
22169
22170               Check_Library_Level_Entity (Body_Id);
22171
22172               --  For entry bodies, verify the legality against:
22173               --    * The mode of the context
22174               --    * The mode of the spec (if any)
22175
22176               if Nkind_In (Decl, N_Entry_Body, N_Subprogram_Body) then
22177
22178                  --  A stand-alone subprogram body
22179
22180                  if Body_Id = Spec_Id then
22181                     Check_Pragma_Conformance
22182                       (Context_Pragma => SPARK_Pragma (Body_Id),
22183                        Entity         => Empty,
22184                        Entity_Pragma  => Empty);
22185
22186                  --  An entry or subprogram body that completes a previous
22187                  --  declaration.
22188
22189                  else
22190                     Check_Pragma_Conformance
22191                       (Context_Pragma => SPARK_Pragma (Body_Id),
22192                        Entity         => Spec_Id,
22193                        Entity_Pragma  => SPARK_Pragma (Spec_Id));
22194                  end if;
22195
22196                  Set_SPARK_Context;
22197                  Set_SPARK_Pragma           (Body_Id, N);
22198                  Set_SPARK_Pragma_Inherited (Body_Id, False);
22199
22200               --  For package bodies, verify the legality against:
22201               --    * The mode of the context
22202               --    * The mode of the private part
22203
22204               --  This case is separated from protected and task bodies
22205               --  because the statement part of the package body inherits
22206               --  the mode of the body declarations.
22207
22208               elsif Nkind (Decl) = N_Package_Body then
22209                  Check_Pragma_Conformance
22210                    (Context_Pragma => SPARK_Pragma (Body_Id),
22211                     Entity         => Spec_Id,
22212                     Entity_Pragma  => SPARK_Aux_Pragma (Spec_Id));
22213
22214                  Set_SPARK_Context;
22215                  Set_SPARK_Pragma               (Body_Id, N);
22216                  Set_SPARK_Pragma_Inherited     (Body_Id, False);
22217                  Set_SPARK_Aux_Pragma           (Body_Id, N);
22218                  Set_SPARK_Aux_Pragma_Inherited (Body_Id, True);
22219
22220               --  For protected and task bodies, verify the legality against:
22221               --    * The mode of the context
22222               --    * The mode of the private part
22223
22224               else
22225                  pragma Assert
22226                    (Nkind_In (Decl, N_Protected_Body, N_Task_Body));
22227
22228                  Check_Pragma_Conformance
22229                    (Context_Pragma => SPARK_Pragma (Body_Id),
22230                     Entity         => Spec_Id,
22231                     Entity_Pragma  => SPARK_Aux_Pragma (Spec_Id));
22232
22233                  Set_SPARK_Context;
22234                  Set_SPARK_Pragma           (Body_Id, N);
22235                  Set_SPARK_Pragma_Inherited (Body_Id, False);
22236               end if;
22237            end Process_Body;
22238
22239            --------------------------
22240            -- Process_Overloadable --
22241            --------------------------
22242
22243            procedure Process_Overloadable (Decl : Node_Id) is
22244               Spec_Id  : constant Entity_Id := Defining_Entity (Decl);
22245               Spec_Typ : constant Entity_Id := Etype (Spec_Id);
22246
22247            begin
22248               Check_Library_Level_Entity (Spec_Id);
22249
22250               --  Verify the legality against:
22251               --    * The mode of the context
22252
22253               Check_Pragma_Conformance
22254                 (Context_Pragma => SPARK_Pragma (Spec_Id),
22255                  Entity         => Empty,
22256                  Entity_Pragma  => Empty);
22257
22258               Set_SPARK_Pragma           (Spec_Id, N);
22259               Set_SPARK_Pragma_Inherited (Spec_Id, False);
22260
22261               --  When the pragma applies to the anonymous object created for
22262               --  a single task type, decorate the type as well. This scenario
22263               --  arises when the single task type lacks a task definition,
22264               --  therefore there is no issue with respect to a potential
22265               --  pragma SPARK_Mode in the private part.
22266
22267               --    task type Anon_Task_Typ;
22268               --    Obj : Anon_Task_Typ;
22269               --    pragma SPARK_Mode ...;
22270
22271               if Is_Single_Task_Object (Spec_Id) then
22272                  Set_SPARK_Pragma               (Spec_Typ, N);
22273                  Set_SPARK_Pragma_Inherited     (Spec_Typ, False);
22274                  Set_SPARK_Aux_Pragma           (Spec_Typ, N);
22275                  Set_SPARK_Aux_Pragma_Inherited (Spec_Typ, True);
22276               end if;
22277            end Process_Overloadable;
22278
22279            --------------------------
22280            -- Process_Private_Part --
22281            --------------------------
22282
22283            procedure Process_Private_Part (Decl : Node_Id) is
22284               Spec_Id : constant Entity_Id := Defining_Entity (Decl);
22285
22286            begin
22287               Check_Library_Level_Entity (Spec_Id);
22288
22289               --  Verify the legality against:
22290               --    * The mode of the visible declarations
22291
22292               Check_Pragma_Conformance
22293                 (Context_Pragma => Empty,
22294                  Entity         => Spec_Id,
22295                  Entity_Pragma  => SPARK_Pragma (Spec_Id));
22296
22297               Set_SPARK_Context;
22298               Set_SPARK_Aux_Pragma           (Spec_Id, N);
22299               Set_SPARK_Aux_Pragma_Inherited (Spec_Id, False);
22300            end Process_Private_Part;
22301
22302            ----------------------------
22303            -- Process_Statement_Part --
22304            ----------------------------
22305
22306            procedure Process_Statement_Part (Decl : Node_Id) is
22307               Body_Id : constant Entity_Id := Defining_Entity (Decl);
22308
22309            begin
22310               Check_Library_Level_Entity (Body_Id);
22311
22312               --  Verify the legality against:
22313               --    * The mode of the body declarations
22314
22315               Check_Pragma_Conformance
22316                 (Context_Pragma => Empty,
22317                  Entity         => Body_Id,
22318                  Entity_Pragma  => SPARK_Pragma (Body_Id));
22319
22320               Set_SPARK_Context;
22321               Set_SPARK_Aux_Pragma           (Body_Id, N);
22322               Set_SPARK_Aux_Pragma_Inherited (Body_Id, False);
22323            end Process_Statement_Part;
22324
22325            --------------------------
22326            -- Process_Visible_Part --
22327            --------------------------
22328
22329            procedure Process_Visible_Part (Decl : Node_Id) is
22330               Spec_Id : constant Entity_Id := Defining_Entity (Decl);
22331               Obj_Id  : Entity_Id;
22332
22333            begin
22334               Check_Library_Level_Entity (Spec_Id);
22335
22336               --  Verify the legality against:
22337               --    * The mode of the context
22338
22339               Check_Pragma_Conformance
22340                 (Context_Pragma => SPARK_Pragma (Spec_Id),
22341                  Entity         => Empty,
22342                  Entity_Pragma  => Empty);
22343
22344               --  A task unit declared without a definition does not set the
22345               --  SPARK_Mode of the context because the task does not have any
22346               --  entries that could inherit the mode.
22347
22348               if not Nkind_In (Decl, N_Single_Task_Declaration,
22349                                      N_Task_Type_Declaration)
22350               then
22351                  Set_SPARK_Context;
22352               end if;
22353
22354               Set_SPARK_Pragma               (Spec_Id, N);
22355               Set_SPARK_Pragma_Inherited     (Spec_Id, False);
22356               Set_SPARK_Aux_Pragma           (Spec_Id, N);
22357               Set_SPARK_Aux_Pragma_Inherited (Spec_Id, True);
22358
22359               --  When the pragma applies to a single protected or task type,
22360               --  decorate the corresponding anonymous object as well.
22361
22362               --    protected Anon_Prot_Typ is
22363               --       pragma SPARK_Mode ...;
22364               --       ...
22365               --    end Anon_Prot_Typ;
22366
22367               --    Obj : Anon_Prot_Typ;
22368
22369               if Is_Single_Concurrent_Type (Spec_Id) then
22370                  Obj_Id := Anonymous_Object (Spec_Id);
22371
22372                  Set_SPARK_Pragma           (Obj_Id, N);
22373                  Set_SPARK_Pragma_Inherited (Obj_Id, False);
22374               end if;
22375            end Process_Visible_Part;
22376
22377            -----------------------
22378            -- Set_SPARK_Context --
22379            -----------------------
22380
22381            procedure Set_SPARK_Context is
22382            begin
22383               SPARK_Mode        := Mode_Id;
22384               SPARK_Mode_Pragma := N;
22385            end Set_SPARK_Context;
22386
22387            --  Local variables
22388
22389            Context : Node_Id;
22390            Mode    : Name_Id;
22391            Stmt    : Node_Id;
22392
22393         --  Start of processing for Do_SPARK_Mode
22394
22395         begin
22396            --  When a SPARK_Mode pragma appears inside an instantiation whose
22397            --  enclosing context has SPARK_Mode set to "off", the pragma has
22398            --  no semantic effect.
22399
22400            if Ignore_SPARK_Mode_Pragmas_In_Instance then
22401               Rewrite (N, Make_Null_Statement (Loc));
22402               Analyze (N);
22403               return;
22404            end if;
22405
22406            GNAT_Pragma;
22407            Check_No_Identifiers;
22408            Check_At_Most_N_Arguments (1);
22409
22410            --  Check the legality of the mode (no argument = ON)
22411
22412            if Arg_Count = 1 then
22413               Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
22414               Mode := Chars (Get_Pragma_Arg (Arg1));
22415            else
22416               Mode := Name_On;
22417            end if;
22418
22419            Mode_Id := Get_SPARK_Mode_Type (Mode);
22420            Context := Parent (N);
22421
22422            --  The pragma appears in a configuration file
22423
22424            if No (Context) then
22425               Check_Valid_Configuration_Pragma;
22426
22427               if Present (SPARK_Mode_Pragma) then
22428                  Duplication_Error
22429                    (Prag => N,
22430                     Prev => SPARK_Mode_Pragma);
22431                  raise Pragma_Exit;
22432               end if;
22433
22434               Set_SPARK_Context;
22435
22436            --  The pragma acts as a configuration pragma in a compilation unit
22437
22438            --    pragma SPARK_Mode ...;
22439            --    package Pack is ...;
22440
22441            elsif Nkind (Context) = N_Compilation_Unit
22442              and then List_Containing (N) = Context_Items (Context)
22443            then
22444               Check_Valid_Configuration_Pragma;
22445               Set_SPARK_Context;
22446
22447            --  Otherwise the placement of the pragma within the tree dictates
22448            --  its associated construct. Inspect the declarative list where
22449            --  the pragma resides to find a potential construct.
22450
22451            else
22452               Stmt := Prev (N);
22453               while Present (Stmt) loop
22454
22455                  --  Skip prior pragmas, but check for duplicates. Note that
22456                  --  this also takes care of pragmas generated for aspects.
22457
22458                  if Nkind (Stmt) = N_Pragma then
22459                     if Pragma_Name (Stmt) = Pname then
22460                        Duplication_Error
22461                          (Prag => N,
22462                           Prev => Stmt);
22463                        raise Pragma_Exit;
22464                     end if;
22465
22466                  --  The pragma applies to an expression function that has
22467                  --  already been rewritten into a subprogram declaration.
22468
22469                  --    function Expr_Func return ... is (...);
22470                  --    pragma SPARK_Mode ...;
22471
22472                  elsif Nkind (Stmt) = N_Subprogram_Declaration
22473                    and then Nkind (Original_Node (Stmt)) =
22474                               N_Expression_Function
22475                  then
22476                     Process_Overloadable (Stmt);
22477                     return;
22478
22479                  --  The pragma applies to the anonymous object created for a
22480                  --  single concurrent type.
22481
22482                  --    protected type Anon_Prot_Typ ...;
22483                  --    Obj : Anon_Prot_Typ;
22484                  --    pragma SPARK_Mode ...;
22485
22486                  elsif Nkind (Stmt) = N_Object_Declaration
22487                    and then Is_Single_Concurrent_Object
22488                               (Defining_Entity (Stmt))
22489                  then
22490                     Process_Overloadable (Stmt);
22491                     return;
22492
22493                  --  Skip internally generated code
22494
22495                  elsif not Comes_From_Source (Stmt) then
22496                     null;
22497
22498                  --  The pragma applies to an entry or [generic] subprogram
22499                  --  declaration.
22500
22501                  --    entry Ent ...;
22502                  --    pragma SPARK_Mode ...;
22503
22504                  --    [generic]
22505                  --    procedure Proc ...;
22506                  --    pragma SPARK_Mode ...;
22507
22508                  elsif Nkind_In (Stmt, N_Generic_Subprogram_Declaration,
22509                                        N_Subprogram_Declaration)
22510                    or else (Nkind (Stmt) = N_Entry_Declaration
22511                              and then Is_Protected_Type
22512                                         (Scope (Defining_Entity (Stmt))))
22513                  then
22514                     Process_Overloadable (Stmt);
22515                     return;
22516
22517                  --  Otherwise the pragma does not apply to a legal construct
22518                  --  or it does not appear at the top of a declarative or a
22519                  --  statement list. Issue an error and stop the analysis.
22520
22521                  else
22522                     Pragma_Misplaced;
22523                     exit;
22524                  end if;
22525
22526                  Prev (Stmt);
22527               end loop;
22528
22529               --  The pragma applies to a package or a subprogram that acts as
22530               --  a compilation unit.
22531
22532               --    procedure Proc ...;
22533               --    pragma SPARK_Mode ...;
22534
22535               if Nkind (Context) = N_Compilation_Unit_Aux then
22536                  Context := Unit (Parent (Context));
22537               end if;
22538
22539               --  The pragma appears at the top of entry, package, protected
22540               --  unit, subprogram or task unit body declarations.
22541
22542               --    entry Ent when ... is
22543               --       pragma SPARK_Mode ...;
22544
22545               --    package body Pack is
22546               --       pragma SPARK_Mode ...;
22547
22548               --    procedure Proc ... is
22549               --       pragma SPARK_Mode;
22550
22551               --    protected body Prot is
22552               --       pragma SPARK_Mode ...;
22553
22554               if Nkind_In (Context, N_Entry_Body,
22555                                     N_Package_Body,
22556                                     N_Protected_Body,
22557                                     N_Subprogram_Body,
22558                                     N_Task_Body)
22559               then
22560                  Process_Body (Context);
22561
22562               --  The pragma appears at the top of the visible or private
22563               --  declaration of a package spec, protected or task unit.
22564
22565               --    package Pack is
22566               --       pragma SPARK_Mode ...;
22567               --    private
22568               --       pragma SPARK_Mode ...;
22569
22570               --    protected [type] Prot is
22571               --       pragma SPARK_Mode ...;
22572               --    private
22573               --       pragma SPARK_Mode ...;
22574
22575               elsif Nkind_In (Context, N_Package_Specification,
22576                                        N_Protected_Definition,
22577                                        N_Task_Definition)
22578               then
22579                  if List_Containing (N) = Visible_Declarations (Context) then
22580                     Process_Visible_Part (Parent (Context));
22581                  else
22582                     Process_Private_Part (Parent (Context));
22583                  end if;
22584
22585               --  The pragma appears at the top of package body statements
22586
22587               --    package body Pack is
22588               --    begin
22589               --       pragma SPARK_Mode;
22590
22591               elsif Nkind (Context) = N_Handled_Sequence_Of_Statements
22592                 and then Nkind (Parent (Context)) = N_Package_Body
22593               then
22594                  Process_Statement_Part (Parent (Context));
22595
22596               --  The pragma appeared as an aspect of a [generic] subprogram
22597               --  declaration that acts as a compilation unit.
22598
22599               --    [generic]
22600               --    procedure Proc ...;
22601               --    pragma SPARK_Mode ...;
22602
22603               elsif Nkind_In (Context, N_Generic_Subprogram_Declaration,
22604                                        N_Subprogram_Declaration)
22605               then
22606                  Process_Overloadable (Context);
22607
22608               --  The pragma does not apply to a legal construct, issue error
22609
22610               else
22611                  Pragma_Misplaced;
22612               end if;
22613            end if;
22614         end Do_SPARK_Mode;
22615
22616         --------------------------------
22617         -- Static_Elaboration_Desired --
22618         --------------------------------
22619
22620         --  pragma Static_Elaboration_Desired (DIRECT_NAME);
22621
22622         when Pragma_Static_Elaboration_Desired =>
22623            GNAT_Pragma;
22624            Check_At_Most_N_Arguments (1);
22625
22626            if Is_Compilation_Unit (Current_Scope)
22627              and then Ekind (Current_Scope) = E_Package
22628            then
22629               Set_Static_Elaboration_Desired (Current_Scope, True);
22630            else
22631               Error_Pragma ("pragma% must apply to a library-level package");
22632            end if;
22633
22634         ------------------
22635         -- Storage_Size --
22636         ------------------
22637
22638         --  pragma Storage_Size (EXPRESSION);
22639
22640         when Pragma_Storage_Size => Storage_Size : declare
22641            P   : constant Node_Id := Parent (N);
22642            Arg : Node_Id;
22643
22644         begin
22645            Check_No_Identifiers;
22646            Check_Arg_Count (1);
22647
22648            --  The expression must be analyzed in the special manner described
22649            --  in "Handling of Default Expressions" in sem.ads.
22650
22651            Arg := Get_Pragma_Arg (Arg1);
22652            Preanalyze_Spec_Expression (Arg, Any_Integer);
22653
22654            if not Is_OK_Static_Expression (Arg) then
22655               Check_Restriction (Static_Storage_Size, Arg);
22656            end if;
22657
22658            if Nkind (P) /= N_Task_Definition then
22659               Pragma_Misplaced;
22660               return;
22661
22662            else
22663               if Has_Storage_Size_Pragma (P) then
22664                  Error_Pragma ("duplicate pragma% not allowed");
22665               else
22666                  Set_Has_Storage_Size_Pragma (P, True);
22667               end if;
22668
22669               Record_Rep_Item (Defining_Identifier (Parent (P)), N);
22670            end if;
22671         end Storage_Size;
22672
22673         ------------------
22674         -- Storage_Unit --
22675         ------------------
22676
22677         --  pragma Storage_Unit (NUMERIC_LITERAL);
22678
22679         --  Only permitted argument is System'Storage_Unit value
22680
22681         when Pragma_Storage_Unit =>
22682            Check_No_Identifiers;
22683            Check_Arg_Count (1);
22684            Check_Arg_Is_Integer_Literal (Arg1);
22685
22686            if Intval (Get_Pragma_Arg (Arg1)) /=
22687              UI_From_Int (Ttypes.System_Storage_Unit)
22688            then
22689               Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
22690               Error_Pragma_Arg
22691                 ("the only allowed argument for pragma% is ^", Arg1);
22692            end if;
22693
22694         --------------------
22695         -- Stream_Convert --
22696         --------------------
22697
22698         --  pragma Stream_Convert (
22699         --    [Entity =>] type_LOCAL_NAME,
22700         --    [Read   =>] function_NAME,
22701         --    [Write  =>] function NAME);
22702
22703         when Pragma_Stream_Convert => Stream_Convert : declare
22704            procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
22705            --  Check that the given argument is the name of a local function
22706            --  of one argument that is not overloaded earlier in the current
22707            --  local scope. A check is also made that the argument is a
22708            --  function with one parameter.
22709
22710            --------------------------------------
22711            -- Check_OK_Stream_Convert_Function --
22712            --------------------------------------
22713
22714            procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
22715               Ent : Entity_Id;
22716
22717            begin
22718               Check_Arg_Is_Local_Name (Arg);
22719               Ent := Entity (Get_Pragma_Arg (Arg));
22720
22721               if Has_Homonym (Ent) then
22722                  Error_Pragma_Arg
22723                    ("argument for pragma% may not be overloaded", Arg);
22724               end if;
22725
22726               if Ekind (Ent) /= E_Function
22727                 or else No (First_Formal (Ent))
22728                 or else Present (Next_Formal (First_Formal (Ent)))
22729               then
22730                  Error_Pragma_Arg
22731                    ("argument for pragma% must be function of one argument",
22732                     Arg);
22733               end if;
22734            end Check_OK_Stream_Convert_Function;
22735
22736         --  Start of processing for Stream_Convert
22737
22738         begin
22739            GNAT_Pragma;
22740            Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
22741            Check_Arg_Count (3);
22742            Check_Optional_Identifier (Arg1, Name_Entity);
22743            Check_Optional_Identifier (Arg2, Name_Read);
22744            Check_Optional_Identifier (Arg3, Name_Write);
22745            Check_Arg_Is_Local_Name (Arg1);
22746            Check_OK_Stream_Convert_Function (Arg2);
22747            Check_OK_Stream_Convert_Function (Arg3);
22748
22749            declare
22750               Typ   : constant Entity_Id :=
22751                         Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
22752               Read  : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
22753               Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
22754
22755            begin
22756               Check_First_Subtype (Arg1);
22757
22758               --  Check for too early or too late. Note that we don't enforce
22759               --  the rule about primitive operations in this case, since, as
22760               --  is the case for explicit stream attributes themselves, these
22761               --  restrictions are not appropriate. Note that the chaining of
22762               --  the pragma by Rep_Item_Too_Late is actually the critical
22763               --  processing done for this pragma.
22764
22765               if Rep_Item_Too_Early (Typ, N)
22766                    or else
22767                  Rep_Item_Too_Late (Typ, N, FOnly => True)
22768               then
22769                  return;
22770               end if;
22771
22772               --  Return if previous error
22773
22774               if Etype (Typ) = Any_Type
22775                    or else
22776                  Etype (Read) = Any_Type
22777                    or else
22778                  Etype (Write) = Any_Type
22779               then
22780                  return;
22781               end if;
22782
22783               --  Error checks
22784
22785               if Underlying_Type (Etype (Read)) /= Typ then
22786                  Error_Pragma_Arg
22787                    ("incorrect return type for function&", Arg2);
22788               end if;
22789
22790               if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
22791                  Error_Pragma_Arg
22792                    ("incorrect parameter type for function&", Arg3);
22793               end if;
22794
22795               if Underlying_Type (Etype (First_Formal (Read))) /=
22796                  Underlying_Type (Etype (Write))
22797               then
22798                  Error_Pragma_Arg
22799                    ("result type of & does not match Read parameter type",
22800                     Arg3);
22801               end if;
22802            end;
22803         end Stream_Convert;
22804
22805         ------------------
22806         -- Style_Checks --
22807         ------------------
22808
22809         --  pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
22810
22811         --  This is processed by the parser since some of the style checks
22812         --  take place during source scanning and parsing. This means that
22813         --  we don't need to issue error messages here.
22814
22815         when Pragma_Style_Checks => Style_Checks : declare
22816            A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
22817            S  : String_Id;
22818            C  : Char_Code;
22819
22820         begin
22821            GNAT_Pragma;
22822            Check_No_Identifiers;
22823
22824            --  Two argument form
22825
22826            if Arg_Count = 2 then
22827               Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
22828
22829               declare
22830                  E_Id : Node_Id;
22831                  E    : Entity_Id;
22832
22833               begin
22834                  E_Id := Get_Pragma_Arg (Arg2);
22835                  Analyze (E_Id);
22836
22837                  if not Is_Entity_Name (E_Id) then
22838                     Error_Pragma_Arg
22839                       ("second argument of pragma% must be entity name",
22840                        Arg2);
22841                  end if;
22842
22843                  E := Entity (E_Id);
22844
22845                  if not Ignore_Style_Checks_Pragmas then
22846                     if E = Any_Id then
22847                        return;
22848                     else
22849                        loop
22850                           Set_Suppress_Style_Checks
22851                             (E, Chars (Get_Pragma_Arg (Arg1)) = Name_Off);
22852                           exit when No (Homonym (E));
22853                           E := Homonym (E);
22854                        end loop;
22855                     end if;
22856                  end if;
22857               end;
22858
22859            --  One argument form
22860
22861            else
22862               Check_Arg_Count (1);
22863
22864               if Nkind (A) = N_String_Literal then
22865                  S := Strval (A);
22866
22867                  declare
22868                     Slen    : constant Natural := Natural (String_Length (S));
22869                     Options : String (1 .. Slen);
22870                     J       : Positive;
22871
22872                  begin
22873                     J := 1;
22874                     loop
22875                        C := Get_String_Char (S, Pos (J));
22876                        exit when not In_Character_Range (C);
22877                        Options (J) := Get_Character (C);
22878
22879                        --  If at end of string, set options. As per discussion
22880                        --  above, no need to check for errors, since we issued
22881                        --  them in the parser.
22882
22883                        if J = Slen then
22884                           if not Ignore_Style_Checks_Pragmas then
22885                              Set_Style_Check_Options (Options);
22886                           end if;
22887
22888                           exit;
22889                        end if;
22890
22891                        J := J + 1;
22892                     end loop;
22893                  end;
22894
22895               elsif Nkind (A) = N_Identifier then
22896                  if Chars (A) = Name_All_Checks then
22897                     if not Ignore_Style_Checks_Pragmas then
22898                        if GNAT_Mode then
22899                           Set_GNAT_Style_Check_Options;
22900                        else
22901                           Set_Default_Style_Check_Options;
22902                        end if;
22903                     end if;
22904
22905                  elsif Chars (A) = Name_On then
22906                     if not Ignore_Style_Checks_Pragmas then
22907                        Style_Check := True;
22908                     end if;
22909
22910                  elsif Chars (A) = Name_Off then
22911                     if not Ignore_Style_Checks_Pragmas then
22912                        Style_Check := False;
22913                     end if;
22914                  end if;
22915               end if;
22916            end if;
22917         end Style_Checks;
22918
22919         --------------
22920         -- Subtitle --
22921         --------------
22922
22923         --  pragma Subtitle ([Subtitle =>] STRING_LITERAL);
22924
22925         when Pragma_Subtitle =>
22926            GNAT_Pragma;
22927            Check_Arg_Count (1);
22928            Check_Optional_Identifier (Arg1, Name_Subtitle);
22929            Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
22930            Store_Note (N);
22931
22932         --------------
22933         -- Suppress --
22934         --------------
22935
22936         --  pragma Suppress (IDENTIFIER [, [On =>] NAME]);
22937
22938         when Pragma_Suppress =>
22939            Process_Suppress_Unsuppress (Suppress_Case => True);
22940
22941         ------------------
22942         -- Suppress_All --
22943         ------------------
22944
22945         --  pragma Suppress_All;
22946
22947         --  The only check made here is that the pragma has no arguments.
22948         --  There are no placement rules, and the processing required (setting
22949         --  the Has_Pragma_Suppress_All flag in the compilation unit node was
22950         --  taken care of by the parser). Process_Compilation_Unit_Pragmas
22951         --  then creates and inserts a pragma Suppress (All_Checks).
22952
22953         when Pragma_Suppress_All =>
22954            GNAT_Pragma;
22955            Check_Arg_Count (0);
22956
22957         -------------------------
22958         -- Suppress_Debug_Info --
22959         -------------------------
22960
22961         --  pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
22962
22963         when Pragma_Suppress_Debug_Info => Suppress_Debug_Info : declare
22964            Nam_Id : Entity_Id;
22965
22966         begin
22967            GNAT_Pragma;
22968            Check_Arg_Count (1);
22969            Check_Optional_Identifier (Arg1, Name_Entity);
22970            Check_Arg_Is_Local_Name (Arg1);
22971
22972            Nam_Id := Entity (Get_Pragma_Arg (Arg1));
22973
22974            --  A pragma that applies to a Ghost entity becomes Ghost for the
22975            --  purposes of legality checks and removal of ignored Ghost code.
22976
22977            Mark_Ghost_Pragma (N, Nam_Id);
22978            Set_Debug_Info_Off (Nam_Id);
22979         end Suppress_Debug_Info;
22980
22981         ----------------------------------
22982         -- Suppress_Exception_Locations --
22983         ----------------------------------
22984
22985         --  pragma Suppress_Exception_Locations;
22986
22987         when Pragma_Suppress_Exception_Locations =>
22988            GNAT_Pragma;
22989            Check_Arg_Count (0);
22990            Check_Valid_Configuration_Pragma;
22991            Exception_Locations_Suppressed := True;
22992
22993         -----------------------------
22994         -- Suppress_Initialization --
22995         -----------------------------
22996
22997         --  pragma Suppress_Initialization ([Entity =>] type_Name);
22998
22999         when Pragma_Suppress_Initialization => Suppress_Init : declare
23000            E    : Entity_Id;
23001            E_Id : Node_Id;
23002
23003         begin
23004            GNAT_Pragma;
23005            Check_Arg_Count (1);
23006            Check_Optional_Identifier (Arg1, Name_Entity);
23007            Check_Arg_Is_Local_Name (Arg1);
23008
23009            E_Id := Get_Pragma_Arg (Arg1);
23010
23011            if Etype (E_Id) = Any_Type then
23012               return;
23013            end if;
23014
23015            E := Entity (E_Id);
23016
23017            --  A pragma that applies to a Ghost entity becomes Ghost for the
23018            --  purposes of legality checks and removal of ignored Ghost code.
23019
23020            Mark_Ghost_Pragma (N, E);
23021
23022            if not Is_Type (E) and then Ekind (E) /= E_Variable then
23023               Error_Pragma_Arg
23024                 ("pragma% requires variable, type or subtype", Arg1);
23025            end if;
23026
23027            if Rep_Item_Too_Early (E, N)
23028                 or else
23029               Rep_Item_Too_Late (E, N, FOnly => True)
23030            then
23031               return;
23032            end if;
23033
23034            --  For incomplete/private type, set flag on full view
23035
23036            if Is_Incomplete_Or_Private_Type (E) then
23037               if No (Full_View (Base_Type (E))) then
23038                  Error_Pragma_Arg
23039                    ("argument of pragma% cannot be an incomplete type", Arg1);
23040               else
23041                  Set_Suppress_Initialization (Full_View (Base_Type (E)));
23042               end if;
23043
23044            --  For first subtype, set flag on base type
23045
23046            elsif Is_First_Subtype (E) then
23047               Set_Suppress_Initialization (Base_Type (E));
23048
23049            --  For other than first subtype, set flag on subtype or variable
23050
23051            else
23052               Set_Suppress_Initialization (E);
23053            end if;
23054         end Suppress_Init;
23055
23056         -----------------
23057         -- System_Name --
23058         -----------------
23059
23060         --  pragma System_Name (DIRECT_NAME);
23061
23062         --  Syntax check: one argument, which must be the identifier GNAT or
23063         --  the identifier GCC, no other identifiers are acceptable.
23064
23065         when Pragma_System_Name =>
23066            GNAT_Pragma;
23067            Check_No_Identifiers;
23068            Check_Arg_Count (1);
23069            Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
23070
23071         -----------------------------
23072         -- Task_Dispatching_Policy --
23073         -----------------------------
23074
23075         --  pragma Task_Dispatching_Policy (policy_IDENTIFIER);
23076
23077         when Pragma_Task_Dispatching_Policy => declare
23078            DP : Character;
23079
23080         begin
23081            Check_Ada_83_Warning;
23082            Check_Arg_Count (1);
23083            Check_No_Identifiers;
23084            Check_Arg_Is_Task_Dispatching_Policy (Arg1);
23085            Check_Valid_Configuration_Pragma;
23086            Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
23087            DP := Fold_Upper (Name_Buffer (1));
23088
23089            if Task_Dispatching_Policy /= ' '
23090              and then Task_Dispatching_Policy /= DP
23091            then
23092               Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
23093               Error_Pragma
23094                 ("task dispatching policy incompatible with policy#");
23095
23096            --  Set new policy, but always preserve System_Location since we
23097            --  like the error message with the run time name.
23098
23099            else
23100               Task_Dispatching_Policy := DP;
23101
23102               if Task_Dispatching_Policy_Sloc /= System_Location then
23103                  Task_Dispatching_Policy_Sloc := Loc;
23104               end if;
23105            end if;
23106         end;
23107
23108         ---------------
23109         -- Task_Info --
23110         ---------------
23111
23112         --  pragma Task_Info (EXPRESSION);
23113
23114         when Pragma_Task_Info => Task_Info : declare
23115            P   : constant Node_Id := Parent (N);
23116            Ent : Entity_Id;
23117
23118         begin
23119            GNAT_Pragma;
23120
23121            if Warn_On_Obsolescent_Feature then
23122               Error_Msg_N
23123                 ("'G'N'A'T pragma Task_Info is now obsolete, use 'C'P'U "
23124                  & "instead?j?", N);
23125            end if;
23126
23127            if Nkind (P) /= N_Task_Definition then
23128               Error_Pragma ("pragma% must appear in task definition");
23129            end if;
23130
23131            Check_No_Identifiers;
23132            Check_Arg_Count (1);
23133
23134            Analyze_And_Resolve
23135              (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
23136
23137            if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
23138               return;
23139            end if;
23140
23141            Ent := Defining_Identifier (Parent (P));
23142
23143            --  Check duplicate pragma before we chain the pragma in the Rep
23144            --  Item chain of Ent.
23145
23146            if Has_Rep_Pragma
23147                 (Ent, Name_Task_Info, Check_Parents => False)
23148            then
23149               Error_Pragma ("duplicate pragma% not allowed");
23150            end if;
23151
23152            Record_Rep_Item (Ent, N);
23153         end Task_Info;
23154
23155         ---------------
23156         -- Task_Name --
23157         ---------------
23158
23159         --  pragma Task_Name (string_EXPRESSION);
23160
23161         when Pragma_Task_Name => Task_Name : declare
23162            P   : constant Node_Id := Parent (N);
23163            Arg : Node_Id;
23164            Ent : Entity_Id;
23165
23166         begin
23167            Check_No_Identifiers;
23168            Check_Arg_Count (1);
23169
23170            Arg := Get_Pragma_Arg (Arg1);
23171
23172            --  The expression is used in the call to Create_Task, and must be
23173            --  expanded there, not in the context of the current spec. It must
23174            --  however be analyzed to capture global references, in case it
23175            --  appears in a generic context.
23176
23177            Preanalyze_And_Resolve (Arg, Standard_String);
23178
23179            if Nkind (P) /= N_Task_Definition then
23180               Pragma_Misplaced;
23181            end if;
23182
23183            Ent := Defining_Identifier (Parent (P));
23184
23185            --  Check duplicate pragma before we chain the pragma in the Rep
23186            --  Item chain of Ent.
23187
23188            if Has_Rep_Pragma
23189                 (Ent, Name_Task_Name, Check_Parents => False)
23190            then
23191               Error_Pragma ("duplicate pragma% not allowed");
23192            end if;
23193
23194            Record_Rep_Item (Ent, N);
23195         end Task_Name;
23196
23197         ------------------
23198         -- Task_Storage --
23199         ------------------
23200
23201         --  pragma Task_Storage (
23202         --     [Task_Type =>] LOCAL_NAME,
23203         --     [Top_Guard =>] static_integer_EXPRESSION);
23204
23205         when Pragma_Task_Storage => Task_Storage : declare
23206            Args  : Args_List (1 .. 2);
23207            Names : constant Name_List (1 .. 2) := (
23208                      Name_Task_Type,
23209                      Name_Top_Guard);
23210
23211            Task_Type : Node_Id renames Args (1);
23212            Top_Guard : Node_Id renames Args (2);
23213
23214            Ent : Entity_Id;
23215
23216         begin
23217            GNAT_Pragma;
23218            Gather_Associations (Names, Args);
23219
23220            if No (Task_Type) then
23221               Error_Pragma
23222                 ("missing task_type argument for pragma%");
23223            end if;
23224
23225            Check_Arg_Is_Local_Name (Task_Type);
23226
23227            Ent := Entity (Task_Type);
23228
23229            if not Is_Task_Type (Ent) then
23230               Error_Pragma_Arg
23231                 ("argument for pragma% must be task type", Task_Type);
23232            end if;
23233
23234            if No (Top_Guard) then
23235               Error_Pragma_Arg
23236                 ("pragma% takes two arguments", Task_Type);
23237            else
23238               Check_Arg_Is_OK_Static_Expression (Top_Guard, Any_Integer);
23239            end if;
23240
23241            Check_First_Subtype (Task_Type);
23242
23243            if Rep_Item_Too_Late (Ent, N) then
23244               raise Pragma_Exit;
23245            end if;
23246         end Task_Storage;
23247
23248         ---------------
23249         -- Test_Case --
23250         ---------------
23251
23252         --  pragma Test_Case
23253         --    ([Name     =>] Static_String_EXPRESSION
23254         --    ,[Mode     =>] MODE_TYPE
23255         --   [, Requires =>  Boolean_EXPRESSION]
23256         --   [, Ensures  =>  Boolean_EXPRESSION]);
23257
23258         --  MODE_TYPE ::= Nominal | Robustness
23259
23260         --  Characteristics:
23261
23262         --    * Analysis - The annotation undergoes initial checks to verify
23263         --    the legal placement and context. Secondary checks preanalyze the
23264         --    expressions in:
23265
23266         --       Analyze_Test_Case_In_Decl_Part
23267
23268         --    * Expansion - None.
23269
23270         --    * Template - The annotation utilizes the generic template of the
23271         --    related subprogram when it is:
23272
23273         --       aspect on subprogram declaration
23274
23275         --    The annotation must prepare its own template when it is:
23276
23277         --       pragma on subprogram declaration
23278
23279         --    * Globals - Capture of global references must occur after full
23280         --    analysis.
23281
23282         --    * Instance - The annotation is instantiated automatically when
23283         --    the related generic subprogram is instantiated except for the
23284         --    "pragma on subprogram declaration" case. In that scenario the
23285         --    annotation must instantiate itself.
23286
23287         when Pragma_Test_Case => Test_Case : declare
23288            procedure Check_Distinct_Name (Subp_Id : Entity_Id);
23289            --  Ensure that the contract of subprogram Subp_Id does not contain
23290            --  another Test_Case pragma with the same Name as the current one.
23291
23292            -------------------------
23293            -- Check_Distinct_Name --
23294            -------------------------
23295
23296            procedure Check_Distinct_Name (Subp_Id : Entity_Id) is
23297               Items : constant Node_Id   := Contract (Subp_Id);
23298               Name  : constant String_Id := Get_Name_From_CTC_Pragma (N);
23299               Prag  : Node_Id;
23300
23301            begin
23302               --  Inspect all Test_Case pragma of the related subprogram
23303               --  looking for one with a duplicate "Name" argument.
23304
23305               if Present (Items) then
23306                  Prag := Contract_Test_Cases (Items);
23307                  while Present (Prag) loop
23308                     if Pragma_Name (Prag) = Name_Test_Case
23309                       and then Prag /= N
23310                       and then String_Equal
23311                                  (Name, Get_Name_From_CTC_Pragma (Prag))
23312                     then
23313                        Error_Msg_Sloc := Sloc (Prag);
23314                        Error_Pragma ("name for pragma % is already used #");
23315                     end if;
23316
23317                     Prag := Next_Pragma (Prag);
23318                  end loop;
23319               end if;
23320            end Check_Distinct_Name;
23321
23322            --  Local variables
23323
23324            Pack_Decl : constant Node_Id := Unit (Cunit (Current_Sem_Unit));
23325            Asp_Arg   : Node_Id;
23326            Context   : Node_Id;
23327            Subp_Decl : Node_Id;
23328            Subp_Id   : Entity_Id;
23329
23330         --  Start of processing for Test_Case
23331
23332         begin
23333            GNAT_Pragma;
23334            Check_At_Least_N_Arguments (2);
23335            Check_At_Most_N_Arguments (4);
23336            Check_Arg_Order
23337              ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
23338
23339            --  Argument "Name"
23340
23341            Check_Optional_Identifier (Arg1, Name_Name);
23342            Check_Arg_Is_OK_Static_Expression (Arg1, Standard_String);
23343
23344            --  Argument "Mode"
23345
23346            Check_Optional_Identifier (Arg2, Name_Mode);
23347            Check_Arg_Is_One_Of (Arg2, Name_Nominal, Name_Robustness);
23348
23349            --  Arguments "Requires" and "Ensures"
23350
23351            if Present (Arg3) then
23352               if Present (Arg4) then
23353                  Check_Identifier (Arg3, Name_Requires);
23354                  Check_Identifier (Arg4, Name_Ensures);
23355               else
23356                  Check_Identifier_Is_One_Of
23357                    (Arg3, Name_Requires, Name_Ensures);
23358               end if;
23359            end if;
23360
23361            --  Pragma Test_Case must be associated with a subprogram declared
23362            --  in a library-level package. First determine whether the current
23363            --  compilation unit is a legal context.
23364
23365            if Nkind_In (Pack_Decl, N_Package_Declaration,
23366                                    N_Generic_Package_Declaration)
23367            then
23368               null;
23369
23370            --  Otherwise the placement is illegal
23371
23372            else
23373               Error_Pragma
23374                 ("pragma % must be specified within a package declaration");
23375               return;
23376            end if;
23377
23378            Subp_Decl := Find_Related_Declaration_Or_Body (N);
23379
23380            --  Find the enclosing context
23381
23382            Context := Parent (Subp_Decl);
23383
23384            if Present (Context) then
23385               Context := Parent (Context);
23386            end if;
23387
23388            --  Verify the placement of the pragma
23389
23390            if Nkind (Subp_Decl) = N_Abstract_Subprogram_Declaration then
23391               Error_Pragma
23392                 ("pragma % cannot be applied to abstract subprogram");
23393               return;
23394
23395            elsif Nkind (Subp_Decl) = N_Entry_Declaration then
23396               Error_Pragma ("pragma % cannot be applied to entry");
23397               return;
23398
23399            --  The context is a [generic] subprogram declared at the top level
23400            --  of the [generic] package unit.
23401
23402            elsif Nkind_In (Subp_Decl, N_Generic_Subprogram_Declaration,
23403                                       N_Subprogram_Declaration)
23404              and then Present (Context)
23405              and then Nkind_In (Context, N_Generic_Package_Declaration,
23406                                          N_Package_Declaration)
23407            then
23408               null;
23409
23410            --  Otherwise the placement is illegal
23411
23412            else
23413               Error_Pragma
23414                 ("pragma % must be applied to a library-level subprogram "
23415                  & "declaration");
23416               return;
23417            end if;
23418
23419            Subp_Id := Defining_Entity (Subp_Decl);
23420
23421            --  A pragma that applies to a Ghost entity becomes Ghost for the
23422            --  purposes of legality checks and removal of ignored Ghost code.
23423
23424            Mark_Ghost_Pragma (N, Subp_Id);
23425
23426            --  Chain the pragma on the contract for further processing by
23427            --  Analyze_Test_Case_In_Decl_Part.
23428
23429            Add_Contract_Item (N, Subp_Id);
23430
23431            --  Preanalyze the original aspect argument "Name" for ASIS or for
23432            --  a generic subprogram to properly capture global references.
23433
23434            if ASIS_Mode or else Is_Generic_Subprogram (Subp_Id) then
23435               Asp_Arg := Test_Case_Arg (N, Name_Name, From_Aspect => True);
23436
23437               if Present (Asp_Arg) then
23438
23439                  --  The argument appears with an identifier in association
23440                  --  form.
23441
23442                  if Nkind (Asp_Arg) = N_Component_Association then
23443                     Asp_Arg := Expression (Asp_Arg);
23444                  end if;
23445
23446                  Check_Expr_Is_OK_Static_Expression
23447                    (Asp_Arg, Standard_String);
23448               end if;
23449            end if;
23450
23451            --  Ensure that the all Test_Case pragmas of the related subprogram
23452            --  have distinct names.
23453
23454            Check_Distinct_Name (Subp_Id);
23455
23456            --  Fully analyze the pragma when it appears inside an entry
23457            --  or subprogram body because it cannot benefit from forward
23458            --  references.
23459
23460            if Nkind_In (Subp_Decl, N_Entry_Body,
23461                                    N_Subprogram_Body,
23462                                    N_Subprogram_Body_Stub)
23463            then
23464               --  The legality checks of pragma Test_Case are affected by the
23465               --  SPARK mode in effect and the volatility of the context.
23466               --  Analyze all pragmas in a specific order.
23467
23468               Analyze_If_Present (Pragma_SPARK_Mode);
23469               Analyze_If_Present (Pragma_Volatile_Function);
23470               Analyze_Test_Case_In_Decl_Part (N);
23471            end if;
23472         end Test_Case;
23473
23474         --------------------------
23475         -- Thread_Local_Storage --
23476         --------------------------
23477
23478         --  pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
23479
23480         when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
23481            E  : Entity_Id;
23482            Id : Node_Id;
23483
23484         begin
23485            GNAT_Pragma;
23486            Check_Arg_Count (1);
23487            Check_Optional_Identifier (Arg1, Name_Entity);
23488            Check_Arg_Is_Library_Level_Local_Name (Arg1);
23489
23490            Id := Get_Pragma_Arg (Arg1);
23491            Analyze (Id);
23492
23493            if not Is_Entity_Name (Id)
23494              or else Ekind (Entity (Id)) /= E_Variable
23495            then
23496               Error_Pragma_Arg ("local variable name required", Arg1);
23497            end if;
23498
23499            E := Entity (Id);
23500
23501            --  A pragma that applies to a Ghost entity becomes Ghost for the
23502            --  purposes of legality checks and removal of ignored Ghost code.
23503
23504            Mark_Ghost_Pragma (N, E);
23505
23506            if Rep_Item_Too_Early (E, N)
23507                 or else
23508               Rep_Item_Too_Late (E, N)
23509            then
23510               raise Pragma_Exit;
23511            end if;
23512
23513            Set_Has_Pragma_Thread_Local_Storage (E);
23514            Set_Has_Gigi_Rep_Item (E);
23515         end Thread_Local_Storage;
23516
23517         ----------------
23518         -- Time_Slice --
23519         ----------------
23520
23521         --  pragma Time_Slice (static_duration_EXPRESSION);
23522
23523         when Pragma_Time_Slice => Time_Slice : declare
23524            Val : Ureal;
23525            Nod : Node_Id;
23526
23527         begin
23528            GNAT_Pragma;
23529            Check_Arg_Count (1);
23530            Check_No_Identifiers;
23531            Check_In_Main_Program;
23532            Check_Arg_Is_OK_Static_Expression (Arg1, Standard_Duration);
23533
23534            if not Error_Posted (Arg1) then
23535               Nod := Next (N);
23536               while Present (Nod) loop
23537                  if Nkind (Nod) = N_Pragma
23538                    and then Pragma_Name (Nod) = Name_Time_Slice
23539                  then
23540                     Error_Msg_Name_1 := Pname;
23541                     Error_Msg_N ("duplicate pragma% not permitted", Nod);
23542                  end if;
23543
23544                  Next (Nod);
23545               end loop;
23546            end if;
23547
23548            --  Process only if in main unit
23549
23550            if Get_Source_Unit (Loc) = Main_Unit then
23551               Opt.Time_Slice_Set := True;
23552               Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
23553
23554               if Val <= Ureal_0 then
23555                  Opt.Time_Slice_Value := 0;
23556
23557               elsif Val > UR_From_Uint (UI_From_Int (1000)) then
23558                  Opt.Time_Slice_Value := 1_000_000_000;
23559
23560               else
23561                  Opt.Time_Slice_Value :=
23562                    UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
23563               end if;
23564            end if;
23565         end Time_Slice;
23566
23567         -----------
23568         -- Title --
23569         -----------
23570
23571         --  pragma Title (TITLING_OPTION [, TITLING OPTION]);
23572
23573         --   TITLING_OPTION ::=
23574         --     [Title =>] STRING_LITERAL
23575         --   | [Subtitle =>] STRING_LITERAL
23576
23577         when Pragma_Title => Title : declare
23578            Args  : Args_List (1 .. 2);
23579            Names : constant Name_List (1 .. 2) := (
23580                      Name_Title,
23581                      Name_Subtitle);
23582
23583         begin
23584            GNAT_Pragma;
23585            Gather_Associations (Names, Args);
23586            Store_Note (N);
23587
23588            for J in 1 .. 2 loop
23589               if Present (Args (J)) then
23590                  Check_Arg_Is_OK_Static_Expression
23591                    (Args (J), Standard_String);
23592               end if;
23593            end loop;
23594         end Title;
23595
23596         ----------------------------
23597         -- Type_Invariant[_Class] --
23598         ----------------------------
23599
23600         --  pragma Type_Invariant[_Class]
23601         --    ([Entity =>] type_LOCAL_NAME,
23602         --     [Check  =>] EXPRESSION);
23603
23604         when Pragma_Type_Invariant
23605            | Pragma_Type_Invariant_Class
23606         =>
23607         Type_Invariant : declare
23608            I_Pragma : Node_Id;
23609
23610         begin
23611            Check_Arg_Count (2);
23612
23613            --  Rewrite Type_Invariant[_Class] pragma as an Invariant pragma,
23614            --  setting Class_Present for the Type_Invariant_Class case.
23615
23616            Set_Class_Present (N, Prag_Id = Pragma_Type_Invariant_Class);
23617            I_Pragma := New_Copy (N);
23618            Set_Pragma_Identifier
23619              (I_Pragma, Make_Identifier (Loc, Name_Invariant));
23620            Rewrite (N, I_Pragma);
23621            Set_Analyzed (N, False);
23622            Analyze (N);
23623         end Type_Invariant;
23624
23625         ---------------------
23626         -- Unchecked_Union --
23627         ---------------------
23628
23629         --  pragma Unchecked_Union (first_subtype_LOCAL_NAME)
23630
23631         when Pragma_Unchecked_Union => Unchecked_Union : declare
23632            Assoc   : constant Node_Id := Arg1;
23633            Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
23634            Clist   : Node_Id;
23635            Comp    : Node_Id;
23636            Tdef    : Node_Id;
23637            Typ     : Entity_Id;
23638            Variant : Node_Id;
23639            Vpart   : Node_Id;
23640
23641         begin
23642            Ada_2005_Pragma;
23643            Check_No_Identifiers;
23644            Check_Arg_Count (1);
23645            Check_Arg_Is_Local_Name (Arg1);
23646
23647            Find_Type (Type_Id);
23648
23649            Typ := Entity (Type_Id);
23650
23651            --  A pragma that applies to a Ghost entity becomes Ghost for the
23652            --  purposes of legality checks and removal of ignored Ghost code.
23653
23654            Mark_Ghost_Pragma (N, Typ);
23655
23656            if Typ = Any_Type
23657              or else Rep_Item_Too_Early (Typ, N)
23658            then
23659               return;
23660            else
23661               Typ := Underlying_Type (Typ);
23662            end if;
23663
23664            if Rep_Item_Too_Late (Typ, N) then
23665               return;
23666            end if;
23667
23668            Check_First_Subtype (Arg1);
23669
23670            --  Note remaining cases are references to a type in the current
23671            --  declarative part. If we find an error, we post the error on
23672            --  the relevant type declaration at an appropriate point.
23673
23674            if not Is_Record_Type (Typ) then
23675               Error_Msg_N ("unchecked union must be record type", Typ);
23676               return;
23677
23678            elsif Is_Tagged_Type (Typ) then
23679               Error_Msg_N ("unchecked union must not be tagged", Typ);
23680               return;
23681
23682            elsif not Has_Discriminants (Typ) then
23683               Error_Msg_N
23684                 ("unchecked union must have one discriminant", Typ);
23685               return;
23686
23687            --  Note: in previous versions of GNAT we used to check for limited
23688            --  types and give an error, but in fact the standard does allow
23689            --  Unchecked_Union on limited types, so this check was removed.
23690
23691            --  Similarly, GNAT used to require that all discriminants have
23692            --  default values, but this is not mandated by the RM.
23693
23694            --  Proceed with basic error checks completed
23695
23696            else
23697               Tdef  := Type_Definition (Declaration_Node (Typ));
23698               Clist := Component_List (Tdef);
23699
23700               --  Check presence of component list and variant part
23701
23702               if No (Clist) or else No (Variant_Part (Clist)) then
23703                  Error_Msg_N
23704                    ("unchecked union must have variant part", Tdef);
23705                  return;
23706               end if;
23707
23708               --  Check components
23709
23710               Comp := First_Non_Pragma (Component_Items (Clist));
23711               while Present (Comp) loop
23712                  Check_Component (Comp, Typ);
23713                  Next_Non_Pragma (Comp);
23714               end loop;
23715
23716               --  Check variant part
23717
23718               Vpart := Variant_Part (Clist);
23719
23720               Variant := First_Non_Pragma (Variants (Vpart));
23721               while Present (Variant) loop
23722                  Check_Variant (Variant, Typ);
23723                  Next_Non_Pragma (Variant);
23724               end loop;
23725            end if;
23726
23727            Set_Is_Unchecked_Union  (Typ);
23728            Set_Convention (Typ, Convention_C);
23729            Set_Has_Unchecked_Union (Base_Type (Typ));
23730            Set_Is_Unchecked_Union  (Base_Type (Typ));
23731         end Unchecked_Union;
23732
23733         ----------------------------
23734         -- Unevaluated_Use_Of_Old --
23735         ----------------------------
23736
23737         --  pragma Unevaluated_Use_Of_Old (Error | Warn | Allow);
23738
23739         when Pragma_Unevaluated_Use_Of_Old =>
23740            GNAT_Pragma;
23741            Check_Arg_Count (1);
23742            Check_No_Identifiers;
23743            Check_Arg_Is_One_Of (Arg1, Name_Error, Name_Warn, Name_Allow);
23744
23745            --  Suppress/Unsuppress can appear as a configuration pragma, or in
23746            --  a declarative part or a package spec.
23747
23748            if not Is_Configuration_Pragma then
23749               Check_Is_In_Decl_Part_Or_Package_Spec;
23750            end if;
23751
23752            --  Store proper setting of Uneval_Old
23753
23754            Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
23755            Uneval_Old := Fold_Upper (Name_Buffer (1));
23756
23757         ------------------------
23758         -- Unimplemented_Unit --
23759         ------------------------
23760
23761         --  pragma Unimplemented_Unit;
23762
23763         --  Note: this only gives an error if we are generating code, or if
23764         --  we are in a generic library unit (where the pragma appears in the
23765         --  body, not in the spec).
23766
23767         when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
23768            Cunitent : constant Entity_Id   :=
23769                         Cunit_Entity (Get_Source_Unit (Loc));
23770            Ent_Kind : constant Entity_Kind := Ekind (Cunitent);
23771
23772         begin
23773            GNAT_Pragma;
23774            Check_Arg_Count (0);
23775
23776            if Operating_Mode = Generate_Code
23777              or else Ent_Kind = E_Generic_Function
23778              or else Ent_Kind = E_Generic_Procedure
23779              or else Ent_Kind = E_Generic_Package
23780            then
23781               Get_Name_String (Chars (Cunitent));
23782               Set_Casing (Mixed_Case);
23783               Write_Str (Name_Buffer (1 .. Name_Len));
23784               Write_Str (" is not supported in this configuration");
23785               Write_Eol;
23786               raise Unrecoverable_Error;
23787            end if;
23788         end Unimplemented_Unit;
23789
23790         ------------------------
23791         -- Universal_Aliasing --
23792         ------------------------
23793
23794         --  pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
23795
23796         when Pragma_Universal_Aliasing => Universal_Alias : declare
23797            E    : Entity_Id;
23798            E_Id : Node_Id;
23799
23800         begin
23801            GNAT_Pragma;
23802            Check_Arg_Count (1);
23803            Check_Optional_Identifier (Arg2, Name_Entity);
23804            Check_Arg_Is_Local_Name (Arg1);
23805            E_Id := Get_Pragma_Arg (Arg1);
23806
23807            if Etype (E_Id) = Any_Type then
23808               return;
23809            end if;
23810
23811            E := Entity (E_Id);
23812
23813            if not Is_Type (E) then
23814               Error_Pragma_Arg ("pragma% requires type", Arg1);
23815            end if;
23816
23817            --  A pragma that applies to a Ghost entity becomes Ghost for the
23818            --  purposes of legality checks and removal of ignored Ghost code.
23819
23820            Mark_Ghost_Pragma (N, E);
23821            Set_Universal_Aliasing (Base_Type (E));
23822            Record_Rep_Item (E, N);
23823         end Universal_Alias;
23824
23825         --------------------
23826         -- Universal_Data --
23827         --------------------
23828
23829         --  pragma Universal_Data [(library_unit_NAME)];
23830
23831         when Pragma_Universal_Data =>
23832            GNAT_Pragma;
23833            Error_Pragma ("??pragma% ignored (applies only to AAMP)");
23834
23835         ----------------
23836         -- Unmodified --
23837         ----------------
23838
23839         --  pragma Unmodified (LOCAL_NAME {, LOCAL_NAME});
23840
23841         when Pragma_Unmodified =>
23842            Analyze_Unmodified_Or_Unused;
23843
23844         ------------------
23845         -- Unreferenced --
23846         ------------------
23847
23848         --  pragma Unreferenced (LOCAL_NAME {, LOCAL_NAME});
23849
23850         --    or when used in a context clause:
23851
23852         --  pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
23853
23854         when Pragma_Unreferenced =>
23855            Analyze_Unreferenced_Or_Unused;
23856
23857         --------------------------
23858         -- Unreferenced_Objects --
23859         --------------------------
23860
23861         --  pragma Unreferenced_Objects (LOCAL_NAME {, LOCAL_NAME});
23862
23863         when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
23864            Arg      : Node_Id;
23865            Arg_Expr : Node_Id;
23866            Arg_Id   : Entity_Id;
23867
23868            Ghost_Error_Posted : Boolean := False;
23869            --  Flag set when an error concerning the illegal mix of Ghost and
23870            --  non-Ghost types is emitted.
23871
23872            Ghost_Id : Entity_Id := Empty;
23873            --  The entity of the first Ghost type encountered while processing
23874            --  the arguments of the pragma.
23875
23876         begin
23877            GNAT_Pragma;
23878            Check_At_Least_N_Arguments (1);
23879
23880            Arg := Arg1;
23881            while Present (Arg) loop
23882               Check_No_Identifier (Arg);
23883               Check_Arg_Is_Local_Name (Arg);
23884               Arg_Expr := Get_Pragma_Arg (Arg);
23885
23886               if Is_Entity_Name (Arg_Expr) then
23887                  Arg_Id := Entity (Arg_Expr);
23888
23889                  if Is_Type (Arg_Id) then
23890                     Set_Has_Pragma_Unreferenced_Objects (Arg_Id);
23891
23892                     --  A pragma that applies to a Ghost entity becomes Ghost
23893                     --  for the purposes of legality checks and removal of
23894                     --  ignored Ghost code.
23895
23896                     Mark_Ghost_Pragma (N, Arg_Id);
23897
23898                     --  Capture the entity of the first Ghost type being
23899                     --  processed for error detection purposes.
23900
23901                     if Is_Ghost_Entity (Arg_Id) then
23902                        if No (Ghost_Id) then
23903                           Ghost_Id := Arg_Id;
23904                        end if;
23905
23906                     --  Otherwise the type is non-Ghost. It is illegal to mix
23907                     --  references to Ghost and non-Ghost entities
23908                     --  (SPARK RM 6.9).
23909
23910                     elsif Present (Ghost_Id)
23911                       and then not Ghost_Error_Posted
23912                     then
23913                        Ghost_Error_Posted := True;
23914
23915                        Error_Msg_Name_1 := Pname;
23916                        Error_Msg_N
23917                          ("pragma % cannot mention ghost and non-ghost types",
23918                           N);
23919
23920                        Error_Msg_Sloc := Sloc (Ghost_Id);
23921                        Error_Msg_NE ("\& # declared as ghost", N, Ghost_Id);
23922
23923                        Error_Msg_Sloc := Sloc (Arg_Id);
23924                        Error_Msg_NE ("\& # declared as non-ghost", N, Arg_Id);
23925                     end if;
23926                  else
23927                     Error_Pragma_Arg
23928                       ("argument for pragma% must be type or subtype", Arg);
23929                  end if;
23930               else
23931                  Error_Pragma_Arg
23932                    ("argument for pragma% must be type or subtype", Arg);
23933               end if;
23934
23935               Next (Arg);
23936            end loop;
23937         end Unreferenced_Objects;
23938
23939         ------------------------------
23940         -- Unreserve_All_Interrupts --
23941         ------------------------------
23942
23943         --  pragma Unreserve_All_Interrupts;
23944
23945         when Pragma_Unreserve_All_Interrupts =>
23946            GNAT_Pragma;
23947            Check_Arg_Count (0);
23948
23949            if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
23950               Unreserve_All_Interrupts := True;
23951            end if;
23952
23953         ----------------
23954         -- Unsuppress --
23955         ----------------
23956
23957         --  pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
23958
23959         when Pragma_Unsuppress =>
23960            Ada_2005_Pragma;
23961            Process_Suppress_Unsuppress (Suppress_Case => False);
23962
23963         ------------
23964         -- Unused --
23965         ------------
23966
23967         --  pragma Unused (LOCAL_NAME {, LOCAL_NAME});
23968
23969         when Pragma_Unused =>
23970            Analyze_Unmodified_Or_Unused   (Is_Unused => True);
23971            Analyze_Unreferenced_Or_Unused (Is_Unused => True);
23972
23973         -------------------
23974         -- Use_VADS_Size --
23975         -------------------
23976
23977         --  pragma Use_VADS_Size;
23978
23979         when Pragma_Use_VADS_Size =>
23980            GNAT_Pragma;
23981            Check_Arg_Count (0);
23982            Check_Valid_Configuration_Pragma;
23983            Use_VADS_Size := True;
23984
23985         ---------------------
23986         -- Validity_Checks --
23987         ---------------------
23988
23989         --  pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
23990
23991         when Pragma_Validity_Checks => Validity_Checks : declare
23992            A  : constant Node_Id := Get_Pragma_Arg (Arg1);
23993            S  : String_Id;
23994            C  : Char_Code;
23995
23996         begin
23997            GNAT_Pragma;
23998            Check_Arg_Count (1);
23999            Check_No_Identifiers;
24000
24001            --  Pragma always active unless in CodePeer or GNATprove modes,
24002            --  which use a fixed configuration of validity checks.
24003
24004            if not (CodePeer_Mode or GNATprove_Mode) then
24005               if Nkind (A) = N_String_Literal then
24006                  S := Strval (A);
24007
24008                  declare
24009                     Slen    : constant Natural := Natural (String_Length (S));
24010                     Options : String (1 .. Slen);
24011                     J       : Positive;
24012
24013                  begin
24014                     --  Couldn't we use a for loop here over Options'Range???
24015
24016                     J := 1;
24017                     loop
24018                        C := Get_String_Char (S, Pos (J));
24019
24020                        --  This is a weird test, it skips setting validity
24021                        --  checks entirely if any element of S is out of
24022                        --  range of Character, what is that about ???
24023
24024                        exit when not In_Character_Range (C);
24025                        Options (J) := Get_Character (C);
24026
24027                        if J = Slen then
24028                           Set_Validity_Check_Options (Options);
24029                           exit;
24030                        else
24031                           J := J + 1;
24032                        end if;
24033                     end loop;
24034                  end;
24035
24036               elsif Nkind (A) = N_Identifier then
24037                  if Chars (A) = Name_All_Checks then
24038                     Set_Validity_Check_Options ("a");
24039                  elsif Chars (A) = Name_On then
24040                     Validity_Checks_On := True;
24041                  elsif Chars (A) = Name_Off then
24042                     Validity_Checks_On := False;
24043                  end if;
24044               end if;
24045            end if;
24046         end Validity_Checks;
24047
24048         --------------
24049         -- Volatile --
24050         --------------
24051
24052         --  pragma Volatile (LOCAL_NAME);
24053
24054         when Pragma_Volatile =>
24055            Process_Atomic_Independent_Shared_Volatile;
24056
24057         -------------------------
24058         -- Volatile_Components --
24059         -------------------------
24060
24061         --  pragma Volatile_Components (array_LOCAL_NAME);
24062
24063         --  Volatile is handled by the same circuit as Atomic_Components
24064
24065         --------------------------
24066         -- Volatile_Full_Access --
24067         --------------------------
24068
24069         --  pragma Volatile_Full_Access (LOCAL_NAME);
24070
24071         when Pragma_Volatile_Full_Access =>
24072            GNAT_Pragma;
24073            Process_Atomic_Independent_Shared_Volatile;
24074
24075         -----------------------
24076         -- Volatile_Function --
24077         -----------------------
24078
24079         --  pragma Volatile_Function [ (boolean_EXPRESSION) ];
24080
24081         when Pragma_Volatile_Function => Volatile_Function : declare
24082            Over_Id   : Entity_Id;
24083            Spec_Id   : Entity_Id;
24084            Subp_Decl : Node_Id;
24085
24086         begin
24087            GNAT_Pragma;
24088            Check_No_Identifiers;
24089            Check_At_Most_N_Arguments (1);
24090
24091            Subp_Decl :=
24092              Find_Related_Declaration_Or_Body (N, Do_Checks => True);
24093
24094            --  Generic subprogram
24095
24096            if Nkind (Subp_Decl) = N_Generic_Subprogram_Declaration then
24097               null;
24098
24099            --  Body acts as spec
24100
24101            elsif Nkind (Subp_Decl) = N_Subprogram_Body
24102              and then No (Corresponding_Spec (Subp_Decl))
24103            then
24104               null;
24105
24106            --  Body stub acts as spec
24107
24108            elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
24109              and then No (Corresponding_Spec_Of_Stub (Subp_Decl))
24110            then
24111               null;
24112
24113            --  Subprogram
24114
24115            elsif Nkind (Subp_Decl) = N_Subprogram_Declaration then
24116               null;
24117
24118            else
24119               Pragma_Misplaced;
24120               return;
24121            end if;
24122
24123            Spec_Id := Unique_Defining_Entity (Subp_Decl);
24124
24125            if not Ekind_In (Spec_Id, E_Function, E_Generic_Function) then
24126               Pragma_Misplaced;
24127               return;
24128            end if;
24129
24130            --  A pragma that applies to a Ghost entity becomes Ghost for the
24131            --  purposes of legality checks and removal of ignored Ghost code.
24132
24133            Mark_Ghost_Pragma (N, Spec_Id);
24134
24135            --  Chain the pragma on the contract for completeness
24136
24137            Add_Contract_Item (N, Spec_Id);
24138
24139            --  The legality checks of pragma Volatile_Function are affected by
24140            --  the SPARK mode in effect. Analyze all pragmas in a specific
24141            --  order.
24142
24143            Analyze_If_Present (Pragma_SPARK_Mode);
24144
24145            --  A volatile function cannot override a non-volatile function
24146            --  (SPARK RM 7.1.2(15)). Overriding checks are usually performed
24147            --  in New_Overloaded_Entity, however at that point the pragma has
24148            --  not been processed yet.
24149
24150            Over_Id := Overridden_Operation (Spec_Id);
24151
24152            if Present (Over_Id)
24153              and then not Is_Volatile_Function (Over_Id)
24154            then
24155               Error_Msg_N
24156                 ("incompatible volatile function values in effect", Spec_Id);
24157
24158               Error_Msg_Sloc := Sloc (Over_Id);
24159               Error_Msg_N
24160                 ("\& declared # with Volatile_Function value False",
24161                  Spec_Id);
24162
24163               Error_Msg_Sloc := Sloc (Spec_Id);
24164               Error_Msg_N
24165                 ("\overridden # with Volatile_Function value True",
24166                  Spec_Id);
24167            end if;
24168
24169            --  Analyze the Boolean expression (if any)
24170
24171            if Present (Arg1) then
24172               Check_Static_Boolean_Expression (Get_Pragma_Arg (Arg1));
24173            end if;
24174         end Volatile_Function;
24175
24176         ----------------------
24177         -- Warning_As_Error --
24178         ----------------------
24179
24180         --  pragma Warning_As_Error (static_string_EXPRESSION);
24181
24182         when Pragma_Warning_As_Error =>
24183            GNAT_Pragma;
24184            Check_Arg_Count (1);
24185            Check_No_Identifiers;
24186            Check_Valid_Configuration_Pragma;
24187
24188            if not Is_Static_String_Expression (Arg1) then
24189               Error_Pragma_Arg
24190                 ("argument of pragma% must be static string expression",
24191                  Arg1);
24192
24193            --  OK static string expression
24194
24195            else
24196               Acquire_Warning_Match_String (Arg1);
24197               Warnings_As_Errors_Count := Warnings_As_Errors_Count + 1;
24198               Warnings_As_Errors (Warnings_As_Errors_Count) :=
24199                 new String'(Name_Buffer (1 .. Name_Len));
24200            end if;
24201
24202         --------------
24203         -- Warnings --
24204         --------------
24205
24206         --  pragma Warnings ([TOOL_NAME,] DETAILS [, REASON]);
24207
24208         --  DETAILS ::= On | Off
24209         --  DETAILS ::= On | Off, local_NAME
24210         --  DETAILS ::= static_string_EXPRESSION
24211         --  DETAILS ::= On | Off, static_string_EXPRESSION
24212
24213         --  TOOL_NAME ::= GNAT | GNATProve
24214
24215         --  REASON ::= Reason => STRING_LITERAL {& STRING_LITERAL}
24216
24217         --  Note: If the first argument matches an allowed tool name, it is
24218         --  always considered to be a tool name, even if there is a string
24219         --  variable of that name.
24220
24221         --  Note if the second argument of DETAILS is a local_NAME then the
24222         --  second form is always understood. If the intention is to use
24223         --  the fourth form, then you can write NAME & "" to force the
24224         --  intepretation as a static_string_EXPRESSION.
24225
24226         when Pragma_Warnings => Warnings : declare
24227            Reason : String_Id;
24228
24229         begin
24230            GNAT_Pragma;
24231            Check_At_Least_N_Arguments (1);
24232
24233            --  See if last argument is labeled Reason. If so, make sure we
24234            --  have a string literal or a concatenation of string literals,
24235            --  and acquire the REASON string. Then remove the REASON argument
24236            --  by decreasing Num_Args by one; Remaining processing looks only
24237            --  at first Num_Args arguments).
24238
24239            declare
24240               Last_Arg : constant Node_Id :=
24241                            Last (Pragma_Argument_Associations (N));
24242
24243            begin
24244               if Nkind (Last_Arg) = N_Pragma_Argument_Association
24245                 and then Chars (Last_Arg) = Name_Reason
24246               then
24247                  Start_String;
24248                  Get_Reason_String (Get_Pragma_Arg (Last_Arg));
24249                  Reason := End_String;
24250                  Arg_Count := Arg_Count - 1;
24251
24252                  --  Not allowed in compiler units (bootstrap issues)
24253
24254                  Check_Compiler_Unit ("Reason for pragma Warnings", N);
24255
24256               --  No REASON string, set null string as reason
24257
24258               else
24259                  Reason := Null_String_Id;
24260               end if;
24261            end;
24262
24263            --  Now proceed with REASON taken care of and eliminated
24264
24265            Check_No_Identifiers;
24266
24267            --  If debug flag -gnatd.i is set, pragma is ignored
24268
24269            if Debug_Flag_Dot_I then
24270               return;
24271            end if;
24272
24273            --  Process various forms of the pragma
24274
24275            declare
24276               Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
24277               Shifted_Args : List_Id;
24278
24279            begin
24280               --  See if first argument is a tool name, currently either
24281               --  GNAT or GNATprove. If so, either ignore the pragma if the
24282               --  tool used does not match, or continue as if no tool name
24283               --  was given otherwise, by shifting the arguments.
24284
24285               if Nkind (Argx) = N_Identifier
24286                 and then Nam_In (Chars (Argx), Name_Gnat, Name_Gnatprove)
24287               then
24288                  if Chars (Argx) = Name_Gnat then
24289                     if CodePeer_Mode or GNATprove_Mode or ASIS_Mode then
24290                        Rewrite (N, Make_Null_Statement (Loc));
24291                        Analyze (N);
24292                        raise Pragma_Exit;
24293                     end if;
24294
24295                  elsif Chars (Argx) = Name_Gnatprove then
24296                     if not GNATprove_Mode then
24297                        Rewrite (N, Make_Null_Statement (Loc));
24298                        Analyze (N);
24299                        raise Pragma_Exit;
24300                     end if;
24301
24302                  else
24303                     raise Program_Error;
24304                  end if;
24305
24306                  --  At this point, the pragma Warnings applies to the tool,
24307                  --  so continue with shifted arguments.
24308
24309                  Arg_Count := Arg_Count - 1;
24310
24311                  if Arg_Count = 1 then
24312                     Shifted_Args := New_List (New_Copy (Arg2));
24313                  elsif Arg_Count = 2 then
24314                     Shifted_Args := New_List (New_Copy (Arg2),
24315                                               New_Copy (Arg3));
24316                  elsif Arg_Count = 3 then
24317                     Shifted_Args := New_List (New_Copy (Arg2),
24318                                               New_Copy (Arg3),
24319                                               New_Copy (Arg4));
24320                  else
24321                     raise Program_Error;
24322                  end if;
24323
24324                  Rewrite (N,
24325                    Make_Pragma (Loc,
24326                      Chars                        => Name_Warnings,
24327                      Pragma_Argument_Associations => Shifted_Args));
24328                  Analyze (N);
24329                  raise Pragma_Exit;
24330               end if;
24331
24332               --  One argument case
24333
24334               if Arg_Count = 1 then
24335
24336                  --  On/Off one argument case was processed by parser
24337
24338                  if Nkind (Argx) = N_Identifier
24339                    and then Nam_In (Chars (Argx), Name_On, Name_Off)
24340                  then
24341                     null;
24342
24343                  --  One argument case must be ON/OFF or static string expr
24344
24345                  elsif not Is_Static_String_Expression (Arg1) then
24346                     Error_Pragma_Arg
24347                       ("argument of pragma% must be On/Off or static string "
24348                        & "expression", Arg1);
24349
24350                  --  One argument string expression case
24351
24352                  else
24353                     declare
24354                        Lit : constant Node_Id   := Expr_Value_S (Argx);
24355                        Str : constant String_Id := Strval (Lit);
24356                        Len : constant Nat       := String_Length (Str);
24357                        C   : Char_Code;
24358                        J   : Nat;
24359                        OK  : Boolean;
24360                        Chr : Character;
24361
24362                     begin
24363                        J := 1;
24364                        while J <= Len loop
24365                           C := Get_String_Char (Str, J);
24366                           OK := In_Character_Range (C);
24367
24368                           if OK then
24369                              Chr := Get_Character (C);
24370
24371                              --  Dash case: only -Wxxx is accepted
24372
24373                              if J = 1
24374                                and then J < Len
24375                                and then Chr = '-'
24376                              then
24377                                 J := J + 1;
24378                                 C := Get_String_Char (Str, J);
24379                                 Chr := Get_Character (C);
24380                                 exit when Chr = 'W';
24381                                 OK := False;
24382
24383                              --  Dot case
24384
24385                              elsif J < Len and then Chr = '.' then
24386                                 J := J + 1;
24387                                 C := Get_String_Char (Str, J);
24388                                 Chr := Get_Character (C);
24389
24390                                 if not Set_Dot_Warning_Switch (Chr) then
24391                                    Error_Pragma_Arg
24392                                      ("invalid warning switch character "
24393                                       & '.' & Chr, Arg1);
24394                                 end if;
24395
24396                              --  Non-Dot case
24397
24398                              else
24399                                 OK := Set_Warning_Switch (Chr);
24400                              end if;
24401
24402                              if not OK then
24403                                 Error_Pragma_Arg
24404                                   ("invalid warning switch character " & Chr,
24405                                    Arg1);
24406                              end if;
24407
24408                           else
24409                              Error_Pragma_Arg
24410                                ("invalid wide character in warning switch ",
24411                                 Arg1);
24412                           end if;
24413
24414                           J := J + 1;
24415                        end loop;
24416                     end;
24417                  end if;
24418
24419               --  Two or more arguments (must be two)
24420
24421               else
24422                  Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
24423                  Check_Arg_Count (2);
24424
24425                  declare
24426                     E_Id : Node_Id;
24427                     E    : Entity_Id;
24428                     Err  : Boolean;
24429
24430                  begin
24431                     E_Id := Get_Pragma_Arg (Arg2);
24432                     Analyze (E_Id);
24433
24434                     --  In the expansion of an inlined body, a reference to
24435                     --  the formal may be wrapped in a conversion if the
24436                     --  actual is a conversion. Retrieve the real entity name.
24437
24438                     if (In_Instance_Body or In_Inlined_Body)
24439                       and then Nkind (E_Id) = N_Unchecked_Type_Conversion
24440                     then
24441                        E_Id := Expression (E_Id);
24442                     end if;
24443
24444                     --  Entity name case
24445
24446                     if Is_Entity_Name (E_Id) then
24447                        E := Entity (E_Id);
24448
24449                        if E = Any_Id then
24450                           return;
24451                        else
24452                           loop
24453                              Set_Warnings_Off
24454                                (E, (Chars (Get_Pragma_Arg (Arg1)) =
24455                                      Name_Off));
24456
24457                              --  For OFF case, make entry in warnings off
24458                              --  pragma table for later processing. But we do
24459                              --  not do that within an instance, since these
24460                              --  warnings are about what is needed in the
24461                              --  template, not an instance of it.
24462
24463                              if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
24464                                and then Warn_On_Warnings_Off
24465                                and then not In_Instance
24466                              then
24467                                 Warnings_Off_Pragmas.Append ((N, E, Reason));
24468                              end if;
24469
24470                              if Is_Enumeration_Type (E) then
24471                                 declare
24472                                    Lit : Entity_Id;
24473                                 begin
24474                                    Lit := First_Literal (E);
24475                                    while Present (Lit) loop
24476                                       Set_Warnings_Off (Lit);
24477                                       Next_Literal (Lit);
24478                                    end loop;
24479                                 end;
24480                              end if;
24481
24482                              exit when No (Homonym (E));
24483                              E := Homonym (E);
24484                           end loop;
24485                        end if;
24486
24487                     --  Error if not entity or static string expression case
24488
24489                     elsif not Is_Static_String_Expression (Arg2) then
24490                        Error_Pragma_Arg
24491                          ("second argument of pragma% must be entity name "
24492                           & "or static string expression", Arg2);
24493
24494                     --  Static string expression case
24495
24496                     else
24497                        Acquire_Warning_Match_String (Arg2);
24498
24499                        --  Note on configuration pragma case: If this is a
24500                        --  configuration pragma, then for an OFF pragma, we
24501                        --  just set Config True in the call, which is all
24502                        --  that needs to be done. For the case of ON, this
24503                        --  is normally an error, unless it is canceling the
24504                        --  effect of a previous OFF pragma in the same file.
24505                        --  In any other case, an error will be signalled (ON
24506                        --  with no matching OFF).
24507
24508                        --  Note: We set Used if we are inside a generic to
24509                        --  disable the test that the non-config case actually
24510                        --  cancels a warning. That's because we can't be sure
24511                        --  there isn't an instantiation in some other unit
24512                        --  where a warning is suppressed.
24513
24514                        --  We could do a little better here by checking if the
24515                        --  generic unit we are inside is public, but for now
24516                        --  we don't bother with that refinement.
24517
24518                        if Chars (Argx) = Name_Off then
24519                           Set_Specific_Warning_Off
24520                             (Loc, Name_Buffer (1 .. Name_Len), Reason,
24521                              Config => Is_Configuration_Pragma,
24522                              Used   => Inside_A_Generic or else In_Instance);
24523
24524                        elsif Chars (Argx) = Name_On then
24525                           Set_Specific_Warning_On
24526                             (Loc, Name_Buffer (1 .. Name_Len), Err);
24527
24528                           if Err then
24529                              Error_Msg
24530                                ("??pragma Warnings On with no matching "
24531                                 & "Warnings Off", Loc);
24532                           end if;
24533                        end if;
24534                     end if;
24535                  end;
24536               end if;
24537            end;
24538         end Warnings;
24539
24540         -------------------
24541         -- Weak_External --
24542         -------------------
24543
24544         --  pragma Weak_External ([Entity =>] LOCAL_NAME);
24545
24546         when Pragma_Weak_External => Weak_External : declare
24547            Ent : Entity_Id;
24548
24549         begin
24550            GNAT_Pragma;
24551            Check_Arg_Count (1);
24552            Check_Optional_Identifier (Arg1, Name_Entity);
24553            Check_Arg_Is_Library_Level_Local_Name (Arg1);
24554            Ent := Entity (Get_Pragma_Arg (Arg1));
24555
24556            if Rep_Item_Too_Early (Ent, N) then
24557               return;
24558            else
24559               Ent := Underlying_Type (Ent);
24560            end if;
24561
24562            --  The only processing required is to link this item on to the
24563            --  list of rep items for the given entity. This is accomplished
24564            --  by the call to Rep_Item_Too_Late (when no error is detected
24565            --  and False is returned).
24566
24567            if Rep_Item_Too_Late (Ent, N) then
24568               return;
24569            else
24570               Set_Has_Gigi_Rep_Item (Ent);
24571            end if;
24572         end Weak_External;
24573
24574         -----------------------------
24575         -- Wide_Character_Encoding --
24576         -----------------------------
24577
24578         --  pragma Wide_Character_Encoding (IDENTIFIER);
24579
24580         when Pragma_Wide_Character_Encoding =>
24581            GNAT_Pragma;
24582
24583            --  Nothing to do, handled in parser. Note that we do not enforce
24584            --  configuration pragma placement, this pragma can appear at any
24585            --  place in the source, allowing mixed encodings within a single
24586            --  source program.
24587
24588            null;
24589
24590         --------------------
24591         -- Unknown_Pragma --
24592         --------------------
24593
24594         --  Should be impossible, since the case of an unknown pragma is
24595         --  separately processed before the case statement is entered.
24596
24597         when Unknown_Pragma =>
24598            raise Program_Error;
24599      end case;
24600
24601      --  AI05-0144: detect dangerous order dependence. Disabled for now,
24602      --  until AI is formally approved.
24603
24604      --  Check_Order_Dependence;
24605
24606   exception
24607      when Pragma_Exit => null;
24608   end Analyze_Pragma;
24609
24610   ---------------------------------------------
24611   -- Analyze_Pre_Post_Condition_In_Decl_Part --
24612   ---------------------------------------------
24613
24614   --  WARNING: This routine manages Ghost regions. Return statements must be
24615   --  replaced by gotos which jump to the end of the routine and restore the
24616   --  Ghost mode.
24617
24618   procedure Analyze_Pre_Post_Condition_In_Decl_Part
24619     (N         : Node_Id;
24620      Freeze_Id : Entity_Id := Empty)
24621   is
24622      Subp_Decl : constant Node_Id   := Find_Related_Declaration_Or_Body (N);
24623      Spec_Id   : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
24624
24625      Disp_Typ : Entity_Id;
24626      --  The dispatching type of the subprogram subject to the pre- or
24627      --  postcondition.
24628
24629      function Check_References (Nod : Node_Id) return Traverse_Result;
24630      --  Check that expression Nod does not mention non-primitives of the
24631      --  type, global objects of the type, or other illegalities described
24632      --  and implied by AI12-0113.
24633
24634      ----------------------
24635      -- Check_References --
24636      ----------------------
24637
24638      function Check_References (Nod : Node_Id) return Traverse_Result is
24639      begin
24640         if Nkind (Nod) = N_Function_Call
24641           and then Is_Entity_Name (Name (Nod))
24642         then
24643            declare
24644               Func : constant Entity_Id := Entity (Name (Nod));
24645               Form : Entity_Id;
24646
24647            begin
24648               --  An operation of the type must be a primitive
24649
24650               if No (Find_Dispatching_Type (Func)) then
24651                  Form := First_Formal (Func);
24652                  while Present (Form) loop
24653                     if Etype (Form) = Disp_Typ then
24654                        Error_Msg_NE
24655                          ("operation in class-wide condition must be "
24656                           & "primitive of &", Nod, Disp_Typ);
24657                     end if;
24658
24659                     Next_Formal (Form);
24660                  end loop;
24661
24662                  --  A return object of the type is illegal as well
24663
24664                  if Etype (Func) = Disp_Typ
24665                    or else Etype (Func) = Class_Wide_Type (Disp_Typ)
24666                  then
24667                     Error_Msg_NE
24668                       ("operation in class-wide condition must be primitive "
24669                        & "of &", Nod, Disp_Typ);
24670                  end if;
24671
24672               --  Otherwise we have a call to an overridden primitive, and we
24673               --  will create a common class-wide clone for the body of
24674               --  original operation and its eventual inherited versions.  If
24675               --  the original operation dispatches on result it is never
24676               --  inherited and there is no need for a clone. There is not
24677               --  need for a clone either in GNATprove mode, as cases that
24678               --  would require it are rejected (when an inherited primitive
24679               --  calls an overridden operation in a class-wide contract), and
24680               --  the clone would make proof impossible in some cases.
24681
24682               elsif not Is_Abstract_Subprogram (Spec_Id)
24683                 and then No (Class_Wide_Clone (Spec_Id))
24684                 and then not Has_Controlling_Result (Spec_Id)
24685                 and then not GNATprove_Mode
24686               then
24687                  Build_Class_Wide_Clone_Decl (Spec_Id);
24688               end if;
24689            end;
24690
24691         elsif Is_Entity_Name (Nod)
24692           and then
24693             (Etype (Nod) = Disp_Typ
24694               or else Etype (Nod) = Class_Wide_Type (Disp_Typ))
24695           and then Ekind_In (Entity (Nod), E_Constant, E_Variable)
24696         then
24697            Error_Msg_NE
24698              ("object in class-wide condition must be formal of type &",
24699                Nod, Disp_Typ);
24700
24701         elsif Nkind (Nod) = N_Explicit_Dereference
24702           and then (Etype (Nod) = Disp_Typ
24703                      or else Etype (Nod) = Class_Wide_Type (Disp_Typ))
24704           and then (not Is_Entity_Name (Prefix (Nod))
24705                      or else not Is_Formal (Entity (Prefix (Nod))))
24706         then
24707            Error_Msg_NE
24708              ("operation in class-wide condition must be primitive of &",
24709               Nod, Disp_Typ);
24710         end if;
24711
24712         return OK;
24713      end Check_References;
24714
24715      procedure Check_Class_Wide_Condition is
24716        new Traverse_Proc (Check_References);
24717
24718      --  Local variables
24719
24720      Expr     : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
24721      Saved_GM : constant Ghost_Mode_Type := Ghost_Mode;
24722      --  Save the Ghost mode to restore on exit
24723
24724      Errors        : Nat;
24725      Restore_Scope : Boolean := False;
24726
24727   --  Start of processing for Analyze_Pre_Post_Condition_In_Decl_Part
24728
24729   begin
24730      --  Do not analyze the pragma multiple times
24731
24732      if Is_Analyzed_Pragma (N) then
24733         return;
24734      end if;
24735
24736      --  Set the Ghost mode in effect from the pragma. Due to the delayed
24737      --  analysis of the pragma, the Ghost mode at point of declaration and
24738      --  point of analysis may not necessarily be the same. Use the mode in
24739      --  effect at the point of declaration.
24740
24741      Set_Ghost_Mode (N);
24742
24743      --  Ensure that the subprogram and its formals are visible when analyzing
24744      --  the expression of the pragma.
24745
24746      if not In_Open_Scopes (Spec_Id) then
24747         Restore_Scope := True;
24748         Push_Scope (Spec_Id);
24749
24750         if Is_Generic_Subprogram (Spec_Id) then
24751            Install_Generic_Formals (Spec_Id);
24752         else
24753            Install_Formals (Spec_Id);
24754         end if;
24755      end if;
24756
24757      Errors := Serious_Errors_Detected;
24758      Preanalyze_Assert_Expression (Expr, Standard_Boolean);
24759
24760      --  Emit a clarification message when the expression contains at least
24761      --  one undefined reference, possibly due to contract freezing.
24762
24763      if Errors /= Serious_Errors_Detected
24764        and then Present (Freeze_Id)
24765        and then Has_Undefined_Reference (Expr)
24766      then
24767         Contract_Freeze_Error (Spec_Id, Freeze_Id);
24768      end if;
24769
24770      if Class_Present (N) then
24771
24772         --  Verify that a class-wide condition is legal, i.e. the operation is
24773         --  a primitive of a tagged type. Note that a generic subprogram is
24774         --  not a primitive operation.
24775
24776         Disp_Typ := Find_Dispatching_Type (Spec_Id);
24777
24778         if No (Disp_Typ) or else Is_Generic_Subprogram (Spec_Id) then
24779            Error_Msg_Name_1 := Original_Aspect_Pragma_Name (N);
24780
24781            if From_Aspect_Specification (N) then
24782               Error_Msg_N
24783                 ("aspect % can only be specified for a primitive operation "
24784                  & "of a tagged type", Corresponding_Aspect (N));
24785
24786            --  The pragma is a source construct
24787
24788            else
24789               Error_Msg_N
24790                 ("pragma % can only be specified for a primitive operation "
24791                  & "of a tagged type", N);
24792            end if;
24793
24794         --  Remaining semantic checks require a full tree traversal
24795
24796         else
24797            Check_Class_Wide_Condition (Expr);
24798         end if;
24799
24800      end if;
24801
24802      if Restore_Scope then
24803         End_Scope;
24804      end if;
24805
24806      --  If analysis of the condition indicates that a class-wide clone
24807      --  has been created, build and analyze its declaration.
24808
24809      if Is_Subprogram (Spec_Id)
24810        and then Present (Class_Wide_Clone (Spec_Id))
24811      then
24812         Analyze (Unit_Declaration_Node (Class_Wide_Clone (Spec_Id)));
24813      end if;
24814
24815      --  Currently it is not possible to inline pre/postconditions on a
24816      --  subprogram subject to pragma Inline_Always.
24817
24818      Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
24819      Set_Is_Analyzed_Pragma (N);
24820
24821      Restore_Ghost_Mode (Saved_GM);
24822   end Analyze_Pre_Post_Condition_In_Decl_Part;
24823
24824   ------------------------------------------
24825   -- Analyze_Refined_Depends_In_Decl_Part --
24826   ------------------------------------------
24827
24828   procedure Analyze_Refined_Depends_In_Decl_Part (N : Node_Id) is
24829      procedure Check_Dependency_Clause
24830        (Spec_Id       : Entity_Id;
24831         Dep_Clause    : Node_Id;
24832         Dep_States    : Elist_Id;
24833         Refinements   : List_Id;
24834         Matched_Items : in out Elist_Id);
24835      --  Try to match a single dependency clause Dep_Clause against one or
24836      --  more refinement clauses found in list Refinements. Each successful
24837      --  match eliminates at least one refinement clause from Refinements.
24838      --  Spec_Id denotes the entity of the related subprogram. Dep_States
24839      --  denotes the entities of all abstract states which appear in pragma
24840      --  Depends. Matched_Items contains the entities of all successfully
24841      --  matched items found in pragma Depends.
24842
24843      procedure Check_Output_States
24844        (Spec_Id      : Entity_Id;
24845         Spec_Inputs  : Elist_Id;
24846         Spec_Outputs : Elist_Id;
24847         Body_Inputs  : Elist_Id;
24848         Body_Outputs : Elist_Id);
24849      --  Determine whether pragma Depends contains an output state with a
24850      --  visible refinement and if so, ensure that pragma Refined_Depends
24851      --  mentions all its constituents as outputs. Spec_Id is the entity of
24852      --  the related subprograms. Spec_Inputs and Spec_Outputs denote the
24853      --  inputs and outputs of the subprogram spec synthesized from pragma
24854      --  Depends. Body_Inputs and Body_Outputs denote the inputs and outputs
24855      --  of the subprogram body synthesized from pragma Refined_Depends.
24856
24857      function Collect_States (Clauses : List_Id) return Elist_Id;
24858      --  Given a normalized list of dependencies obtained from calling
24859      --  Normalize_Clauses, return a list containing the entities of all
24860      --  states appearing in dependencies. It helps in checking refinements
24861      --  involving a state and a corresponding constituent which is not a
24862      --  direct constituent of the state.
24863
24864      procedure Normalize_Clauses (Clauses : List_Id);
24865      --  Given a list of dependence or refinement clauses Clauses, normalize
24866      --  each clause by creating multiple dependencies with exactly one input
24867      --  and one output.
24868
24869      procedure Remove_Extra_Clauses
24870        (Clauses       : List_Id;
24871         Matched_Items : Elist_Id);
24872      --  Given a list of refinement clauses Clauses, remove all clauses whose
24873      --  inputs and/or outputs have been previously matched. See the body for
24874      --  all special cases. Matched_Items contains the entities of all matched
24875      --  items found in pragma Depends.
24876
24877      procedure Report_Extra_Clauses
24878        (Spec_Id : Entity_Id;
24879         Clauses : List_Id);
24880      --  Emit an error for each extra clause found in list Clauses. Spec_Id
24881      --  denotes the entity of the related subprogram.
24882
24883      -----------------------------
24884      -- Check_Dependency_Clause --
24885      -----------------------------
24886
24887      procedure Check_Dependency_Clause
24888        (Spec_Id       : Entity_Id;
24889         Dep_Clause    : Node_Id;
24890         Dep_States    : Elist_Id;
24891         Refinements   : List_Id;
24892         Matched_Items : in out Elist_Id)
24893      is
24894         Dep_Input  : constant Node_Id := Expression (Dep_Clause);
24895         Dep_Output : constant Node_Id := First (Choices (Dep_Clause));
24896
24897         function Is_Already_Matched (Dep_Item : Node_Id) return Boolean;
24898         --  Determine whether dependency item Dep_Item has been matched in a
24899         --  previous clause.
24900
24901         function Is_In_Out_State_Clause return Boolean;
24902         --  Determine whether dependence clause Dep_Clause denotes an abstract
24903         --  state that depends on itself (State => State).
24904
24905         function Is_Null_Refined_State (Item : Node_Id) return Boolean;
24906         --  Determine whether item Item denotes an abstract state with visible
24907         --  null refinement.
24908
24909         procedure Match_Items
24910           (Dep_Item : Node_Id;
24911            Ref_Item : Node_Id;
24912            Matched  : out Boolean);
24913         --  Try to match dependence item Dep_Item against refinement item
24914         --  Ref_Item. To match against a possible null refinement (see 2, 9),
24915         --  set Ref_Item to Empty. Flag Matched is set to True when one of
24916         --  the following conformance scenarios is in effect:
24917         --    1) Both items denote null
24918         --    2) Dep_Item denotes null and Ref_Item is Empty (special case)
24919         --    3) Both items denote attribute 'Result
24920         --    4) Both items denote the same object
24921         --    5) Both items denote the same formal parameter
24922         --    6) Both items denote the same current instance of a type
24923         --    7) Both items denote the same discriminant
24924         --    8) Dep_Item is an abstract state with visible null refinement
24925         --       and Ref_Item denotes null.
24926         --    9) Dep_Item is an abstract state with visible null refinement
24927         --       and Ref_Item is Empty (special case).
24928         --   10) Dep_Item is an abstract state with full or partial visible
24929         --       non-null refinement and Ref_Item denotes one of its
24930         --       constituents.
24931         --   11) Dep_Item is an abstract state without a full visible
24932         --       refinement and Ref_Item denotes the same state.
24933         --  When scenario 10 is in effect, the entity of the abstract state
24934         --  denoted by Dep_Item is added to list Refined_States.
24935
24936         procedure Record_Item (Item_Id : Entity_Id);
24937         --  Store the entity of an item denoted by Item_Id in Matched_Items
24938
24939         ------------------------
24940         -- Is_Already_Matched --
24941         ------------------------
24942
24943         function Is_Already_Matched (Dep_Item : Node_Id) return Boolean is
24944            Item_Id : Entity_Id := Empty;
24945
24946         begin
24947            --  When the dependency item denotes attribute 'Result, check for
24948            --  the entity of the related subprogram.
24949
24950            if Is_Attribute_Result (Dep_Item) then
24951               Item_Id := Spec_Id;
24952
24953            elsif Is_Entity_Name (Dep_Item) then
24954               Item_Id := Available_View (Entity_Of (Dep_Item));
24955            end if;
24956
24957            return
24958              Present (Item_Id) and then Contains (Matched_Items, Item_Id);
24959         end Is_Already_Matched;
24960
24961         ----------------------------
24962         -- Is_In_Out_State_Clause --
24963         ----------------------------
24964
24965         function Is_In_Out_State_Clause return Boolean is
24966            Dep_Input_Id  : Entity_Id;
24967            Dep_Output_Id : Entity_Id;
24968
24969         begin
24970            --  Detect the following clause:
24971            --    State => State
24972
24973            if Is_Entity_Name (Dep_Input)
24974              and then Is_Entity_Name (Dep_Output)
24975            then
24976               --  Handle abstract views generated for limited with clauses
24977
24978               Dep_Input_Id  := Available_View (Entity_Of (Dep_Input));
24979               Dep_Output_Id := Available_View (Entity_Of (Dep_Output));
24980
24981               return
24982                 Ekind (Dep_Input_Id) = E_Abstract_State
24983                   and then Dep_Input_Id = Dep_Output_Id;
24984            else
24985               return False;
24986            end if;
24987         end Is_In_Out_State_Clause;
24988
24989         ---------------------------
24990         -- Is_Null_Refined_State --
24991         ---------------------------
24992
24993         function Is_Null_Refined_State (Item : Node_Id) return Boolean is
24994            Item_Id : Entity_Id;
24995
24996         begin
24997            if Is_Entity_Name (Item) then
24998
24999               --  Handle abstract views generated for limited with clauses
25000
25001               Item_Id := Available_View (Entity_Of (Item));
25002
25003               return
25004                 Ekind (Item_Id) = E_Abstract_State
25005                   and then Has_Null_Visible_Refinement (Item_Id);
25006            else
25007               return False;
25008            end if;
25009         end Is_Null_Refined_State;
25010
25011         -----------------
25012         -- Match_Items --
25013         -----------------
25014
25015         procedure Match_Items
25016           (Dep_Item : Node_Id;
25017            Ref_Item : Node_Id;
25018            Matched  : out Boolean)
25019         is
25020            Dep_Item_Id : Entity_Id;
25021            Ref_Item_Id : Entity_Id;
25022
25023         begin
25024            --  Assume that the two items do not match
25025
25026            Matched := False;
25027
25028            --  A null matches null or Empty (special case)
25029
25030            if Nkind (Dep_Item) = N_Null
25031              and then (No (Ref_Item) or else Nkind (Ref_Item) = N_Null)
25032            then
25033               Matched := True;
25034
25035            --  Attribute 'Result matches attribute 'Result
25036
25037            elsif Is_Attribute_Result (Dep_Item)
25038              and then Is_Attribute_Result (Ref_Item)
25039            then
25040               --  Put the entity of the related function on the list of
25041               --  matched items because attribute 'Result does not carry
25042               --  an entity similar to states and constituents.
25043
25044               Record_Item (Spec_Id);
25045               Matched := True;
25046
25047            --  Abstract states, current instances of concurrent types,
25048            --  discriminants, formal parameters and objects.
25049
25050            elsif Is_Entity_Name (Dep_Item) then
25051
25052               --  Handle abstract views generated for limited with clauses
25053
25054               Dep_Item_Id := Available_View (Entity_Of (Dep_Item));
25055
25056               if Ekind (Dep_Item_Id) = E_Abstract_State then
25057
25058                  --  An abstract state with visible null refinement matches
25059                  --  null or Empty (special case).
25060
25061                  if Has_Null_Visible_Refinement (Dep_Item_Id)
25062                    and then (No (Ref_Item) or else Nkind (Ref_Item) = N_Null)
25063                  then
25064                     Record_Item (Dep_Item_Id);
25065                     Matched := True;
25066
25067                  --  An abstract state with visible non-null refinement
25068                  --  matches one of its constituents, or itself for an
25069                  --  abstract state with partial visible refinement.
25070
25071                  elsif Has_Non_Null_Visible_Refinement (Dep_Item_Id) then
25072                     if Is_Entity_Name (Ref_Item) then
25073                        Ref_Item_Id := Entity_Of (Ref_Item);
25074
25075                        if Ekind_In (Ref_Item_Id, E_Abstract_State,
25076                                                  E_Constant,
25077                                                  E_Variable)
25078                          and then Present (Encapsulating_State (Ref_Item_Id))
25079                          and then Find_Encapsulating_State
25080                                     (Dep_States, Ref_Item_Id) = Dep_Item_Id
25081                        then
25082                           Record_Item (Dep_Item_Id);
25083                           Matched := True;
25084
25085                        elsif not Has_Visible_Refinement (Dep_Item_Id)
25086                          and then Ref_Item_Id = Dep_Item_Id
25087                        then
25088                           Record_Item (Dep_Item_Id);
25089                           Matched := True;
25090                        end if;
25091                     end if;
25092
25093                  --  An abstract state without a visible refinement matches
25094                  --  itself.
25095
25096                  elsif Is_Entity_Name (Ref_Item)
25097                    and then Entity_Of (Ref_Item) = Dep_Item_Id
25098                  then
25099                     Record_Item (Dep_Item_Id);
25100                     Matched := True;
25101                  end if;
25102
25103               --  A current instance of a concurrent type, discriminant,
25104               --  formal parameter or an object matches itself.
25105
25106               elsif Is_Entity_Name (Ref_Item)
25107                 and then Entity_Of (Ref_Item) = Dep_Item_Id
25108               then
25109                  Record_Item (Dep_Item_Id);
25110                  Matched := True;
25111               end if;
25112            end if;
25113         end Match_Items;
25114
25115         -----------------
25116         -- Record_Item --
25117         -----------------
25118
25119         procedure Record_Item (Item_Id : Entity_Id) is
25120         begin
25121            if No (Matched_Items) then
25122               Matched_Items := New_Elmt_List;
25123            end if;
25124
25125            Append_Unique_Elmt (Item_Id, Matched_Items);
25126         end Record_Item;
25127
25128         --  Local variables
25129
25130         Clause_Matched  : Boolean := False;
25131         Dummy           : Boolean := False;
25132         Inputs_Match    : Boolean;
25133         Next_Ref_Clause : Node_Id;
25134         Outputs_Match   : Boolean;
25135         Ref_Clause      : Node_Id;
25136         Ref_Input       : Node_Id;
25137         Ref_Output      : Node_Id;
25138
25139      --  Start of processing for Check_Dependency_Clause
25140
25141      begin
25142         --  Do not perform this check in an instance because it was already
25143         --  performed successfully in the generic template.
25144
25145         if Is_Generic_Instance (Spec_Id) then
25146            return;
25147         end if;
25148
25149         --  Examine all refinement clauses and compare them against the
25150         --  dependence clause.
25151
25152         Ref_Clause := First (Refinements);
25153         while Present (Ref_Clause) loop
25154            Next_Ref_Clause := Next (Ref_Clause);
25155
25156            --  Obtain the attributes of the current refinement clause
25157
25158            Ref_Input  := Expression (Ref_Clause);
25159            Ref_Output := First (Choices (Ref_Clause));
25160
25161            --  The current refinement clause matches the dependence clause
25162            --  when both outputs match and both inputs match. See routine
25163            --  Match_Items for all possible conformance scenarios.
25164
25165            --    Depends           Dep_Output => Dep_Input
25166            --                          ^             ^
25167            --                        match ?       match ?
25168            --                          v             v
25169            --    Refined_Depends   Ref_Output => Ref_Input
25170
25171            Match_Items
25172              (Dep_Item => Dep_Input,
25173               Ref_Item => Ref_Input,
25174               Matched  => Inputs_Match);
25175
25176            Match_Items
25177              (Dep_Item => Dep_Output,
25178               Ref_Item => Ref_Output,
25179               Matched  => Outputs_Match);
25180
25181            --  An In_Out state clause may be matched against a refinement with
25182            --  a null input or null output as long as the non-null side of the
25183            --  relation contains a valid constituent of the In_Out_State.
25184
25185            if Is_In_Out_State_Clause then
25186
25187               --  Depends         => (State => State)
25188               --  Refined_Depends => (null => Constit)  --  OK
25189
25190               if Inputs_Match
25191                 and then not Outputs_Match
25192                 and then Nkind (Ref_Output) = N_Null
25193               then
25194                  Outputs_Match := True;
25195               end if;
25196
25197               --  Depends         => (State => State)
25198               --  Refined_Depends => (Constit => null)  --  OK
25199
25200               if not Inputs_Match
25201                 and then Outputs_Match
25202                 and then Nkind (Ref_Input) = N_Null
25203               then
25204                  Inputs_Match := True;
25205               end if;
25206            end if;
25207
25208            --  The current refinement clause is legally constructed following
25209            --  the rules in SPARK RM 7.2.5, therefore it can be removed from
25210            --  the pool of candidates. The seach continues because a single
25211            --  dependence clause may have multiple matching refinements.
25212
25213            if Inputs_Match and Outputs_Match then
25214               Clause_Matched := True;
25215               Remove (Ref_Clause);
25216            end if;
25217
25218            Ref_Clause := Next_Ref_Clause;
25219         end loop;
25220
25221         --  Depending on the order or composition of refinement clauses, an
25222         --  In_Out state clause may not be directly refinable.
25223
25224         --    Refined_State   => (State => (Constit_1, Constit_2))
25225         --    Depends         => ((Output, State) => (Input, State))
25226         --    Refined_Depends => (Constit_1 => Input, Output => Constit_2)
25227
25228         --  Matching normalized clause (State => State) fails because there is
25229         --  no direct refinement capable of satisfying this relation. Another
25230         --  similar case arises when clauses (Constit_1 => Input) and (Output
25231         --  => Constit_2) are matched first, leaving no candidates for clause
25232         --  (State => State). Both scenarios are legal as long as one of the
25233         --  previous clauses mentioned a valid constituent of State.
25234
25235         if not Clause_Matched
25236           and then Is_In_Out_State_Clause
25237           and then Is_Already_Matched (Dep_Input)
25238         then
25239            Clause_Matched := True;
25240         end if;
25241
25242         --  A clause where the input is an abstract state with visible null
25243         --  refinement or a 'Result attribute is implicitly matched when the
25244         --  output has already been matched in a previous clause.
25245
25246         --    Refined_State   => (State => null)
25247         --    Depends         => (Output => State)      --  implicitly OK
25248         --    Refined_Depends => (Output => ...)
25249         --    Depends         => (...'Result => State)  --  implicitly OK
25250         --    Refined_Depends => (...'Result => ...)
25251
25252         if not Clause_Matched
25253           and then Is_Null_Refined_State (Dep_Input)
25254           and then Is_Already_Matched (Dep_Output)
25255         then
25256            Clause_Matched := True;
25257         end if;
25258
25259         --  A clause where the output is an abstract state with visible null
25260         --  refinement is implicitly matched when the input has already been
25261         --  matched in a previous clause.
25262
25263         --    Refined_State     => (State => null)
25264         --    Depends           => (State => Input)  --  implicitly OK
25265         --    Refined_Depends   => (... => Input)
25266
25267         if not Clause_Matched
25268           and then Is_Null_Refined_State (Dep_Output)
25269           and then Is_Already_Matched (Dep_Input)
25270         then
25271            Clause_Matched := True;
25272         end if;
25273
25274         --  At this point either all refinement clauses have been examined or
25275         --  pragma Refined_Depends contains a solitary null. Only an abstract
25276         --  state with null refinement can possibly match these cases.
25277
25278         --    Refined_State   => (State => null)
25279         --    Depends         => (State => null)
25280         --    Refined_Depends =>  null            --  OK
25281
25282         if not Clause_Matched then
25283            Match_Items
25284              (Dep_Item => Dep_Input,
25285               Ref_Item => Empty,
25286               Matched  => Inputs_Match);
25287
25288            Match_Items
25289              (Dep_Item => Dep_Output,
25290               Ref_Item => Empty,
25291               Matched  => Outputs_Match);
25292
25293            Clause_Matched := Inputs_Match and Outputs_Match;
25294         end if;
25295
25296         --  If the contents of Refined_Depends are legal, then the current
25297         --  dependence clause should be satisfied either by an explicit match
25298         --  or by one of the special cases.
25299
25300         if not Clause_Matched then
25301            SPARK_Msg_NE
25302              (Fix_Msg (Spec_Id, "dependence clause of subprogram & has no "
25303               & "matching refinement in body"), Dep_Clause, Spec_Id);
25304         end if;
25305      end Check_Dependency_Clause;
25306
25307      -------------------------
25308      -- Check_Output_States --
25309      -------------------------
25310
25311      procedure Check_Output_States
25312        (Spec_Id      : Entity_Id;
25313         Spec_Inputs  : Elist_Id;
25314         Spec_Outputs : Elist_Id;
25315         Body_Inputs  : Elist_Id;
25316         Body_Outputs : Elist_Id)
25317      is
25318         procedure Check_Constituent_Usage (State_Id : Entity_Id);
25319         --  Determine whether all constituents of state State_Id with full
25320         --  visible refinement are used as outputs in pragma Refined_Depends.
25321         --  Emit an error if this is not the case (SPARK RM 7.2.4(5)).
25322
25323         -----------------------------
25324         -- Check_Constituent_Usage --
25325         -----------------------------
25326
25327         procedure Check_Constituent_Usage (State_Id : Entity_Id) is
25328            Constits     : constant Elist_Id :=
25329                             Partial_Refinement_Constituents (State_Id);
25330            Constit_Elmt : Elmt_Id;
25331            Constit_Id   : Entity_Id;
25332            Only_Partial : constant Boolean :=
25333                             not Has_Visible_Refinement (State_Id);
25334            Posted       : Boolean := False;
25335
25336         begin
25337            if Present (Constits) then
25338               Constit_Elmt := First_Elmt (Constits);
25339               while Present (Constit_Elmt) loop
25340                  Constit_Id := Node (Constit_Elmt);
25341
25342                  --  Issue an error when a constituent of State_Id is used,
25343                  --  and State_Id has only partial visible refinement
25344                  --  (SPARK RM 7.2.4(3d)).
25345
25346                  if Only_Partial then
25347                     if (Present (Body_Inputs)
25348                          and then Appears_In (Body_Inputs, Constit_Id))
25349                       or else
25350                        (Present (Body_Outputs)
25351                          and then Appears_In (Body_Outputs, Constit_Id))
25352                     then
25353                        Error_Msg_Name_1 := Chars (State_Id);
25354                        SPARK_Msg_NE
25355                          ("constituent & of state % cannot be used in "
25356                           & "dependence refinement", N, Constit_Id);
25357                        Error_Msg_Name_1 := Chars (State_Id);
25358                        SPARK_Msg_N ("\use state % instead", N);
25359                     end if;
25360
25361                  --  The constituent acts as an input (SPARK RM 7.2.5(3))
25362
25363                  elsif Present (Body_Inputs)
25364                    and then Appears_In (Body_Inputs, Constit_Id)
25365                  then
25366                     Error_Msg_Name_1 := Chars (State_Id);
25367                     SPARK_Msg_NE
25368                       ("constituent & of state % must act as output in "
25369                        & "dependence refinement", N, Constit_Id);
25370
25371                  --  The constituent is altogether missing (SPARK RM 7.2.5(3))
25372
25373                  elsif No (Body_Outputs)
25374                    or else not Appears_In (Body_Outputs, Constit_Id)
25375                  then
25376                     if not Posted then
25377                        Posted := True;
25378                        SPARK_Msg_NE
25379                          ("output state & must be replaced by all its "
25380                           & "constituents in dependence refinement",
25381                           N, State_Id);
25382                     end if;
25383
25384                     SPARK_Msg_NE
25385                       ("\constituent & is missing in output list",
25386                        N, Constit_Id);
25387                  end if;
25388
25389                  Next_Elmt (Constit_Elmt);
25390               end loop;
25391            end if;
25392         end Check_Constituent_Usage;
25393
25394         --  Local variables
25395
25396         Item      : Node_Id;
25397         Item_Elmt : Elmt_Id;
25398         Item_Id   : Entity_Id;
25399
25400      --  Start of processing for Check_Output_States
25401
25402      begin
25403         --  Do not perform this check in an instance because it was already
25404         --  performed successfully in the generic template.
25405
25406         if Is_Generic_Instance (Spec_Id) then
25407            null;
25408
25409         --  Inspect the outputs of pragma Depends looking for a state with a
25410         --  visible refinement.
25411
25412         elsif Present (Spec_Outputs) then
25413            Item_Elmt := First_Elmt (Spec_Outputs);
25414            while Present (Item_Elmt) loop
25415               Item := Node (Item_Elmt);
25416
25417               --  Deal with the mixed nature of the input and output lists
25418
25419               if Nkind (Item) = N_Defining_Identifier then
25420                  Item_Id := Item;
25421               else
25422                  Item_Id := Available_View (Entity_Of (Item));
25423               end if;
25424
25425               if Ekind (Item_Id) = E_Abstract_State then
25426
25427                  --  The state acts as an input-output, skip it
25428
25429                  if Present (Spec_Inputs)
25430                    and then Appears_In (Spec_Inputs, Item_Id)
25431                  then
25432                     null;
25433
25434                  --  Ensure that all of the constituents are utilized as
25435                  --  outputs in pragma Refined_Depends.
25436
25437                  elsif Has_Non_Null_Visible_Refinement (Item_Id) then
25438                     Check_Constituent_Usage (Item_Id);
25439                  end if;
25440               end if;
25441
25442               Next_Elmt (Item_Elmt);
25443            end loop;
25444         end if;
25445      end Check_Output_States;
25446
25447      --------------------
25448      -- Collect_States --
25449      --------------------
25450
25451      function Collect_States (Clauses : List_Id) return Elist_Id is
25452         procedure Collect_State
25453           (Item   : Node_Id;
25454            States : in out Elist_Id);
25455         --  Add the entity of Item to list States when it denotes to a state
25456
25457         -------------------
25458         -- Collect_State --
25459         -------------------
25460
25461         procedure Collect_State
25462           (Item   : Node_Id;
25463            States : in out Elist_Id)
25464         is
25465            Id : Entity_Id;
25466
25467         begin
25468            if Is_Entity_Name (Item) then
25469               Id := Entity_Of (Item);
25470
25471               if Ekind (Id) = E_Abstract_State then
25472                  if No (States) then
25473                     States := New_Elmt_List;
25474                  end if;
25475
25476                  Append_Unique_Elmt (Id, States);
25477               end if;
25478            end if;
25479         end Collect_State;
25480
25481         --  Local variables
25482
25483         Clause : Node_Id;
25484         Input  : Node_Id;
25485         Output : Node_Id;
25486         States : Elist_Id := No_Elist;
25487
25488      --  Start of processing for Collect_States
25489
25490      begin
25491         Clause := First (Clauses);
25492         while Present (Clause) loop
25493            Input  := Expression (Clause);
25494            Output := First (Choices (Clause));
25495
25496            Collect_State (Input,  States);
25497            Collect_State (Output, States);
25498
25499            Next (Clause);
25500         end loop;
25501
25502         return States;
25503      end Collect_States;
25504
25505      -----------------------
25506      -- Normalize_Clauses --
25507      -----------------------
25508
25509      procedure Normalize_Clauses (Clauses : List_Id) is
25510         procedure Normalize_Inputs (Clause : Node_Id);
25511         --  Normalize clause Clause by creating multiple clauses for each
25512         --  input item of Clause. It is assumed that Clause has exactly one
25513         --  output. The transformation is as follows:
25514         --
25515         --    Output => (Input_1, Input_2)      --  original
25516         --
25517         --    Output => Input_1                 --  normalizations
25518         --    Output => Input_2
25519
25520         procedure Normalize_Outputs (Clause : Node_Id);
25521         --  Normalize clause Clause by creating multiple clause for each
25522         --  output item of Clause. The transformation is as follows:
25523         --
25524         --    (Output_1, Output_2) => Input     --  original
25525         --
25526         --     Output_1 => Input                --  normalization
25527         --     Output_2 => Input
25528
25529         ----------------------
25530         -- Normalize_Inputs --
25531         ----------------------
25532
25533         procedure Normalize_Inputs (Clause : Node_Id) is
25534            Inputs     : constant Node_Id    := Expression (Clause);
25535            Loc        : constant Source_Ptr := Sloc (Clause);
25536            Output     : constant List_Id    := Choices (Clause);
25537            Last_Input : Node_Id;
25538            Input      : Node_Id;
25539            New_Clause : Node_Id;
25540            Next_Input : Node_Id;
25541
25542         begin
25543            --  Normalization is performed only when the original clause has
25544            --  more than one input. Multiple inputs appear as an aggregate.
25545
25546            if Nkind (Inputs) = N_Aggregate then
25547               Last_Input := Last (Expressions (Inputs));
25548
25549               --  Create a new clause for each input
25550
25551               Input := First (Expressions (Inputs));
25552               while Present (Input) loop
25553                  Next_Input := Next (Input);
25554
25555                  --  Unhook the current input from the original input list
25556                  --  because it will be relocated to a new clause.
25557
25558                  Remove (Input);
25559
25560                  --  Special processing for the last input. At this point the
25561                  --  original aggregate has been stripped down to one element.
25562                  --  Replace the aggregate by the element itself.
25563
25564                  if Input = Last_Input then
25565                     Rewrite (Inputs, Input);
25566
25567                  --  Generate a clause of the form:
25568                  --    Output => Input
25569
25570                  else
25571                     New_Clause :=
25572                       Make_Component_Association (Loc,
25573                         Choices    => New_Copy_List_Tree (Output),
25574                         Expression => Input);
25575
25576                     --  The new clause contains replicated content that has
25577                     --  already been analyzed, mark the clause as analyzed.
25578
25579                     Set_Analyzed (New_Clause);
25580                     Insert_After (Clause, New_Clause);
25581                  end if;
25582
25583                  Input := Next_Input;
25584               end loop;
25585            end if;
25586         end Normalize_Inputs;
25587
25588         -----------------------
25589         -- Normalize_Outputs --
25590         -----------------------
25591
25592         procedure Normalize_Outputs (Clause : Node_Id) is
25593            Inputs      : constant Node_Id    := Expression (Clause);
25594            Loc         : constant Source_Ptr := Sloc (Clause);
25595            Outputs     : constant Node_Id    := First (Choices (Clause));
25596            Last_Output : Node_Id;
25597            New_Clause  : Node_Id;
25598            Next_Output : Node_Id;
25599            Output      : Node_Id;
25600
25601         begin
25602            --  Multiple outputs appear as an aggregate. Nothing to do when
25603            --  the clause has exactly one output.
25604
25605            if Nkind (Outputs) = N_Aggregate then
25606               Last_Output := Last (Expressions (Outputs));
25607
25608               --  Create a clause for each output. Note that each time a new
25609               --  clause is created, the original output list slowly shrinks
25610               --  until there is one item left.
25611
25612               Output := First (Expressions (Outputs));
25613               while Present (Output) loop
25614                  Next_Output := Next (Output);
25615
25616                  --  Unhook the output from the original output list as it
25617                  --  will be relocated to a new clause.
25618
25619                  Remove (Output);
25620
25621                  --  Special processing for the last output. At this point
25622                  --  the original aggregate has been stripped down to one
25623                  --  element. Replace the aggregate by the element itself.
25624
25625                  if Output = Last_Output then
25626                     Rewrite (Outputs, Output);
25627
25628                  else
25629                     --  Generate a clause of the form:
25630                     --    (Output => Inputs)
25631
25632                     New_Clause :=
25633                       Make_Component_Association (Loc,
25634                         Choices    => New_List (Output),
25635                         Expression => New_Copy_Tree (Inputs));
25636
25637                     --  The new clause contains replicated content that has
25638                     --  already been analyzed. There is not need to reanalyze
25639                     --  them.
25640
25641                     Set_Analyzed (New_Clause);
25642                     Insert_After (Clause, New_Clause);
25643                  end if;
25644
25645                  Output := Next_Output;
25646               end loop;
25647            end if;
25648         end Normalize_Outputs;
25649
25650         --  Local variables
25651
25652         Clause : Node_Id;
25653
25654      --  Start of processing for Normalize_Clauses
25655
25656      begin
25657         Clause := First (Clauses);
25658         while Present (Clause) loop
25659            Normalize_Outputs (Clause);
25660            Next (Clause);
25661         end loop;
25662
25663         Clause := First (Clauses);
25664         while Present (Clause) loop
25665            Normalize_Inputs (Clause);
25666            Next (Clause);
25667         end loop;
25668      end Normalize_Clauses;
25669
25670      --------------------------
25671      -- Remove_Extra_Clauses --
25672      --------------------------
25673
25674      procedure Remove_Extra_Clauses
25675        (Clauses       : List_Id;
25676         Matched_Items : Elist_Id)
25677      is
25678         Clause      : Node_Id;
25679         Input       : Node_Id;
25680         Input_Id    : Entity_Id;
25681         Next_Clause : Node_Id;
25682         Output      : Node_Id;
25683         State_Id    : Entity_Id;
25684
25685      begin
25686         Clause := First (Clauses);
25687         while Present (Clause) loop
25688            Next_Clause := Next (Clause);
25689
25690            Input  := Expression (Clause);
25691            Output := First (Choices (Clause));
25692
25693            --  Recognize a clause of the form
25694
25695            --    null => Input
25696
25697            --  where Input is a constituent of a state which was already
25698            --  successfully matched. This clause must be removed because it
25699            --  simply indicates that some of the constituents of the state
25700            --  are not used.
25701
25702            --    Refined_State   => (State => (Constit_1, Constit_2))
25703            --    Depends         => (Output => State)
25704            --    Refined_Depends => ((Output => Constit_1),  --  State matched
25705            --                        (null => Constit_2))    --  OK
25706
25707            if Nkind (Output) = N_Null and then Is_Entity_Name (Input) then
25708
25709               --  Handle abstract views generated for limited with clauses
25710
25711               Input_Id := Available_View (Entity_Of (Input));
25712
25713               --  The input must be a constituent of a state
25714
25715               if Ekind_In (Input_Id, E_Abstract_State,
25716                                      E_Constant,
25717                                      E_Variable)
25718                 and then Present (Encapsulating_State (Input_Id))
25719               then
25720                  State_Id := Encapsulating_State (Input_Id);
25721
25722                  --  The state must have a non-null visible refinement and be
25723                  --  matched in a previous clause.
25724
25725                  if Has_Non_Null_Visible_Refinement (State_Id)
25726                    and then Contains (Matched_Items, State_Id)
25727                  then
25728                     Remove (Clause);
25729                  end if;
25730               end if;
25731
25732            --  Recognize a clause of the form
25733
25734            --    Output => null
25735
25736            --  where Output is an arbitrary item. This clause must be removed
25737            --  because a null input legitimately matches anything.
25738
25739            elsif Nkind (Input) = N_Null then
25740               Remove (Clause);
25741            end if;
25742
25743            Clause := Next_Clause;
25744         end loop;
25745      end Remove_Extra_Clauses;
25746
25747      --------------------------
25748      -- Report_Extra_Clauses --
25749      --------------------------
25750
25751      procedure Report_Extra_Clauses
25752        (Spec_Id : Entity_Id;
25753         Clauses : List_Id)
25754      is
25755         Clause : Node_Id;
25756
25757      begin
25758         --  Do not perform this check in an instance because it was already
25759         --  performed successfully in the generic template.
25760
25761         if Is_Generic_Instance (Spec_Id) then
25762            null;
25763
25764         elsif Present (Clauses) then
25765            Clause := First (Clauses);
25766            while Present (Clause) loop
25767               SPARK_Msg_N
25768                 ("unmatched or extra clause in dependence refinement",
25769                  Clause);
25770
25771               Next (Clause);
25772            end loop;
25773         end if;
25774      end Report_Extra_Clauses;
25775
25776      --  Local variables
25777
25778      Body_Decl : constant Node_Id   := Find_Related_Declaration_Or_Body (N);
25779      Body_Id   : constant Entity_Id := Defining_Entity (Body_Decl);
25780      Errors    : constant Nat       := Serious_Errors_Detected;
25781
25782      Clause : Node_Id;
25783      Deps   : Node_Id;
25784      Dummy  : Boolean;
25785      Refs   : Node_Id;
25786
25787      Body_Inputs  : Elist_Id := No_Elist;
25788      Body_Outputs : Elist_Id := No_Elist;
25789      --  The inputs and outputs of the subprogram body synthesized from pragma
25790      --  Refined_Depends.
25791
25792      Dependencies : List_Id := No_List;
25793      Depends      : Node_Id;
25794      --  The corresponding Depends pragma along with its clauses
25795
25796      Matched_Items : Elist_Id := No_Elist;
25797      --  A list containing the entities of all successfully matched items
25798      --  found in pragma Depends.
25799
25800      Refinements : List_Id := No_List;
25801      --  The clauses of pragma Refined_Depends
25802
25803      Spec_Id : Entity_Id;
25804      --  The entity of the subprogram subject to pragma Refined_Depends
25805
25806      Spec_Inputs  : Elist_Id := No_Elist;
25807      Spec_Outputs : Elist_Id := No_Elist;
25808      --  The inputs and outputs of the subprogram spec synthesized from pragma
25809      --  Depends.
25810
25811      States : Elist_Id := No_Elist;
25812      --  A list containing the entities of all states whose constituents
25813      --  appear in pragma Depends.
25814
25815   --  Start of processing for Analyze_Refined_Depends_In_Decl_Part
25816
25817   begin
25818      --  Do not analyze the pragma multiple times
25819
25820      if Is_Analyzed_Pragma (N) then
25821         return;
25822      end if;
25823
25824      Spec_Id := Unique_Defining_Entity (Body_Decl);
25825
25826      --  Use the anonymous object as the proper spec when Refined_Depends
25827      --  applies to the body of a single task type. The object carries the
25828      --  proper Chars as well as all non-refined versions of pragmas.
25829
25830      if Is_Single_Concurrent_Type (Spec_Id) then
25831         Spec_Id := Anonymous_Object (Spec_Id);
25832      end if;
25833
25834      Depends := Get_Pragma (Spec_Id, Pragma_Depends);
25835
25836      --  Subprogram declarations lacks pragma Depends. Refined_Depends is
25837      --  rendered useless as there is nothing to refine (SPARK RM 7.2.5(2)).
25838
25839      if No (Depends) then
25840         SPARK_Msg_NE
25841           (Fix_Msg (Spec_Id, "useless refinement, declaration of subprogram "
25842            & "& lacks aspect or pragma Depends"), N, Spec_Id);
25843         goto Leave;
25844      end if;
25845
25846      Deps := Expression (Get_Argument (Depends, Spec_Id));
25847
25848      --  A null dependency relation renders the refinement useless because it
25849      --  cannot possibly mention abstract states with visible refinement. Note
25850      --  that the inverse is not true as states may be refined to null
25851      --  (SPARK RM 7.2.5(2)).
25852
25853      if Nkind (Deps) = N_Null then
25854         SPARK_Msg_NE
25855           (Fix_Msg (Spec_Id, "useless refinement, subprogram & does not "
25856            & "depend on abstract state with visible refinement"), N, Spec_Id);
25857         goto Leave;
25858      end if;
25859
25860      --  Analyze Refined_Depends as if it behaved as a regular pragma Depends.
25861      --  This ensures that the categorization of all refined dependency items
25862      --  is consistent with their role.
25863
25864      Analyze_Depends_In_Decl_Part (N);
25865
25866      --  Do not match dependencies against refinements if Refined_Depends is
25867      --  illegal to avoid emitting misleading error.
25868
25869      if Serious_Errors_Detected = Errors then
25870
25871         --  The related subprogram lacks pragma [Refined_]Global. Synthesize
25872         --  the inputs and outputs of the subprogram spec and body to verify
25873         --  the use of states with visible refinement and their constituents.
25874
25875         if No (Get_Pragma (Spec_Id, Pragma_Global))
25876           or else No (Get_Pragma (Body_Id, Pragma_Refined_Global))
25877         then
25878            Collect_Subprogram_Inputs_Outputs
25879              (Subp_Id      => Spec_Id,
25880               Synthesize   => True,
25881               Subp_Inputs  => Spec_Inputs,
25882               Subp_Outputs => Spec_Outputs,
25883               Global_Seen  => Dummy);
25884
25885            Collect_Subprogram_Inputs_Outputs
25886              (Subp_Id      => Body_Id,
25887               Synthesize   => True,
25888               Subp_Inputs  => Body_Inputs,
25889               Subp_Outputs => Body_Outputs,
25890               Global_Seen  => Dummy);
25891
25892            --  For an output state with a visible refinement, ensure that all
25893            --  constituents appear as outputs in the dependency refinement.
25894
25895            Check_Output_States
25896              (Spec_Id      => Spec_Id,
25897               Spec_Inputs  => Spec_Inputs,
25898               Spec_Outputs => Spec_Outputs,
25899               Body_Inputs  => Body_Inputs,
25900               Body_Outputs => Body_Outputs);
25901         end if;
25902
25903         --  Matching is disabled in ASIS because clauses are not normalized as
25904         --  this is a tree altering activity similar to expansion.
25905
25906         if ASIS_Mode then
25907            goto Leave;
25908         end if;
25909
25910         --  Multiple dependency clauses appear as component associations of an
25911         --  aggregate. Note that the clauses are copied because the algorithm
25912         --  modifies them and this should not be visible in Depends.
25913
25914         pragma Assert (Nkind (Deps) = N_Aggregate);
25915         Dependencies := New_Copy_List_Tree (Component_Associations (Deps));
25916         Normalize_Clauses (Dependencies);
25917
25918         --  Gather all states which appear in Depends
25919
25920         States := Collect_States (Dependencies);
25921
25922         Refs := Expression (Get_Argument (N, Spec_Id));
25923
25924         if Nkind (Refs) = N_Null then
25925            Refinements := No_List;
25926
25927         --  Multiple dependency clauses appear as component associations of an
25928         --  aggregate. Note that the clauses are copied because the algorithm
25929         --  modifies them and this should not be visible in Refined_Depends.
25930
25931         else pragma Assert (Nkind (Refs) = N_Aggregate);
25932            Refinements := New_Copy_List_Tree (Component_Associations (Refs));
25933            Normalize_Clauses (Refinements);
25934         end if;
25935
25936         --  At this point the clauses of pragmas Depends and Refined_Depends
25937         --  have been normalized into simple dependencies between one output
25938         --  and one input. Examine all clauses of pragma Depends looking for
25939         --  matching clauses in pragma Refined_Depends.
25940
25941         Clause := First (Dependencies);
25942         while Present (Clause) loop
25943            Check_Dependency_Clause
25944              (Spec_Id       => Spec_Id,
25945               Dep_Clause    => Clause,
25946               Dep_States    => States,
25947               Refinements   => Refinements,
25948               Matched_Items => Matched_Items);
25949
25950            Next (Clause);
25951         end loop;
25952
25953         --  Pragma Refined_Depends may contain multiple clarification clauses
25954         --  which indicate that certain constituents do not influence the data
25955         --  flow in any way. Such clauses must be removed as long as the state
25956         --  has been matched, otherwise they will be incorrectly flagged as
25957         --  unmatched.
25958
25959         --    Refined_State   => (State => (Constit_1, Constit_2))
25960         --    Depends         => (Output => State)
25961         --    Refined_Depends => ((Output => Constit_1),  --  State matched
25962         --                        (null => Constit_2))    --  must be removed
25963
25964         Remove_Extra_Clauses (Refinements, Matched_Items);
25965
25966         if Serious_Errors_Detected = Errors then
25967            Report_Extra_Clauses (Spec_Id, Refinements);
25968         end if;
25969      end if;
25970
25971      <<Leave>>
25972      Set_Is_Analyzed_Pragma (N);
25973   end Analyze_Refined_Depends_In_Decl_Part;
25974
25975   -----------------------------------------
25976   -- Analyze_Refined_Global_In_Decl_Part --
25977   -----------------------------------------
25978
25979   procedure Analyze_Refined_Global_In_Decl_Part (N : Node_Id) is
25980      Global : Node_Id;
25981      --  The corresponding Global pragma
25982
25983      Has_In_State       : Boolean := False;
25984      Has_In_Out_State   : Boolean := False;
25985      Has_Out_State      : Boolean := False;
25986      Has_Proof_In_State : Boolean := False;
25987      --  These flags are set when the corresponding Global pragma has a state
25988      --  of mode Input, In_Out, Output or Proof_In respectively with a visible
25989      --  refinement.
25990
25991      Has_Null_State : Boolean := False;
25992      --  This flag is set when the corresponding Global pragma has at least
25993      --  one state with a null refinement.
25994
25995      In_Constits       : Elist_Id := No_Elist;
25996      In_Out_Constits   : Elist_Id := No_Elist;
25997      Out_Constits      : Elist_Id := No_Elist;
25998      Proof_In_Constits : Elist_Id := No_Elist;
25999      --  These lists contain the entities of all Input, In_Out, Output and
26000      --  Proof_In constituents that appear in Refined_Global and participate
26001      --  in state refinement.
26002
26003      In_Items       : Elist_Id := No_Elist;
26004      In_Out_Items   : Elist_Id := No_Elist;
26005      Out_Items      : Elist_Id := No_Elist;
26006      Proof_In_Items : Elist_Id := No_Elist;
26007      --  These lists contain the entities of all Input, In_Out, Output and
26008      --  Proof_In items defined in the corresponding Global pragma.
26009
26010      Repeat_Items : Elist_Id := No_Elist;
26011      --  A list of all global items without full visible refinement found
26012      --  in pragma Global. These states should be repeated in the global
26013      --  refinement (SPARK RM 7.2.4(3c)) unless they have a partial visible
26014      --  refinement, in which case they may be repeated (SPARK RM 7.2.4(3d)).
26015
26016      Spec_Id : Entity_Id;
26017      --  The entity of the subprogram subject to pragma Refined_Global
26018
26019      States : Elist_Id := No_Elist;
26020      --  A list of all states with full or partial visible refinement found in
26021      --  pragma Global.
26022
26023      procedure Check_In_Out_States;
26024      --  Determine whether the corresponding Global pragma mentions In_Out
26025      --  states with visible refinement and if so, ensure that one of the
26026      --  following completions apply to the constituents of the state:
26027      --    1) there is at least one constituent of mode In_Out
26028      --    2) there is at least one Input and one Output constituent
26029      --    3) not all constituents are present and one of them is of mode
26030      --       Output.
26031      --  This routine may remove elements from In_Constits, In_Out_Constits,
26032      --  Out_Constits and Proof_In_Constits.
26033
26034      procedure Check_Input_States;
26035      --  Determine whether the corresponding Global pragma mentions Input
26036      --  states with visible refinement and if so, ensure that at least one of
26037      --  its constituents appears as an Input item in Refined_Global.
26038      --  This routine may remove elements from In_Constits, In_Out_Constits,
26039      --  Out_Constits and Proof_In_Constits.
26040
26041      procedure Check_Output_States;
26042      --  Determine whether the corresponding Global pragma mentions Output
26043      --  states with visible refinement and if so, ensure that all of its
26044      --  constituents appear as Output items in Refined_Global.
26045      --  This routine may remove elements from In_Constits, In_Out_Constits,
26046      --  Out_Constits and Proof_In_Constits.
26047
26048      procedure Check_Proof_In_States;
26049      --  Determine whether the corresponding Global pragma mentions Proof_In
26050      --  states with visible refinement and if so, ensure that at least one of
26051      --  its constituents appears as a Proof_In item in Refined_Global.
26052      --  This routine may remove elements from In_Constits, In_Out_Constits,
26053      --  Out_Constits and Proof_In_Constits.
26054
26055      procedure Check_Refined_Global_List
26056        (List        : Node_Id;
26057         Global_Mode : Name_Id := Name_Input);
26058      --  Verify the legality of a single global list declaration. Global_Mode
26059      --  denotes the current mode in effect.
26060
26061      procedure Collect_Global_Items
26062        (List : Node_Id;
26063         Mode : Name_Id := Name_Input);
26064      --  Gather all Input, In_Out, Output and Proof_In items from node List
26065      --  and separate them in lists In_Items, In_Out_Items, Out_Items and
26066      --  Proof_In_Items. Flags Has_In_State, Has_In_Out_State, Has_Out_State
26067      --  and Has_Proof_In_State are set when there is at least one abstract
26068      --  state with full or partial visible refinement available in the
26069      --  corresponding mode. Flag Has_Null_State is set when at least state
26070      --  has a null refinement. Mode denotes the current global mode in
26071      --  effect.
26072
26073      function Present_Then_Remove
26074        (List : Elist_Id;
26075         Item : Entity_Id) return Boolean;
26076      --  Search List for a particular entity Item. If Item has been found,
26077      --  remove it from List. This routine is used to strip lists In_Constits,
26078      --  In_Out_Constits and Out_Constits of valid constituents.
26079
26080      procedure Present_Then_Remove (List : Elist_Id; Item : Entity_Id);
26081      --  Same as function Present_Then_Remove, but do not report the presence
26082      --  of Item in List.
26083
26084      procedure Report_Extra_Constituents;
26085      --  Emit an error for each constituent found in lists In_Constits,
26086      --  In_Out_Constits and Out_Constits.
26087
26088      procedure Report_Missing_Items;
26089      --  Emit an error for each global item not repeated found in list
26090      --  Repeat_Items.
26091
26092      -------------------------
26093      -- Check_In_Out_States --
26094      -------------------------
26095
26096      procedure Check_In_Out_States is
26097         procedure Check_Constituent_Usage (State_Id : Entity_Id);
26098         --  Determine whether one of the following coverage scenarios is in
26099         --  effect:
26100         --    1) there is at least one constituent of mode In_Out or Output
26101         --    2) there is at least one pair of constituents with modes Input
26102         --       and Output, or Proof_In and Output.
26103         --    3) there is at least one constituent of mode Output and not all
26104         --       constituents are present.
26105         --  If this is not the case, emit an error (SPARK RM 7.2.4(5)).
26106
26107         -----------------------------
26108         -- Check_Constituent_Usage --
26109         -----------------------------
26110
26111         procedure Check_Constituent_Usage (State_Id : Entity_Id) is
26112            Constits      : constant Elist_Id :=
26113                              Partial_Refinement_Constituents (State_Id);
26114            Constit_Elmt  : Elmt_Id;
26115            Constit_Id    : Entity_Id;
26116            Has_Missing   : Boolean := False;
26117            In_Out_Seen   : Boolean := False;
26118            Input_Seen    : Boolean := False;
26119            Output_Seen   : Boolean := False;
26120            Proof_In_Seen : Boolean := False;
26121
26122         begin
26123            --  Process all the constituents of the state and note their modes
26124            --  within the global refinement.
26125
26126            if Present (Constits) then
26127               Constit_Elmt := First_Elmt (Constits);
26128               while Present (Constit_Elmt) loop
26129                  Constit_Id := Node (Constit_Elmt);
26130
26131                  if Present_Then_Remove (In_Constits, Constit_Id) then
26132                     Input_Seen := True;
26133
26134                  elsif Present_Then_Remove (In_Out_Constits, Constit_Id) then
26135                     In_Out_Seen := True;
26136
26137                  elsif Present_Then_Remove (Out_Constits, Constit_Id) then
26138                     Output_Seen := True;
26139
26140                  elsif Present_Then_Remove (Proof_In_Constits, Constit_Id)
26141                  then
26142                     Proof_In_Seen := True;
26143
26144                  else
26145                     Has_Missing := True;
26146                  end if;
26147
26148                  Next_Elmt (Constit_Elmt);
26149               end loop;
26150            end if;
26151
26152            --  An In_Out constituent is a valid completion
26153
26154            if In_Out_Seen then
26155               null;
26156
26157            --  A pair of one Input/Proof_In and one Output constituent is a
26158            --  valid completion.
26159
26160            elsif (Input_Seen or Proof_In_Seen) and Output_Seen then
26161               null;
26162
26163            elsif Output_Seen then
26164
26165               --  A single Output constituent is a valid completion only when
26166               --  some of the other constituents are missing.
26167
26168               if Has_Missing then
26169                  null;
26170
26171               --  Otherwise all constituents are of mode Output
26172
26173               else
26174                  SPARK_Msg_NE
26175                    ("global refinement of state & must include at least one "
26176                     & "constituent of mode `In_Out`, `Input`, or `Proof_In`",
26177                     N, State_Id);
26178               end if;
26179
26180            --  The state lacks a completion. When full refinement is visible,
26181            --  always emit an error (SPARK RM 7.2.4(3a)). When only partial
26182            --  refinement is visible, emit an error if the abstract state
26183            --  itself is not utilized (SPARK RM 7.2.4(3d)). In the case where
26184            --  both are utilized, Check_State_And_Constituent_Use. will issue
26185            --  the error.
26186
26187            elsif not Input_Seen
26188              and then not In_Out_Seen
26189              and then not Output_Seen
26190              and then not Proof_In_Seen
26191            then
26192               if Has_Visible_Refinement (State_Id)
26193                 or else Contains (Repeat_Items, State_Id)
26194               then
26195                  SPARK_Msg_NE
26196                    ("missing global refinement of state &", N, State_Id);
26197               end if;
26198
26199            --  Otherwise the state has a malformed completion where at least
26200            --  one of the constituents has a different mode.
26201
26202            else
26203               SPARK_Msg_NE
26204                 ("global refinement of state & redefines the mode of its "
26205                  & "constituents", N, State_Id);
26206            end if;
26207         end Check_Constituent_Usage;
26208
26209         --  Local variables
26210
26211         Item_Elmt : Elmt_Id;
26212         Item_Id   : Entity_Id;
26213
26214      --  Start of processing for Check_In_Out_States
26215
26216      begin
26217         --  Do not perform this check in an instance because it was already
26218         --  performed successfully in the generic template.
26219
26220         if Is_Generic_Instance (Spec_Id) then
26221            null;
26222
26223         --  Inspect the In_Out items of the corresponding Global pragma
26224         --  looking for a state with a visible refinement.
26225
26226         elsif Has_In_Out_State and then Present (In_Out_Items) then
26227            Item_Elmt := First_Elmt (In_Out_Items);
26228            while Present (Item_Elmt) loop
26229               Item_Id := Node (Item_Elmt);
26230
26231               --  Ensure that one of the three coverage variants is satisfied
26232
26233               if Ekind (Item_Id) = E_Abstract_State
26234                 and then Has_Non_Null_Visible_Refinement (Item_Id)
26235               then
26236                  Check_Constituent_Usage (Item_Id);
26237               end if;
26238
26239               Next_Elmt (Item_Elmt);
26240            end loop;
26241         end if;
26242      end Check_In_Out_States;
26243
26244      ------------------------
26245      -- Check_Input_States --
26246      ------------------------
26247
26248      procedure Check_Input_States is
26249         procedure Check_Constituent_Usage (State_Id : Entity_Id);
26250         --  Determine whether at least one constituent of state State_Id with
26251         --  full or partial visible refinement is used and has mode Input.
26252         --  Ensure that the remaining constituents do not have In_Out or
26253         --  Output modes. Emit an error if this is not the case
26254         --  (SPARK RM 7.2.4(5)).
26255
26256         -----------------------------
26257         -- Check_Constituent_Usage --
26258         -----------------------------
26259
26260         procedure Check_Constituent_Usage (State_Id : Entity_Id) is
26261            Constits     : constant Elist_Id :=
26262                             Partial_Refinement_Constituents (State_Id);
26263            Constit_Elmt : Elmt_Id;
26264            Constit_Id   : Entity_Id;
26265            In_Seen      : Boolean := False;
26266
26267         begin
26268            if Present (Constits) then
26269               Constit_Elmt := First_Elmt (Constits);
26270               while Present (Constit_Elmt) loop
26271                  Constit_Id := Node (Constit_Elmt);
26272
26273                  --  At least one of the constituents appears as an Input
26274
26275                  if Present_Then_Remove (In_Constits, Constit_Id) then
26276                     In_Seen := True;
26277
26278                  --  A Proof_In constituent can refine an Input state as long
26279                  --  as there is at least one Input constituent present.
26280
26281                  elsif Present_Then_Remove (Proof_In_Constits, Constit_Id)
26282                  then
26283                     null;
26284
26285                  --  The constituent appears in the global refinement, but has
26286                  --  mode In_Out or Output (SPARK RM 7.2.4(5)).
26287
26288                  elsif Present_Then_Remove (In_Out_Constits, Constit_Id)
26289                    or else Present_Then_Remove (Out_Constits, Constit_Id)
26290                  then
26291                     Error_Msg_Name_1 := Chars (State_Id);
26292                     SPARK_Msg_NE
26293                       ("constituent & of state % must have mode `Input` in "
26294                        & "global refinement", N, Constit_Id);
26295                  end if;
26296
26297                  Next_Elmt (Constit_Elmt);
26298               end loop;
26299            end if;
26300
26301            --  Not one of the constituents appeared as Input. Always emit an
26302            --  error when the full refinement is visible (SPARK RM 7.2.4(3a)).
26303            --  When only partial refinement is visible, emit an error if the
26304            --  abstract state itself is not utilized (SPARK RM 7.2.4(3d)). In
26305            --  the case where both are utilized, an error will be issued in
26306            --  Check_State_And_Constituent_Use.
26307
26308            if not In_Seen
26309              and then (Has_Visible_Refinement (State_Id)
26310                         or else Contains (Repeat_Items, State_Id))
26311            then
26312               SPARK_Msg_NE
26313                 ("global refinement of state & must include at least one "
26314                  & "constituent of mode `Input`", N, State_Id);
26315            end if;
26316         end Check_Constituent_Usage;
26317
26318         --  Local variables
26319
26320         Item_Elmt : Elmt_Id;
26321         Item_Id   : Entity_Id;
26322
26323      --  Start of processing for Check_Input_States
26324
26325      begin
26326         --  Do not perform this check in an instance because it was already
26327         --  performed successfully in the generic template.
26328
26329         if Is_Generic_Instance (Spec_Id) then
26330            null;
26331
26332         --  Inspect the Input items of the corresponding Global pragma looking
26333         --  for a state with a visible refinement.
26334
26335         elsif Has_In_State and then Present (In_Items) then
26336            Item_Elmt := First_Elmt (In_Items);
26337            while Present (Item_Elmt) loop
26338               Item_Id := Node (Item_Elmt);
26339
26340               --  When full refinement is visible, ensure that at least one of
26341               --  the constituents is utilized and is of mode Input. When only
26342               --  partial refinement is visible, ensure that either one of
26343               --  the constituents is utilized and is of mode Input, or the
26344               --  abstract state is repeated and no constituent is utilized.
26345
26346               if Ekind (Item_Id) = E_Abstract_State
26347                 and then Has_Non_Null_Visible_Refinement (Item_Id)
26348               then
26349                  Check_Constituent_Usage (Item_Id);
26350               end if;
26351
26352               Next_Elmt (Item_Elmt);
26353            end loop;
26354         end if;
26355      end Check_Input_States;
26356
26357      -------------------------
26358      -- Check_Output_States --
26359      -------------------------
26360
26361      procedure Check_Output_States is
26362         procedure Check_Constituent_Usage (State_Id : Entity_Id);
26363         --  Determine whether all constituents of state State_Id with full
26364         --  visible refinement are used and have mode Output. Emit an error
26365         --  if this is not the case (SPARK RM 7.2.4(5)).
26366
26367         -----------------------------
26368         -- Check_Constituent_Usage --
26369         -----------------------------
26370
26371         procedure Check_Constituent_Usage (State_Id : Entity_Id) is
26372            Constits     : constant Elist_Id :=
26373                             Partial_Refinement_Constituents (State_Id);
26374            Only_Partial : constant Boolean :=
26375                             not Has_Visible_Refinement (State_Id);
26376            Constit_Elmt : Elmt_Id;
26377            Constit_Id   : Entity_Id;
26378            Posted       : Boolean := False;
26379
26380         begin
26381            if Present (Constits) then
26382               Constit_Elmt := First_Elmt (Constits);
26383               while Present (Constit_Elmt) loop
26384                  Constit_Id := Node (Constit_Elmt);
26385
26386                  --  Issue an error when a constituent of State_Id is utilized
26387                  --  and State_Id has only partial visible refinement
26388                  --  (SPARK RM 7.2.4(3d)).
26389
26390                  if Only_Partial then
26391                     if Present_Then_Remove (Out_Constits, Constit_Id)
26392                       or else Present_Then_Remove (In_Constits, Constit_Id)
26393                       or else
26394                         Present_Then_Remove (In_Out_Constits, Constit_Id)
26395                       or else
26396                         Present_Then_Remove (Proof_In_Constits, Constit_Id)
26397                     then
26398                        Error_Msg_Name_1 := Chars (State_Id);
26399                        SPARK_Msg_NE
26400                          ("constituent & of state % cannot be used in global "
26401                           & "refinement", N, Constit_Id);
26402                        Error_Msg_Name_1 := Chars (State_Id);
26403                        SPARK_Msg_N ("\use state % instead", N);
26404                     end if;
26405
26406                  elsif Present_Then_Remove (Out_Constits, Constit_Id) then
26407                     null;
26408
26409                  --  The constituent appears in the global refinement, but has
26410                  --  mode Input, In_Out or Proof_In (SPARK RM 7.2.4(5)).
26411
26412                  elsif Present_Then_Remove (In_Constits, Constit_Id)
26413                    or else Present_Then_Remove (In_Out_Constits, Constit_Id)
26414                    or else Present_Then_Remove (Proof_In_Constits, Constit_Id)
26415                  then
26416                     Error_Msg_Name_1 := Chars (State_Id);
26417                     SPARK_Msg_NE
26418                       ("constituent & of state % must have mode `Output` in "
26419                        & "global refinement", N, Constit_Id);
26420
26421                  --  The constituent is altogether missing (SPARK RM 7.2.5(3))
26422
26423                  else
26424                     if not Posted then
26425                        Posted := True;
26426                        SPARK_Msg_NE
26427                          ("`Output` state & must be replaced by all its "
26428                           & "constituents in global refinement", N, State_Id);
26429                     end if;
26430
26431                     SPARK_Msg_NE
26432                       ("\constituent & is missing in output list",
26433                        N, Constit_Id);
26434                  end if;
26435
26436                  Next_Elmt (Constit_Elmt);
26437               end loop;
26438            end if;
26439         end Check_Constituent_Usage;
26440
26441         --  Local variables
26442
26443         Item_Elmt : Elmt_Id;
26444         Item_Id   : Entity_Id;
26445
26446      --  Start of processing for Check_Output_States
26447
26448      begin
26449         --  Do not perform this check in an instance because it was already
26450         --  performed successfully in the generic template.
26451
26452         if Is_Generic_Instance (Spec_Id) then
26453            null;
26454
26455         --  Inspect the Output items of the corresponding Global pragma
26456         --  looking for a state with a visible refinement.
26457
26458         elsif Has_Out_State and then Present (Out_Items) then
26459            Item_Elmt := First_Elmt (Out_Items);
26460            while Present (Item_Elmt) loop
26461               Item_Id := Node (Item_Elmt);
26462
26463               --  When full refinement is visible, ensure that all of the
26464               --  constituents are utilized and they have mode Output. When
26465               --  only partial refinement is visible, ensure that no
26466               --  constituent is utilized.
26467
26468               if Ekind (Item_Id) = E_Abstract_State
26469                 and then Has_Non_Null_Visible_Refinement (Item_Id)
26470               then
26471                  Check_Constituent_Usage (Item_Id);
26472               end if;
26473
26474               Next_Elmt (Item_Elmt);
26475            end loop;
26476         end if;
26477      end Check_Output_States;
26478
26479      ---------------------------
26480      -- Check_Proof_In_States --
26481      ---------------------------
26482
26483      procedure Check_Proof_In_States is
26484         procedure Check_Constituent_Usage (State_Id : Entity_Id);
26485         --  Determine whether at least one constituent of state State_Id with
26486         --  full or partial visible refinement is used and has mode Proof_In.
26487         --  Ensure that the remaining constituents do not have Input, In_Out,
26488         --  or Output modes. Emit an error if this is not the case
26489         --  (SPARK RM 7.2.4(5)).
26490
26491         -----------------------------
26492         -- Check_Constituent_Usage --
26493         -----------------------------
26494
26495         procedure Check_Constituent_Usage (State_Id : Entity_Id) is
26496            Constits      : constant Elist_Id :=
26497                              Partial_Refinement_Constituents (State_Id);
26498            Constit_Elmt  : Elmt_Id;
26499            Constit_Id    : Entity_Id;
26500            Proof_In_Seen : Boolean := False;
26501
26502         begin
26503            if Present (Constits) then
26504               Constit_Elmt := First_Elmt (Constits);
26505               while Present (Constit_Elmt) loop
26506                  Constit_Id := Node (Constit_Elmt);
26507
26508                  --  At least one of the constituents appears as Proof_In
26509
26510                  if Present_Then_Remove (Proof_In_Constits, Constit_Id) then
26511                     Proof_In_Seen := True;
26512
26513                  --  The constituent appears in the global refinement, but has
26514                  --  mode Input, In_Out or Output (SPARK RM 7.2.4(5)).
26515
26516                  elsif Present_Then_Remove (In_Constits, Constit_Id)
26517                    or else Present_Then_Remove (In_Out_Constits, Constit_Id)
26518                    or else Present_Then_Remove (Out_Constits, Constit_Id)
26519                  then
26520                     Error_Msg_Name_1 := Chars (State_Id);
26521                     SPARK_Msg_NE
26522                       ("constituent & of state % must have mode `Proof_In` "
26523                        & "in global refinement", N, Constit_Id);
26524                  end if;
26525
26526                  Next_Elmt (Constit_Elmt);
26527               end loop;
26528            end if;
26529
26530            --  Not one of the constituents appeared as Proof_In. Always emit
26531            --  an error when full refinement is visible (SPARK RM 7.2.4(3a)).
26532            --  When only partial refinement is visible, emit an error if the
26533            --  abstract state itself is not utilized (SPARK RM 7.2.4(3d)). In
26534            --  the case where both are utilized, an error will be issued by
26535            --  Check_State_And_Constituent_Use.
26536
26537            if not Proof_In_Seen
26538              and then (Has_Visible_Refinement (State_Id)
26539                         or else Contains (Repeat_Items, State_Id))
26540            then
26541               SPARK_Msg_NE
26542                 ("global refinement of state & must include at least one "
26543                  & "constituent of mode `Proof_In`", N, State_Id);
26544            end if;
26545         end Check_Constituent_Usage;
26546
26547         --  Local variables
26548
26549         Item_Elmt : Elmt_Id;
26550         Item_Id   : Entity_Id;
26551
26552      --  Start of processing for Check_Proof_In_States
26553
26554      begin
26555         --  Do not perform this check in an instance because it was already
26556         --  performed successfully in the generic template.
26557
26558         if Is_Generic_Instance (Spec_Id) then
26559            null;
26560
26561         --  Inspect the Proof_In items of the corresponding Global pragma
26562         --  looking for a state with a visible refinement.
26563
26564         elsif Has_Proof_In_State and then Present (Proof_In_Items) then
26565            Item_Elmt := First_Elmt (Proof_In_Items);
26566            while Present (Item_Elmt) loop
26567               Item_Id := Node (Item_Elmt);
26568
26569               --  Ensure that at least one of the constituents is utilized
26570               --  and is of mode Proof_In. When only partial refinement is
26571               --  visible, ensure that either one of the constituents is
26572               --  utilized and is of mode Proof_In, or the abstract state
26573               --  is repeated and no constituent is utilized.
26574
26575               if Ekind (Item_Id) = E_Abstract_State
26576                 and then Has_Non_Null_Visible_Refinement (Item_Id)
26577               then
26578                  Check_Constituent_Usage (Item_Id);
26579               end if;
26580
26581               Next_Elmt (Item_Elmt);
26582            end loop;
26583         end if;
26584      end Check_Proof_In_States;
26585
26586      -------------------------------
26587      -- Check_Refined_Global_List --
26588      -------------------------------
26589
26590      procedure Check_Refined_Global_List
26591        (List        : Node_Id;
26592         Global_Mode : Name_Id := Name_Input)
26593      is
26594         procedure Check_Refined_Global_Item
26595           (Item        : Node_Id;
26596            Global_Mode : Name_Id);
26597         --  Verify the legality of a single global item declaration. Parameter
26598         --  Global_Mode denotes the current mode in effect.
26599
26600         -------------------------------
26601         -- Check_Refined_Global_Item --
26602         -------------------------------
26603
26604         procedure Check_Refined_Global_Item
26605           (Item        : Node_Id;
26606            Global_Mode : Name_Id)
26607         is
26608            Item_Id : constant Entity_Id := Entity_Of (Item);
26609
26610            procedure Inconsistent_Mode_Error (Expect : Name_Id);
26611            --  Issue a common error message for all mode mismatches. Expect
26612            --  denotes the expected mode.
26613
26614            -----------------------------
26615            -- Inconsistent_Mode_Error --
26616            -----------------------------
26617
26618            procedure Inconsistent_Mode_Error (Expect : Name_Id) is
26619            begin
26620               SPARK_Msg_NE
26621                 ("global item & has inconsistent modes", Item, Item_Id);
26622
26623               Error_Msg_Name_1 := Global_Mode;
26624               Error_Msg_Name_2 := Expect;
26625               SPARK_Msg_N ("\expected mode %, found mode %", Item);
26626            end Inconsistent_Mode_Error;
26627
26628            --  Local variables
26629
26630            Enc_State : Entity_Id := Empty;
26631            --  Encapsulating state for constituent, Empty otherwise
26632
26633         --  Start of processing for Check_Refined_Global_Item
26634
26635         begin
26636            if Ekind_In (Item_Id, E_Abstract_State,
26637                                  E_Constant,
26638                                  E_Variable)
26639            then
26640               Enc_State := Find_Encapsulating_State (States, Item_Id);
26641            end if;
26642
26643            --  When the state or object acts as a constituent of another
26644            --  state with a visible refinement, collect it for the state
26645            --  completeness checks performed later on. Note that the item
26646            --  acts as a constituent only when the encapsulating state is
26647            --  present in pragma Global.
26648
26649            if Present (Enc_State)
26650              and then (Has_Visible_Refinement (Enc_State)
26651                         or else Has_Partial_Visible_Refinement (Enc_State))
26652              and then Contains (States, Enc_State)
26653            then
26654               --  If the state has only partial visible refinement, remove it
26655               --  from the list of items that should be repeated from pragma
26656               --  Global.
26657
26658               if not Has_Visible_Refinement (Enc_State) then
26659                  Present_Then_Remove (Repeat_Items, Enc_State);
26660               end if;
26661
26662               if Global_Mode = Name_Input then
26663                  Append_New_Elmt (Item_Id, In_Constits);
26664
26665               elsif Global_Mode = Name_In_Out then
26666                  Append_New_Elmt (Item_Id, In_Out_Constits);
26667
26668               elsif Global_Mode = Name_Output then
26669                  Append_New_Elmt (Item_Id, Out_Constits);
26670
26671               elsif Global_Mode = Name_Proof_In then
26672                  Append_New_Elmt (Item_Id, Proof_In_Constits);
26673               end if;
26674
26675            --  When not a constituent, ensure that both occurrences of the
26676            --  item in pragmas Global and Refined_Global match. Also remove
26677            --  it when present from the list of items that should be repeated
26678            --  from pragma Global.
26679
26680            else
26681               Present_Then_Remove (Repeat_Items, Item_Id);
26682
26683               if Contains (In_Items, Item_Id) then
26684                  if Global_Mode /= Name_Input then
26685                     Inconsistent_Mode_Error (Name_Input);
26686                  end if;
26687
26688               elsif Contains (In_Out_Items, Item_Id) then
26689                  if Global_Mode /= Name_In_Out then
26690                     Inconsistent_Mode_Error (Name_In_Out);
26691                  end if;
26692
26693               elsif Contains (Out_Items, Item_Id) then
26694                  if Global_Mode /= Name_Output then
26695                     Inconsistent_Mode_Error (Name_Output);
26696                  end if;
26697
26698               elsif Contains (Proof_In_Items, Item_Id) then
26699                  null;
26700
26701               --  The item does not appear in the corresponding Global pragma,
26702               --  it must be an extra (SPARK RM 7.2.4(3)).
26703
26704               else
26705                  SPARK_Msg_NE ("extra global item &", Item, Item_Id);
26706               end if;
26707            end if;
26708         end Check_Refined_Global_Item;
26709
26710         --  Local variables
26711
26712         Item : Node_Id;
26713
26714      --  Start of processing for Check_Refined_Global_List
26715
26716      begin
26717         --  Do not perform this check in an instance because it was already
26718         --  performed successfully in the generic template.
26719
26720         if Is_Generic_Instance (Spec_Id) then
26721            null;
26722
26723         elsif Nkind (List) = N_Null then
26724            null;
26725
26726         --  Single global item declaration
26727
26728         elsif Nkind_In (List, N_Expanded_Name,
26729                               N_Identifier,
26730                               N_Selected_Component)
26731         then
26732            Check_Refined_Global_Item (List, Global_Mode);
26733
26734         --  Simple global list or moded global list declaration
26735
26736         elsif Nkind (List) = N_Aggregate then
26737
26738            --  The declaration of a simple global list appear as a collection
26739            --  of expressions.
26740
26741            if Present (Expressions (List)) then
26742               Item := First (Expressions (List));
26743               while Present (Item) loop
26744                  Check_Refined_Global_Item (Item, Global_Mode);
26745                  Next (Item);
26746               end loop;
26747
26748            --  The declaration of a moded global list appears as a collection
26749            --  of component associations where individual choices denote
26750            --  modes.
26751
26752            elsif Present (Component_Associations (List)) then
26753               Item := First (Component_Associations (List));
26754               while Present (Item) loop
26755                  Check_Refined_Global_List
26756                    (List        => Expression (Item),
26757                     Global_Mode => Chars (First (Choices (Item))));
26758
26759                  Next (Item);
26760               end loop;
26761
26762            --  Invalid tree
26763
26764            else
26765               raise Program_Error;
26766            end if;
26767
26768         --  Invalid list
26769
26770         else
26771            raise Program_Error;
26772         end if;
26773      end Check_Refined_Global_List;
26774
26775      --------------------------
26776      -- Collect_Global_Items --
26777      --------------------------
26778
26779      procedure Collect_Global_Items
26780        (List : Node_Id;
26781         Mode : Name_Id := Name_Input)
26782      is
26783         procedure Collect_Global_Item
26784           (Item      : Node_Id;
26785            Item_Mode : Name_Id);
26786         --  Add a single item to the appropriate list. Item_Mode denotes the
26787         --  current mode in effect.
26788
26789         -------------------------
26790         -- Collect_Global_Item --
26791         -------------------------
26792
26793         procedure Collect_Global_Item
26794           (Item      : Node_Id;
26795            Item_Mode : Name_Id)
26796         is
26797            Item_Id : constant Entity_Id := Available_View (Entity_Of (Item));
26798            --  The above handles abstract views of variables and states built
26799            --  for limited with clauses.
26800
26801         begin
26802            --  Signal that the global list contains at least one abstract
26803            --  state with a visible refinement. Note that the refinement may
26804            --  be null in which case there are no constituents.
26805
26806            if Ekind (Item_Id) = E_Abstract_State then
26807               if Has_Null_Visible_Refinement (Item_Id) then
26808                  Has_Null_State := True;
26809
26810               elsif Has_Non_Null_Visible_Refinement (Item_Id) then
26811                  Append_New_Elmt (Item_Id, States);
26812
26813                  if Item_Mode = Name_Input then
26814                     Has_In_State := True;
26815                  elsif Item_Mode = Name_In_Out then
26816                     Has_In_Out_State := True;
26817                  elsif Item_Mode = Name_Output then
26818                     Has_Out_State := True;
26819                  elsif Item_Mode = Name_Proof_In then
26820                     Has_Proof_In_State := True;
26821                  end if;
26822               end if;
26823            end if;
26824
26825            --  Record global items without full visible refinement found in
26826            --  pragma Global which should be repeated in the global refinement
26827            --  (SPARK RM 7.2.4(3c), SPARK RM 7.2.4(3d)).
26828
26829            if Ekind (Item_Id) /= E_Abstract_State
26830              or else not Has_Visible_Refinement (Item_Id)
26831            then
26832               Append_New_Elmt (Item_Id, Repeat_Items);
26833            end if;
26834
26835            --  Add the item to the proper list
26836
26837            if Item_Mode = Name_Input then
26838               Append_New_Elmt (Item_Id, In_Items);
26839            elsif Item_Mode = Name_In_Out then
26840               Append_New_Elmt (Item_Id, In_Out_Items);
26841            elsif Item_Mode = Name_Output then
26842               Append_New_Elmt (Item_Id, Out_Items);
26843            elsif Item_Mode = Name_Proof_In then
26844               Append_New_Elmt (Item_Id, Proof_In_Items);
26845            end if;
26846         end Collect_Global_Item;
26847
26848         --  Local variables
26849
26850         Item : Node_Id;
26851
26852      --  Start of processing for Collect_Global_Items
26853
26854      begin
26855         if Nkind (List) = N_Null then
26856            null;
26857
26858         --  Single global item declaration
26859
26860         elsif Nkind_In (List, N_Expanded_Name,
26861                               N_Identifier,
26862                               N_Selected_Component)
26863         then
26864            Collect_Global_Item (List, Mode);
26865
26866         --  Single global list or moded global list declaration
26867
26868         elsif Nkind (List) = N_Aggregate then
26869
26870            --  The declaration of a simple global list appear as a collection
26871            --  of expressions.
26872
26873            if Present (Expressions (List)) then
26874               Item := First (Expressions (List));
26875               while Present (Item) loop
26876                  Collect_Global_Item (Item, Mode);
26877                  Next (Item);
26878               end loop;
26879
26880            --  The declaration of a moded global list appears as a collection
26881            --  of component associations where individual choices denote mode.
26882
26883            elsif Present (Component_Associations (List)) then
26884               Item := First (Component_Associations (List));
26885               while Present (Item) loop
26886                  Collect_Global_Items
26887                    (List => Expression (Item),
26888                     Mode => Chars (First (Choices (Item))));
26889
26890                  Next (Item);
26891               end loop;
26892
26893            --  Invalid tree
26894
26895            else
26896               raise Program_Error;
26897            end if;
26898
26899         --  To accommodate partial decoration of disabled SPARK features, this
26900         --  routine may be called with illegal input. If this is the case, do
26901         --  not raise Program_Error.
26902
26903         else
26904            null;
26905         end if;
26906      end Collect_Global_Items;
26907
26908      -------------------------
26909      -- Present_Then_Remove --
26910      -------------------------
26911
26912      function Present_Then_Remove
26913        (List : Elist_Id;
26914         Item : Entity_Id) return Boolean
26915      is
26916         Elmt : Elmt_Id;
26917
26918      begin
26919         if Present (List) then
26920            Elmt := First_Elmt (List);
26921            while Present (Elmt) loop
26922               if Node (Elmt) = Item then
26923                  Remove_Elmt (List, Elmt);
26924                  return True;
26925               end if;
26926
26927               Next_Elmt (Elmt);
26928            end loop;
26929         end if;
26930
26931         return False;
26932      end Present_Then_Remove;
26933
26934      procedure Present_Then_Remove (List : Elist_Id; Item : Entity_Id) is
26935         Ignore : Boolean;
26936      begin
26937         Ignore := Present_Then_Remove (List, Item);
26938      end Present_Then_Remove;
26939
26940      -------------------------------
26941      -- Report_Extra_Constituents --
26942      -------------------------------
26943
26944      procedure Report_Extra_Constituents is
26945         procedure Report_Extra_Constituents_In_List (List : Elist_Id);
26946         --  Emit an error for every element of List
26947
26948         ---------------------------------------
26949         -- Report_Extra_Constituents_In_List --
26950         ---------------------------------------
26951
26952         procedure Report_Extra_Constituents_In_List (List : Elist_Id) is
26953            Constit_Elmt : Elmt_Id;
26954
26955         begin
26956            if Present (List) then
26957               Constit_Elmt := First_Elmt (List);
26958               while Present (Constit_Elmt) loop
26959                  SPARK_Msg_NE ("extra constituent &", N, Node (Constit_Elmt));
26960                  Next_Elmt (Constit_Elmt);
26961               end loop;
26962            end if;
26963         end Report_Extra_Constituents_In_List;
26964
26965      --  Start of processing for Report_Extra_Constituents
26966
26967      begin
26968         --  Do not perform this check in an instance because it was already
26969         --  performed successfully in the generic template.
26970
26971         if Is_Generic_Instance (Spec_Id) then
26972            null;
26973
26974         else
26975            Report_Extra_Constituents_In_List (In_Constits);
26976            Report_Extra_Constituents_In_List (In_Out_Constits);
26977            Report_Extra_Constituents_In_List (Out_Constits);
26978            Report_Extra_Constituents_In_List (Proof_In_Constits);
26979         end if;
26980      end Report_Extra_Constituents;
26981
26982      --------------------------
26983      -- Report_Missing_Items --
26984      --------------------------
26985
26986      procedure Report_Missing_Items is
26987         Item_Elmt : Elmt_Id;
26988         Item_Id   : Entity_Id;
26989
26990      begin
26991         --  Do not perform this check in an instance because it was already
26992         --  performed successfully in the generic template.
26993
26994         if Is_Generic_Instance (Spec_Id) then
26995            null;
26996
26997         else
26998            if Present (Repeat_Items) then
26999               Item_Elmt := First_Elmt (Repeat_Items);
27000               while Present (Item_Elmt) loop
27001                  Item_Id := Node (Item_Elmt);
27002                  SPARK_Msg_NE ("missing global item &", N, Item_Id);
27003                  Next_Elmt (Item_Elmt);
27004               end loop;
27005            end if;
27006         end if;
27007      end Report_Missing_Items;
27008
27009      --  Local variables
27010
27011      Body_Decl  : constant Node_Id := Find_Related_Declaration_Or_Body (N);
27012      Errors     : constant Nat     := Serious_Errors_Detected;
27013      Items      : Node_Id;
27014      No_Constit : Boolean;
27015
27016   --  Start of processing for Analyze_Refined_Global_In_Decl_Part
27017
27018   begin
27019      --  Do not analyze the pragma multiple times
27020
27021      if Is_Analyzed_Pragma (N) then
27022         return;
27023      end if;
27024
27025      Spec_Id := Unique_Defining_Entity (Body_Decl);
27026
27027      --  Use the anonymous object as the proper spec when Refined_Global
27028      --  applies to the body of a single task type. The object carries the
27029      --  proper Chars as well as all non-refined versions of pragmas.
27030
27031      if Is_Single_Concurrent_Type (Spec_Id) then
27032         Spec_Id := Anonymous_Object (Spec_Id);
27033      end if;
27034
27035      Global := Get_Pragma (Spec_Id, Pragma_Global);
27036      Items  := Expression (Get_Argument (N, Spec_Id));
27037
27038      --  The subprogram declaration lacks pragma Global. This renders
27039      --  Refined_Global useless as there is nothing to refine.
27040
27041      if No (Global) then
27042         SPARK_Msg_NE
27043           (Fix_Msg (Spec_Id, "useless refinement, declaration of subprogram "
27044            & "& lacks aspect or pragma Global"), N, Spec_Id);
27045         goto Leave;
27046      end if;
27047
27048      --  Extract all relevant items from the corresponding Global pragma
27049
27050      Collect_Global_Items (Expression (Get_Argument (Global, Spec_Id)));
27051
27052      --  Package and subprogram bodies are instantiated individually in
27053      --  a separate compiler pass. Due to this mode of instantiation, the
27054      --  refinement of a state may no longer be visible when a subprogram
27055      --  body contract is instantiated. Since the generic template is legal,
27056      --  do not perform this check in the instance to circumvent this oddity.
27057
27058      if Is_Generic_Instance (Spec_Id) then
27059         null;
27060
27061      --  Non-instance case
27062
27063      else
27064         --  The corresponding Global pragma must mention at least one
27065         --  state with a visible refinement at the point Refined_Global
27066         --  is processed. States with null refinements need Refined_Global
27067         --  pragma (SPARK RM 7.2.4(2)).
27068
27069         if not Has_In_State
27070           and then not Has_In_Out_State
27071           and then not Has_Out_State
27072           and then not Has_Proof_In_State
27073           and then not Has_Null_State
27074         then
27075            SPARK_Msg_NE
27076              (Fix_Msg (Spec_Id, "useless refinement, subprogram & does not "
27077               & "depend on abstract state with visible refinement"),
27078               N, Spec_Id);
27079            goto Leave;
27080
27081         --  The global refinement of inputs and outputs cannot be null when
27082         --  the corresponding Global pragma contains at least one item except
27083         --  in the case where we have states with null refinements.
27084
27085         elsif Nkind (Items) = N_Null
27086           and then
27087             (Present (In_Items)
27088               or else Present (In_Out_Items)
27089               or else Present (Out_Items)
27090               or else Present (Proof_In_Items))
27091           and then not Has_Null_State
27092         then
27093            SPARK_Msg_NE
27094              (Fix_Msg (Spec_Id, "refinement cannot be null, subprogram & has "
27095               & "global items"), N, Spec_Id);
27096            goto Leave;
27097         end if;
27098      end if;
27099
27100      --  Analyze Refined_Global as if it behaved as a regular pragma Global.
27101      --  This ensures that the categorization of all refined global items is
27102      --  consistent with their role.
27103
27104      Analyze_Global_In_Decl_Part (N);
27105
27106      --  Perform all refinement checks with respect to completeness and mode
27107      --  matching.
27108
27109      if Serious_Errors_Detected = Errors then
27110         Check_Refined_Global_List (Items);
27111      end if;
27112
27113      --  Store the information that no constituent is used in the global
27114      --  refinement, prior to calling checking procedures which remove items
27115      --  from the list of constituents.
27116
27117      No_Constit :=
27118        No (In_Constits)
27119          and then No (In_Out_Constits)
27120          and then No (Out_Constits)
27121          and then No (Proof_In_Constits);
27122
27123      --  For Input states with visible refinement, at least one constituent
27124      --  must be used as an Input in the global refinement.
27125
27126      if Serious_Errors_Detected = Errors then
27127         Check_Input_States;
27128      end if;
27129
27130      --  Verify all possible completion variants for In_Out states with
27131      --  visible refinement.
27132
27133      if Serious_Errors_Detected = Errors then
27134         Check_In_Out_States;
27135      end if;
27136
27137      --  For Output states with visible refinement, all constituents must be
27138      --  used as Outputs in the global refinement.
27139
27140      if Serious_Errors_Detected = Errors then
27141         Check_Output_States;
27142      end if;
27143
27144      --  For Proof_In states with visible refinement, at least one constituent
27145      --  must be used as Proof_In in the global refinement.
27146
27147      if Serious_Errors_Detected = Errors then
27148         Check_Proof_In_States;
27149      end if;
27150
27151      --  Emit errors for all constituents that belong to other states with
27152      --  visible refinement that do not appear in Global.
27153
27154      if Serious_Errors_Detected = Errors then
27155         Report_Extra_Constituents;
27156      end if;
27157
27158      --  Emit errors for all items in Global that are not repeated in the
27159      --  global refinement and for which there is no full visible refinement
27160      --  and, in the case of states with partial visible refinement, no
27161      --  constituent is mentioned in the global refinement.
27162
27163      if Serious_Errors_Detected = Errors then
27164         Report_Missing_Items;
27165      end if;
27166
27167      --  Emit an error if no constituent is used in the global refinement
27168      --  (SPARK RM 7.2.4(3f)). Emit this error last, in case a more precise
27169      --  one may be issued by the checking procedures. Do not perform this
27170      --  check in an instance because it was already performed successfully
27171      --  in the generic template.
27172
27173      if Serious_Errors_Detected = Errors
27174        and then not Is_Generic_Instance (Spec_Id)
27175        and then not Has_Null_State
27176        and then No_Constit
27177      then
27178         SPARK_Msg_N ("missing refinement", N);
27179      end if;
27180
27181      <<Leave>>
27182      Set_Is_Analyzed_Pragma (N);
27183   end Analyze_Refined_Global_In_Decl_Part;
27184
27185   ----------------------------------------
27186   -- Analyze_Refined_State_In_Decl_Part --
27187   ----------------------------------------
27188
27189   procedure Analyze_Refined_State_In_Decl_Part
27190     (N         : Node_Id;
27191      Freeze_Id : Entity_Id := Empty)
27192   is
27193      Body_Decl : constant Node_Id   := Find_Related_Package_Or_Body (N);
27194      Body_Id   : constant Entity_Id := Defining_Entity (Body_Decl);
27195      Spec_Id   : constant Entity_Id := Corresponding_Spec (Body_Decl);
27196
27197      Available_States : Elist_Id := No_Elist;
27198      --  A list of all abstract states defined in the package declaration that
27199      --  are available for refinement. The list is used to report unrefined
27200      --  states.
27201
27202      Body_States : Elist_Id := No_Elist;
27203      --  A list of all hidden states that appear in the body of the related
27204      --  package. The list is used to report unused hidden states.
27205
27206      Constituents_Seen : Elist_Id := No_Elist;
27207      --  A list that contains all constituents processed so far. The list is
27208      --  used to detect multiple uses of the same constituent.
27209
27210      Freeze_Posted : Boolean := False;
27211      --  A flag that controls the output of a freezing-related error (see use
27212      --  below).
27213
27214      Refined_States_Seen : Elist_Id := No_Elist;
27215      --  A list that contains all refined states processed so far. The list is
27216      --  used to detect duplicate refinements.
27217
27218      procedure Analyze_Refinement_Clause (Clause : Node_Id);
27219      --  Perform full analysis of a single refinement clause
27220
27221      procedure Report_Unrefined_States (States : Elist_Id);
27222      --  Emit errors for all unrefined abstract states found in list States
27223
27224      -------------------------------
27225      -- Analyze_Refinement_Clause --
27226      -------------------------------
27227
27228      procedure Analyze_Refinement_Clause (Clause : Node_Id) is
27229         AR_Constit : Entity_Id := Empty;
27230         AW_Constit : Entity_Id := Empty;
27231         ER_Constit : Entity_Id := Empty;
27232         EW_Constit : Entity_Id := Empty;
27233         --  The entities of external constituents that contain one of the
27234         --  following enabled properties: Async_Readers, Async_Writers,
27235         --  Effective_Reads and Effective_Writes.
27236
27237         External_Constit_Seen : Boolean := False;
27238         --  Flag used to mark when at least one external constituent is part
27239         --  of the state refinement.
27240
27241         Non_Null_Seen : Boolean := False;
27242         Null_Seen     : Boolean := False;
27243         --  Flags used to detect multiple uses of null in a single clause or a
27244         --  mixture of null and non-null constituents.
27245
27246         Part_Of_Constits : Elist_Id := No_Elist;
27247         --  A list of all candidate constituents subject to indicator Part_Of
27248         --  where the encapsulating state is the current state.
27249
27250         State    : Node_Id;
27251         State_Id : Entity_Id;
27252         --  The current state being refined
27253
27254         procedure Analyze_Constituent (Constit : Node_Id);
27255         --  Perform full analysis of a single constituent
27256
27257         procedure Check_External_Property
27258           (Prop_Nam : Name_Id;
27259            Enabled  : Boolean;
27260            Constit  : Entity_Id);
27261         --  Determine whether a property denoted by name Prop_Nam is present
27262         --  in the refined state. Emit an error if this is not the case. Flag
27263         --  Enabled should be set when the property applies to the refined
27264         --  state. Constit denotes the constituent (if any) which introduces
27265         --  the property in the refinement.
27266
27267         procedure Match_State;
27268         --  Determine whether the state being refined appears in list
27269         --  Available_States. Emit an error when attempting to re-refine the
27270         --  state or when the state is not defined in the package declaration,
27271         --  otherwise remove the state from Available_States.
27272
27273         procedure Report_Unused_Constituents (Constits : Elist_Id);
27274         --  Emit errors for all unused Part_Of constituents in list Constits
27275
27276         -------------------------
27277         -- Analyze_Constituent --
27278         -------------------------
27279
27280         procedure Analyze_Constituent (Constit : Node_Id) is
27281            procedure Match_Constituent (Constit_Id : Entity_Id);
27282            --  Determine whether constituent Constit denoted by its entity
27283            --  Constit_Id appears in Body_States. Emit an error when the
27284            --  constituent is not a valid hidden state of the related package
27285            --  or when it is used more than once. Otherwise remove the
27286            --  constituent from Body_States.
27287
27288            -----------------------
27289            -- Match_Constituent --
27290            -----------------------
27291
27292            procedure Match_Constituent (Constit_Id : Entity_Id) is
27293               procedure Collect_Constituent;
27294               --  Verify the legality of constituent Constit_Id and add it to
27295               --  the refinements of State_Id.
27296
27297               -------------------------
27298               -- Collect_Constituent --
27299               -------------------------
27300
27301               procedure Collect_Constituent is
27302                  Constits : Elist_Id;
27303
27304               begin
27305                  --  The Ghost policy in effect at the point of abstract state
27306                  --  declaration and constituent must match (SPARK RM 6.9(15))
27307
27308                  Check_Ghost_Refinement
27309                    (State, State_Id, Constit, Constit_Id);
27310
27311                  --  A synchronized state must be refined by a synchronized
27312                  --  object or another synchronized state (SPARK RM 9.6).
27313
27314                  if Is_Synchronized_State (State_Id)
27315                    and then not Is_Synchronized_Object (Constit_Id)
27316                    and then not Is_Synchronized_State (Constit_Id)
27317                  then
27318                     SPARK_Msg_NE
27319                       ("constituent of synchronized state & must be "
27320                        & "synchronized", Constit, State_Id);
27321                  end if;
27322
27323                  --  Add the constituent to the list of processed items to aid
27324                  --  with the detection of duplicates.
27325
27326                  Append_New_Elmt (Constit_Id, Constituents_Seen);
27327
27328                  --  Collect the constituent in the list of refinement items
27329                  --  and establish a relation between the refined state and
27330                  --  the item.
27331
27332                  Constits := Refinement_Constituents (State_Id);
27333
27334                  if No (Constits) then
27335                     Constits := New_Elmt_List;
27336                     Set_Refinement_Constituents (State_Id, Constits);
27337                  end if;
27338
27339                  Append_Elmt (Constit_Id, Constits);
27340                  Set_Encapsulating_State (Constit_Id, State_Id);
27341
27342                  --  The state has at least one legal constituent, mark the
27343                  --  start of the refinement region. The region ends when the
27344                  --  body declarations end (see routine Analyze_Declarations).
27345
27346                  Set_Has_Visible_Refinement (State_Id);
27347
27348                  --  When the constituent is external, save its relevant
27349                  --  property for further checks.
27350
27351                  if Async_Readers_Enabled (Constit_Id) then
27352                     AR_Constit := Constit_Id;
27353                     External_Constit_Seen := True;
27354                  end if;
27355
27356                  if Async_Writers_Enabled (Constit_Id) then
27357                     AW_Constit := Constit_Id;
27358                     External_Constit_Seen := True;
27359                  end if;
27360
27361                  if Effective_Reads_Enabled (Constit_Id) then
27362                     ER_Constit := Constit_Id;
27363                     External_Constit_Seen := True;
27364                  end if;
27365
27366                  if Effective_Writes_Enabled (Constit_Id) then
27367                     EW_Constit := Constit_Id;
27368                     External_Constit_Seen := True;
27369                  end if;
27370               end Collect_Constituent;
27371
27372               --  Local variables
27373
27374               State_Elmt : Elmt_Id;
27375
27376            --  Start of processing for Match_Constituent
27377
27378            begin
27379               --  Detect a duplicate use of a constituent
27380
27381               if Contains (Constituents_Seen, Constit_Id) then
27382                  SPARK_Msg_NE
27383                    ("duplicate use of constituent &", Constit, Constit_Id);
27384                  return;
27385               end if;
27386
27387               --  The constituent is subject to a Part_Of indicator
27388
27389               if Present (Encapsulating_State (Constit_Id)) then
27390                  if Encapsulating_State (Constit_Id) = State_Id then
27391                     Remove (Part_Of_Constits, Constit_Id);
27392                     Collect_Constituent;
27393
27394                  --  The constituent is part of another state and is used
27395                  --  incorrectly in the refinement of the current state.
27396
27397                  else
27398                     Error_Msg_Name_1 := Chars (State_Id);
27399                     SPARK_Msg_NE
27400                       ("& cannot act as constituent of state %",
27401                        Constit, Constit_Id);
27402                     SPARK_Msg_NE
27403                       ("\Part_Of indicator specifies encapsulator &",
27404                        Constit, Encapsulating_State (Constit_Id));
27405                  end if;
27406
27407               --  The only other source of legal constituents is the body
27408               --  state space of the related package.
27409
27410               else
27411                  if Present (Body_States) then
27412                     State_Elmt := First_Elmt (Body_States);
27413                     while Present (State_Elmt) loop
27414
27415                        --  Consume a valid constituent to signal that it has
27416                        --  been encountered.
27417
27418                        if Node (State_Elmt) = Constit_Id then
27419                           Remove_Elmt (Body_States, State_Elmt);
27420                           Collect_Constituent;
27421                           return;
27422                        end if;
27423
27424                        Next_Elmt (State_Elmt);
27425                     end loop;
27426                  end if;
27427
27428                  --  At this point it is known that the constituent is not
27429                  --  part of the package hidden state and cannot be used in
27430                  --  a refinement (SPARK RM 7.2.2(9)).
27431
27432                  Error_Msg_Name_1 := Chars (Spec_Id);
27433                  SPARK_Msg_NE
27434                    ("cannot use & in refinement, constituent is not a hidden "
27435                     & "state of package %", Constit, Constit_Id);
27436               end if;
27437            end Match_Constituent;
27438
27439            --  Local variables
27440
27441            Constit_Id : Entity_Id;
27442            Constits   : Elist_Id;
27443
27444         --  Start of processing for Analyze_Constituent
27445
27446         begin
27447            --  Detect multiple uses of null in a single refinement clause or a
27448            --  mixture of null and non-null constituents.
27449
27450            if Nkind (Constit) = N_Null then
27451               if Null_Seen then
27452                  SPARK_Msg_N
27453                    ("multiple null constituents not allowed", Constit);
27454
27455               elsif Non_Null_Seen then
27456                  SPARK_Msg_N
27457                    ("cannot mix null and non-null constituents", Constit);
27458
27459               else
27460                  Null_Seen := True;
27461
27462                  --  Collect the constituent in the list of refinement items
27463
27464                  Constits := Refinement_Constituents (State_Id);
27465
27466                  if No (Constits) then
27467                     Constits := New_Elmt_List;
27468                     Set_Refinement_Constituents (State_Id, Constits);
27469                  end if;
27470
27471                  Append_Elmt (Constit, Constits);
27472
27473                  --  The state has at least one legal constituent, mark the
27474                  --  start of the refinement region. The region ends when the
27475                  --  body declarations end (see Analyze_Declarations).
27476
27477                  Set_Has_Visible_Refinement (State_Id);
27478               end if;
27479
27480            --  Non-null constituents
27481
27482            else
27483               Non_Null_Seen := True;
27484
27485               if Null_Seen then
27486                  SPARK_Msg_N
27487                    ("cannot mix null and non-null constituents", Constit);
27488               end if;
27489
27490               Analyze       (Constit);
27491               Resolve_State (Constit);
27492
27493               --  Ensure that the constituent denotes a valid state or a
27494               --  whole object (SPARK RM 7.2.2(5)).
27495
27496               if Is_Entity_Name (Constit) then
27497                  Constit_Id := Entity_Of (Constit);
27498
27499                  --  When a constituent is declared after a subprogram body
27500                  --  that caused freezing of the related contract where
27501                  --  pragma Refined_State resides, the constituent appears
27502                  --  undefined and carries Any_Id as its entity.
27503
27504                  --    package body Pack
27505                  --      with Refined_State => (State => Constit)
27506                  --    is
27507                  --       procedure Proc
27508                  --         with Refined_Global => (Input => Constit)
27509                  --       is
27510                  --          ...
27511                  --       end Proc;
27512
27513                  --       Constit : ...;
27514                  --    end Pack;
27515
27516                  if Constit_Id = Any_Id then
27517                     SPARK_Msg_NE ("& is undefined", Constit, Constit_Id);
27518
27519                     --  Emit a specialized info message when the contract of
27520                     --  the related package body was "frozen" by another body.
27521                     --  Note that it is not possible to precisely identify why
27522                     --  the constituent is undefined because it is not visible
27523                     --  when pragma Refined_State is analyzed. This message is
27524                     --  a reasonable approximation.
27525
27526                     if Present (Freeze_Id) and then not Freeze_Posted then
27527                        Freeze_Posted := True;
27528
27529                        Error_Msg_Name_1 := Chars (Body_Id);
27530                        Error_Msg_Sloc   := Sloc (Freeze_Id);
27531                        SPARK_Msg_NE
27532                          ("body & declared # freezes the contract of %",
27533                           N, Freeze_Id);
27534                        SPARK_Msg_N
27535                          ("\all constituents must be declared before body #",
27536                           N);
27537
27538                        --  A misplaced constituent is a critical error because
27539                        --  pragma Refined_Depends or Refined_Global depends on
27540                        --  the proper link between a state and a constituent.
27541                        --  Stop the compilation, as this leads to a multitude
27542                        --  of misleading cascaded errors.
27543
27544                        raise Unrecoverable_Error;
27545                     end if;
27546
27547                  --  The constituent is a valid state or object
27548
27549                  elsif Ekind_In (Constit_Id, E_Abstract_State,
27550                                              E_Constant,
27551                                              E_Variable)
27552                  then
27553                     Match_Constituent (Constit_Id);
27554
27555                     --  The variable may eventually become a constituent of a
27556                     --  single protected/task type. Record the reference now
27557                     --  and verify its legality when analyzing the contract of
27558                     --  the variable (SPARK RM 9.3).
27559
27560                     if Ekind (Constit_Id) = E_Variable then
27561                        Record_Possible_Part_Of_Reference
27562                          (Var_Id => Constit_Id,
27563                           Ref    => Constit);
27564                     end if;
27565
27566                  --  Otherwise the constituent is illegal
27567
27568                  else
27569                     SPARK_Msg_NE
27570                       ("constituent & must denote object or state",
27571                        Constit, Constit_Id);
27572                  end if;
27573
27574               --  The constituent is illegal
27575
27576               else
27577                  SPARK_Msg_N ("malformed constituent", Constit);
27578               end if;
27579            end if;
27580         end Analyze_Constituent;
27581
27582         -----------------------------
27583         -- Check_External_Property --
27584         -----------------------------
27585
27586         procedure Check_External_Property
27587           (Prop_Nam : Name_Id;
27588            Enabled  : Boolean;
27589            Constit  : Entity_Id)
27590         is
27591         begin
27592            --  The property is missing in the declaration of the state, but
27593            --  a constituent is introducing it in the state refinement
27594            --  (SPARK RM 7.2.8(2)).
27595
27596            if not Enabled and then Present (Constit) then
27597               Error_Msg_Name_1 := Prop_Nam;
27598               Error_Msg_Name_2 := Chars (State_Id);
27599               SPARK_Msg_NE
27600                 ("constituent & introduces external property % in refinement "
27601                  & "of state %", State, Constit);
27602
27603               Error_Msg_Sloc := Sloc (State_Id);
27604               SPARK_Msg_N
27605                 ("\property is missing in abstract state declaration #",
27606                  State);
27607            end if;
27608         end Check_External_Property;
27609
27610         -----------------
27611         -- Match_State --
27612         -----------------
27613
27614         procedure Match_State is
27615            State_Elmt : Elmt_Id;
27616
27617         begin
27618            --  Detect a duplicate refinement of a state (SPARK RM 7.2.2(8))
27619
27620            if Contains (Refined_States_Seen, State_Id) then
27621               SPARK_Msg_NE
27622                 ("duplicate refinement of state &", State, State_Id);
27623               return;
27624            end if;
27625
27626            --  Inspect the abstract states defined in the package declaration
27627            --  looking for a match.
27628
27629            State_Elmt := First_Elmt (Available_States);
27630            while Present (State_Elmt) loop
27631
27632               --  A valid abstract state is being refined in the body. Add
27633               --  the state to the list of processed refined states to aid
27634               --  with the detection of duplicate refinements. Remove the
27635               --  state from Available_States to signal that it has already
27636               --  been refined.
27637
27638               if Node (State_Elmt) = State_Id then
27639                  Append_New_Elmt (State_Id, Refined_States_Seen);
27640                  Remove_Elmt (Available_States, State_Elmt);
27641                  return;
27642               end if;
27643
27644               Next_Elmt (State_Elmt);
27645            end loop;
27646
27647            --  If we get here, we are refining a state that is not defined in
27648            --  the package declaration.
27649
27650            Error_Msg_Name_1 := Chars (Spec_Id);
27651            SPARK_Msg_NE
27652              ("cannot refine state, & is not defined in package %",
27653               State, State_Id);
27654         end Match_State;
27655
27656         --------------------------------
27657         -- Report_Unused_Constituents --
27658         --------------------------------
27659
27660         procedure Report_Unused_Constituents (Constits : Elist_Id) is
27661            Constit_Elmt : Elmt_Id;
27662            Constit_Id   : Entity_Id;
27663            Posted       : Boolean := False;
27664
27665         begin
27666            if Present (Constits) then
27667               Constit_Elmt := First_Elmt (Constits);
27668               while Present (Constit_Elmt) loop
27669                  Constit_Id := Node (Constit_Elmt);
27670
27671                  --  Generate an error message of the form:
27672
27673                  --    state ... has unused Part_Of constituents
27674                  --      abstract state ... defined at ...
27675                  --      constant ... defined at ...
27676                  --      variable ... defined at ...
27677
27678                  if not Posted then
27679                     Posted := True;
27680                     SPARK_Msg_NE
27681                       ("state & has unused Part_Of constituents",
27682                        State, State_Id);
27683                  end if;
27684
27685                  Error_Msg_Sloc := Sloc (Constit_Id);
27686
27687                  if Ekind (Constit_Id) = E_Abstract_State then
27688                     SPARK_Msg_NE
27689                       ("\abstract state & defined #", State, Constit_Id);
27690
27691                  elsif Ekind (Constit_Id) = E_Constant then
27692                     SPARK_Msg_NE
27693                       ("\constant & defined #", State, Constit_Id);
27694
27695                  else
27696                     pragma Assert (Ekind (Constit_Id) = E_Variable);
27697                     SPARK_Msg_NE ("\variable & defined #", State, Constit_Id);
27698                  end if;
27699
27700                  Next_Elmt (Constit_Elmt);
27701               end loop;
27702            end if;
27703         end Report_Unused_Constituents;
27704
27705         --  Local declarations
27706
27707         Body_Ref      : Node_Id;
27708         Body_Ref_Elmt : Elmt_Id;
27709         Constit       : Node_Id;
27710         Extra_State   : Node_Id;
27711
27712      --  Start of processing for Analyze_Refinement_Clause
27713
27714      begin
27715         --  A refinement clause appears as a component association where the
27716         --  sole choice is the state and the expressions are the constituents.
27717         --  This is a syntax error, always report.
27718
27719         if Nkind (Clause) /= N_Component_Association then
27720            Error_Msg_N ("malformed state refinement clause", Clause);
27721            return;
27722         end if;
27723
27724         --  Analyze the state name of a refinement clause
27725
27726         State := First (Choices (Clause));
27727
27728         Analyze       (State);
27729         Resolve_State (State);
27730
27731         --  Ensure that the state name denotes a valid abstract state that is
27732         --  defined in the spec of the related package.
27733
27734         if Is_Entity_Name (State) then
27735            State_Id := Entity_Of (State);
27736
27737            --  When the abstract state is undefined, it appears as Any_Id. Do
27738            --  not continue with the analysis of the clause.
27739
27740            if State_Id = Any_Id then
27741               return;
27742
27743            --  Catch any attempts to re-refine a state or refine a state that
27744            --  is not defined in the package declaration.
27745
27746            elsif Ekind (State_Id) = E_Abstract_State then
27747               Match_State;
27748
27749            else
27750               SPARK_Msg_NE ("& must denote abstract state", State, State_Id);
27751               return;
27752            end if;
27753
27754            --  References to a state with visible refinement are illegal.
27755            --  When nested packages are involved, detecting such references is
27756            --  tricky because pragma Refined_State is analyzed later than the
27757            --  offending pragma Depends or Global. References that occur in
27758            --  such nested context are stored in a list. Emit errors for all
27759            --  references found in Body_References (SPARK RM 6.1.4(8)).
27760
27761            if Present (Body_References (State_Id)) then
27762               Body_Ref_Elmt := First_Elmt (Body_References (State_Id));
27763               while Present (Body_Ref_Elmt) loop
27764                  Body_Ref := Node (Body_Ref_Elmt);
27765
27766                  SPARK_Msg_N ("reference to & not allowed", Body_Ref);
27767                  Error_Msg_Sloc := Sloc (State);
27768                  SPARK_Msg_N ("\refinement of & is visible#", Body_Ref);
27769
27770                  Next_Elmt (Body_Ref_Elmt);
27771               end loop;
27772            end if;
27773
27774         --  The state name is illegal. This is a syntax error, always report.
27775
27776         else
27777            Error_Msg_N ("malformed state name in refinement clause", State);
27778            return;
27779         end if;
27780
27781         --  A refinement clause may only refine one state at a time
27782
27783         Extra_State := Next (State);
27784
27785         if Present (Extra_State) then
27786            SPARK_Msg_N
27787              ("refinement clause cannot cover multiple states", Extra_State);
27788         end if;
27789
27790         --  Replicate the Part_Of constituents of the refined state because
27791         --  the algorithm will consume items.
27792
27793         Part_Of_Constits := New_Copy_Elist (Part_Of_Constituents (State_Id));
27794
27795         --  Analyze all constituents of the refinement. Multiple constituents
27796         --  appear as an aggregate.
27797
27798         Constit := Expression (Clause);
27799
27800         if Nkind (Constit) = N_Aggregate then
27801            if Present (Component_Associations (Constit)) then
27802               SPARK_Msg_N
27803                 ("constituents of refinement clause must appear in "
27804                  & "positional form", Constit);
27805
27806            else pragma Assert (Present (Expressions (Constit)));
27807               Constit := First (Expressions (Constit));
27808               while Present (Constit) loop
27809                  Analyze_Constituent (Constit);
27810                  Next (Constit);
27811               end loop;
27812            end if;
27813
27814         --  Various forms of a single constituent. Note that these may include
27815         --  malformed constituents.
27816
27817         else
27818            Analyze_Constituent (Constit);
27819         end if;
27820
27821         --  Verify that external constituents do not introduce new external
27822         --  property in the state refinement (SPARK RM 7.2.8(2)).
27823
27824         if Is_External_State (State_Id) then
27825            Check_External_Property
27826              (Prop_Nam => Name_Async_Readers,
27827               Enabled  => Async_Readers_Enabled (State_Id),
27828               Constit  => AR_Constit);
27829
27830            Check_External_Property
27831              (Prop_Nam => Name_Async_Writers,
27832               Enabled  => Async_Writers_Enabled (State_Id),
27833               Constit  => AW_Constit);
27834
27835            Check_External_Property
27836              (Prop_Nam => Name_Effective_Reads,
27837               Enabled  => Effective_Reads_Enabled (State_Id),
27838               Constit  => ER_Constit);
27839
27840            Check_External_Property
27841              (Prop_Nam => Name_Effective_Writes,
27842               Enabled  => Effective_Writes_Enabled (State_Id),
27843               Constit  => EW_Constit);
27844
27845         --  When a refined state is not external, it should not have external
27846         --  constituents (SPARK RM 7.2.8(1)).
27847
27848         elsif External_Constit_Seen then
27849            SPARK_Msg_NE
27850              ("non-external state & cannot contain external constituents in "
27851               & "refinement", State, State_Id);
27852         end if;
27853
27854         --  Ensure that all Part_Of candidate constituents have been mentioned
27855         --  in the refinement clause.
27856
27857         Report_Unused_Constituents (Part_Of_Constits);
27858      end Analyze_Refinement_Clause;
27859
27860      -----------------------------
27861      -- Report_Unrefined_States --
27862      -----------------------------
27863
27864      procedure Report_Unrefined_States (States : Elist_Id) is
27865         State_Elmt : Elmt_Id;
27866
27867      begin
27868         if Present (States) then
27869            State_Elmt := First_Elmt (States);
27870            while Present (State_Elmt) loop
27871               SPARK_Msg_N
27872                 ("abstract state & must be refined", Node (State_Elmt));
27873
27874               Next_Elmt (State_Elmt);
27875            end loop;
27876         end if;
27877      end Report_Unrefined_States;
27878
27879      --  Local declarations
27880
27881      Clauses : constant Node_Id := Expression (Get_Argument (N, Spec_Id));
27882      Clause  : Node_Id;
27883
27884   --  Start of processing for Analyze_Refined_State_In_Decl_Part
27885
27886   begin
27887      --  Do not analyze the pragma multiple times
27888
27889      if Is_Analyzed_Pragma (N) then
27890         return;
27891      end if;
27892
27893      --  Save the scenario for examination by the ABE Processing phase
27894
27895      Record_Elaboration_Scenario (N);
27896
27897      --  Replicate the abstract states declared by the package because the
27898      --  matching algorithm will consume states.
27899
27900      Available_States := New_Copy_Elist (Abstract_States (Spec_Id));
27901
27902      --  Gather all abstract states and objects declared in the visible
27903      --  state space of the package body. These items must be utilized as
27904      --  constituents in a state refinement.
27905
27906      Body_States := Collect_Body_States (Body_Id);
27907
27908      --  Multiple non-null state refinements appear as an aggregate
27909
27910      if Nkind (Clauses) = N_Aggregate then
27911         if Present (Expressions (Clauses)) then
27912            SPARK_Msg_N
27913              ("state refinements must appear as component associations",
27914               Clauses);
27915
27916         else pragma Assert (Present (Component_Associations (Clauses)));
27917            Clause := First (Component_Associations (Clauses));
27918            while Present (Clause) loop
27919               Analyze_Refinement_Clause (Clause);
27920               Next (Clause);
27921            end loop;
27922         end if;
27923
27924      --  Various forms of a single state refinement. Note that these may
27925      --  include malformed refinements.
27926
27927      else
27928         Analyze_Refinement_Clause (Clauses);
27929      end if;
27930
27931      --  List all abstract states that were left unrefined
27932
27933      Report_Unrefined_States (Available_States);
27934
27935      Set_Is_Analyzed_Pragma (N);
27936   end Analyze_Refined_State_In_Decl_Part;
27937
27938   ------------------------------------
27939   -- Analyze_Test_Case_In_Decl_Part --
27940   ------------------------------------
27941
27942   procedure Analyze_Test_Case_In_Decl_Part (N : Node_Id) is
27943      Subp_Decl : constant Node_Id   := Find_Related_Declaration_Or_Body (N);
27944      Spec_Id   : constant Entity_Id := Unique_Defining_Entity (Subp_Decl);
27945
27946      procedure Preanalyze_Test_Case_Arg (Arg_Nam : Name_Id);
27947      --  Preanalyze one of the optional arguments "Requires" or "Ensures"
27948      --  denoted by Arg_Nam.
27949
27950      ------------------------------
27951      -- Preanalyze_Test_Case_Arg --
27952      ------------------------------
27953
27954      procedure Preanalyze_Test_Case_Arg (Arg_Nam : Name_Id) is
27955         Arg : Node_Id;
27956
27957      begin
27958         --  Preanalyze the original aspect argument for ASIS or for a generic
27959         --  subprogram to properly capture global references.
27960
27961         if ASIS_Mode or else Is_Generic_Subprogram (Spec_Id) then
27962            Arg :=
27963              Test_Case_Arg
27964                (Prag        => N,
27965                 Arg_Nam     => Arg_Nam,
27966                 From_Aspect => True);
27967
27968            if Present (Arg) then
27969               Preanalyze_Assert_Expression
27970                 (Expression (Arg), Standard_Boolean);
27971            end if;
27972         end if;
27973
27974         Arg := Test_Case_Arg (N, Arg_Nam);
27975
27976         if Present (Arg) then
27977            Preanalyze_Assert_Expression (Expression (Arg), Standard_Boolean);
27978         end if;
27979      end Preanalyze_Test_Case_Arg;
27980
27981      --  Local variables
27982
27983      Restore_Scope : Boolean := False;
27984
27985   --  Start of processing for Analyze_Test_Case_In_Decl_Part
27986
27987   begin
27988      --  Do not analyze the pragma multiple times
27989
27990      if Is_Analyzed_Pragma (N) then
27991         return;
27992      end if;
27993
27994      --  Ensure that the formal parameters are visible when analyzing all
27995      --  clauses. This falls out of the general rule of aspects pertaining
27996      --  to subprogram declarations.
27997
27998      if not In_Open_Scopes (Spec_Id) then
27999         Restore_Scope := True;
28000         Push_Scope (Spec_Id);
28001
28002         if Is_Generic_Subprogram (Spec_Id) then
28003            Install_Generic_Formals (Spec_Id);
28004         else
28005            Install_Formals (Spec_Id);
28006         end if;
28007      end if;
28008
28009      Preanalyze_Test_Case_Arg (Name_Requires);
28010      Preanalyze_Test_Case_Arg (Name_Ensures);
28011
28012      if Restore_Scope then
28013         End_Scope;
28014      end if;
28015
28016      --  Currently it is not possible to inline pre/postconditions on a
28017      --  subprogram subject to pragma Inline_Always.
28018
28019      Check_Postcondition_Use_In_Inlined_Subprogram (N, Spec_Id);
28020
28021      Set_Is_Analyzed_Pragma (N);
28022   end Analyze_Test_Case_In_Decl_Part;
28023
28024   ----------------
28025   -- Appears_In --
28026   ----------------
28027
28028   function Appears_In (List : Elist_Id; Item_Id : Entity_Id) return Boolean is
28029      Elmt : Elmt_Id;
28030      Id   : Entity_Id;
28031
28032   begin
28033      if Present (List) then
28034         Elmt := First_Elmt (List);
28035         while Present (Elmt) loop
28036            if Nkind (Node (Elmt)) = N_Defining_Identifier then
28037               Id := Node (Elmt);
28038            else
28039               Id := Entity_Of (Node (Elmt));
28040            end if;
28041
28042            if Id = Item_Id then
28043               return True;
28044            end if;
28045
28046            Next_Elmt (Elmt);
28047         end loop;
28048      end if;
28049
28050      return False;
28051   end Appears_In;
28052
28053   -----------------------------------
28054   -- Build_Pragma_Check_Equivalent --
28055   -----------------------------------
28056
28057   function Build_Pragma_Check_Equivalent
28058     (Prag           : Node_Id;
28059      Subp_Id        : Entity_Id := Empty;
28060      Inher_Id       : Entity_Id := Empty;
28061      Keep_Pragma_Id : Boolean := False) return Node_Id
28062   is
28063      function Suppress_Reference (N : Node_Id) return Traverse_Result;
28064      --  Detect whether node N references a formal parameter subject to
28065      --  pragma Unreferenced. If this is the case, set Comes_From_Source
28066      --  to False to suppress the generation of a reference when analyzing
28067      --  N later on.
28068
28069      ------------------------
28070      -- Suppress_Reference --
28071      ------------------------
28072
28073      function Suppress_Reference (N : Node_Id) return Traverse_Result is
28074         Formal : Entity_Id;
28075
28076      begin
28077         if Is_Entity_Name (N) and then Present (Entity (N)) then
28078            Formal := Entity (N);
28079
28080            --  The formal parameter is subject to pragma Unreferenced. Prevent
28081            --  the generation of references by resetting the Comes_From_Source
28082            --  flag.
28083
28084            if Is_Formal (Formal)
28085              and then Has_Pragma_Unreferenced (Formal)
28086            then
28087               Set_Comes_From_Source (N, False);
28088            end if;
28089         end if;
28090
28091         return OK;
28092      end Suppress_Reference;
28093
28094      procedure Suppress_References is
28095        new Traverse_Proc (Suppress_Reference);
28096
28097      --  Local variables
28098
28099      Loc        : constant Source_Ptr := Sloc (Prag);
28100      Prag_Nam   : constant Name_Id    := Pragma_Name (Prag);
28101      Check_Prag : Node_Id;
28102      Msg_Arg    : Node_Id;
28103      Nam        : Name_Id;
28104
28105      Needs_Wrapper : Boolean;
28106      pragma Unreferenced (Needs_Wrapper);
28107
28108   --  Start of processing for Build_Pragma_Check_Equivalent
28109
28110   begin
28111      --  When the pre- or postcondition is inherited, map the formals of the
28112      --  inherited subprogram to those of the current subprogram. In addition,
28113      --  map primitive operations of the parent type into the corresponding
28114      --  primitive operations of the descendant.
28115
28116      if Present (Inher_Id) then
28117         pragma Assert (Present (Subp_Id));
28118
28119         Update_Primitives_Mapping (Inher_Id, Subp_Id);
28120
28121         --  Use generic machinery to copy inherited pragma, as if it were an
28122         --  instantiation, resetting source locations appropriately, so that
28123         --  expressions inside the inherited pragma use chained locations.
28124         --  This is used in particular in GNATprove to locate precisely
28125         --  messages on a given inherited pragma.
28126
28127         Set_Copied_Sloc_For_Inherited_Pragma
28128           (Unit_Declaration_Node (Subp_Id), Inher_Id);
28129         Check_Prag := New_Copy_Tree (Source => Prag);
28130
28131         --  Build the inherited class-wide condition
28132
28133         Build_Class_Wide_Expression
28134           (Prag          => Check_Prag,
28135            Subp          => Subp_Id,
28136            Par_Subp      => Inher_Id,
28137            Adjust_Sloc   => True,
28138            Needs_Wrapper => Needs_Wrapper);
28139
28140      --  If not an inherited condition simply copy the original pragma
28141
28142      else
28143         Check_Prag := New_Copy_Tree (Source => Prag);
28144      end if;
28145
28146      --  Mark the pragma as being internally generated and reset the Analyzed
28147      --  flag.
28148
28149      Set_Analyzed          (Check_Prag, False);
28150      Set_Comes_From_Source (Check_Prag, False);
28151
28152      --  The tree of the original pragma may contain references to the
28153      --  formal parameters of the related subprogram. At the same time
28154      --  the corresponding body may mark the formals as unreferenced:
28155
28156      --     procedure Proc (Formal : ...)
28157      --       with Pre => Formal ...;
28158
28159      --     procedure Proc (Formal : ...) is
28160      --        pragma Unreferenced (Formal);
28161      --     ...
28162
28163      --  This creates problems because all pragma Check equivalents are
28164      --  analyzed at the end of the body declarations. Since all source
28165      --  references have already been accounted for, reset any references
28166      --  to such formals in the generated pragma Check equivalent.
28167
28168      Suppress_References (Check_Prag);
28169
28170      if Present (Corresponding_Aspect (Prag)) then
28171         Nam := Chars (Identifier (Corresponding_Aspect (Prag)));
28172      else
28173         Nam := Prag_Nam;
28174      end if;
28175
28176      --  Unless Keep_Pragma_Id is True in order to keep the identifier of
28177      --  the copied pragma in the newly created pragma, convert the copy into
28178      --  pragma Check by correcting the name and adding a check_kind argument.
28179
28180      if not Keep_Pragma_Id then
28181         Set_Class_Present (Check_Prag, False);
28182
28183         Set_Pragma_Identifier
28184           (Check_Prag, Make_Identifier (Loc, Name_Check));
28185
28186         Prepend_To (Pragma_Argument_Associations (Check_Prag),
28187           Make_Pragma_Argument_Association (Loc,
28188             Expression => Make_Identifier (Loc, Nam)));
28189      end if;
28190
28191      --  Update the error message when the pragma is inherited
28192
28193      if Present (Inher_Id) then
28194         Msg_Arg := Last (Pragma_Argument_Associations (Check_Prag));
28195
28196         if Chars (Msg_Arg) = Name_Message then
28197            String_To_Name_Buffer (Strval (Expression (Msg_Arg)));
28198
28199            --  Insert "inherited" to improve the error message
28200
28201            if Name_Buffer (1 .. 8) = "failed p" then
28202               Insert_Str_In_Name_Buffer ("inherited ", 8);
28203               Set_Strval (Expression (Msg_Arg), String_From_Name_Buffer);
28204            end if;
28205         end if;
28206      end if;
28207
28208      return Check_Prag;
28209   end Build_Pragma_Check_Equivalent;
28210
28211   -----------------------------
28212   -- Check_Applicable_Policy --
28213   -----------------------------
28214
28215   procedure Check_Applicable_Policy (N : Node_Id) is
28216      PP     : Node_Id;
28217      Policy : Name_Id;
28218
28219      Ename : constant Name_Id := Original_Aspect_Pragma_Name (N);
28220
28221   begin
28222      --  No effect if not valid assertion kind name
28223
28224      if not Is_Valid_Assertion_Kind (Ename) then
28225         return;
28226      end if;
28227
28228      --  Loop through entries in check policy list
28229
28230      PP := Opt.Check_Policy_List;
28231      while Present (PP) loop
28232         declare
28233            PPA : constant List_Id := Pragma_Argument_Associations (PP);
28234            Pnm : constant Name_Id := Chars (Get_Pragma_Arg (First (PPA)));
28235
28236         begin
28237            if Ename = Pnm
28238              or else Pnm = Name_Assertion
28239              or else (Pnm = Name_Statement_Assertions
28240                        and then Nam_In (Ename, Name_Assert,
28241                                                Name_Assert_And_Cut,
28242                                                Name_Assume,
28243                                                Name_Loop_Invariant,
28244                                                Name_Loop_Variant))
28245            then
28246               Policy := Chars (Get_Pragma_Arg (Last (PPA)));
28247
28248               case Policy is
28249                  when Name_Ignore
28250                     | Name_Off
28251                  =>
28252                     Set_Is_Ignored (N, True);
28253                     Set_Is_Checked (N, False);
28254
28255                  when Name_Check
28256                     | Name_On
28257                  =>
28258                     Set_Is_Checked (N, True);
28259                     Set_Is_Ignored (N, False);
28260
28261                  when Name_Disable =>
28262                     Set_Is_Ignored  (N, True);
28263                     Set_Is_Checked  (N, False);
28264                     Set_Is_Disabled (N, True);
28265
28266                  --  That should be exhaustive, the null here is a defence
28267                  --  against a malformed tree from previous errors.
28268
28269                  when others =>
28270                     null;
28271               end case;
28272
28273               return;
28274            end if;
28275
28276            PP := Next_Pragma (PP);
28277         end;
28278      end loop;
28279
28280      --  If there are no specific entries that matched, then we let the
28281      --  setting of assertions govern. Note that this provides the needed
28282      --  compatibility with the RM for the cases of assertion, invariant,
28283      --  precondition, predicate, and postcondition.
28284
28285      if Assertions_Enabled then
28286         Set_Is_Checked (N, True);
28287         Set_Is_Ignored (N, False);
28288      else
28289         Set_Is_Checked (N, False);
28290         Set_Is_Ignored (N, True);
28291      end if;
28292   end Check_Applicable_Policy;
28293
28294   -------------------------------
28295   -- Check_External_Properties --
28296   -------------------------------
28297
28298   procedure Check_External_Properties
28299     (Item : Node_Id;
28300      AR   : Boolean;
28301      AW   : Boolean;
28302      ER   : Boolean;
28303      EW   : Boolean)
28304   is
28305   begin
28306      --  All properties enabled
28307
28308      if AR and AW and ER and EW then
28309         null;
28310
28311      --  Async_Readers + Effective_Writes
28312      --  Async_Readers + Async_Writers + Effective_Writes
28313
28314      elsif AR and EW and not ER then
28315         null;
28316
28317      --  Async_Writers + Effective_Reads
28318      --  Async_Readers + Async_Writers + Effective_Reads
28319
28320      elsif AW and ER and not EW then
28321         null;
28322
28323      --  Async_Readers + Async_Writers
28324
28325      elsif AR and AW and not ER and not EW then
28326         null;
28327
28328      --  Async_Readers
28329
28330      elsif AR and not AW and not ER and not EW then
28331         null;
28332
28333      --  Async_Writers
28334
28335      elsif AW and not AR and not ER and not EW then
28336         null;
28337
28338      else
28339         SPARK_Msg_N
28340           ("illegal combination of external properties (SPARK RM 7.1.2(6))",
28341            Item);
28342      end if;
28343   end Check_External_Properties;
28344
28345   ----------------
28346   -- Check_Kind --
28347   ----------------
28348
28349   function Check_Kind (Nam : Name_Id) return Name_Id is
28350      PP : Node_Id;
28351
28352   begin
28353      --  Loop through entries in check policy list
28354
28355      PP := Opt.Check_Policy_List;
28356      while Present (PP) loop
28357         declare
28358            PPA : constant List_Id := Pragma_Argument_Associations (PP);
28359            Pnm : constant Name_Id := Chars (Get_Pragma_Arg (First (PPA)));
28360
28361         begin
28362            if Nam = Pnm
28363              or else (Pnm = Name_Assertion
28364                        and then Is_Valid_Assertion_Kind (Nam))
28365              or else (Pnm = Name_Statement_Assertions
28366                        and then Nam_In (Nam, Name_Assert,
28367                                              Name_Assert_And_Cut,
28368                                              Name_Assume,
28369                                              Name_Loop_Invariant,
28370                                              Name_Loop_Variant))
28371            then
28372               case (Chars (Get_Pragma_Arg (Last (PPA)))) is
28373                  when Name_Check
28374                     | Name_On
28375                  =>
28376                     return Name_Check;
28377
28378                  when Name_Ignore
28379                     | Name_Off
28380                  =>
28381                     return Name_Ignore;
28382
28383                  when Name_Disable =>
28384                     return Name_Disable;
28385
28386                  when others =>
28387                     raise Program_Error;
28388               end case;
28389
28390            else
28391               PP := Next_Pragma (PP);
28392            end if;
28393         end;
28394      end loop;
28395
28396      --  If there are no specific entries that matched, then we let the
28397      --  setting of assertions govern. Note that this provides the needed
28398      --  compatibility with the RM for the cases of assertion, invariant,
28399      --  precondition, predicate, and postcondition.
28400
28401      if Assertions_Enabled then
28402         return Name_Check;
28403      else
28404         return Name_Ignore;
28405      end if;
28406   end Check_Kind;
28407
28408   ---------------------------
28409   -- Check_Missing_Part_Of --
28410   ---------------------------
28411
28412   procedure Check_Missing_Part_Of (Item_Id : Entity_Id) is
28413      function Has_Visible_State (Pack_Id : Entity_Id) return Boolean;
28414      --  Determine whether a package denoted by Pack_Id declares at least one
28415      --  visible state.
28416
28417      -----------------------
28418      -- Has_Visible_State --
28419      -----------------------
28420
28421      function Has_Visible_State (Pack_Id : Entity_Id) return Boolean is
28422         Item_Id : Entity_Id;
28423
28424      begin
28425         --  Traverse the entity chain of the package trying to find at least
28426         --  one visible abstract state, variable or a package [instantiation]
28427         --  that declares a visible state.
28428
28429         Item_Id := First_Entity (Pack_Id);
28430         while Present (Item_Id)
28431           and then not In_Private_Part (Item_Id)
28432         loop
28433            --  Do not consider internally generated items
28434
28435            if not Comes_From_Source (Item_Id) then
28436               null;
28437
28438            --  A visible state has been found
28439
28440            elsif Ekind_In (Item_Id, E_Abstract_State, E_Variable) then
28441               return True;
28442
28443            --  Recursively peek into nested packages and instantiations
28444
28445            elsif Ekind (Item_Id) = E_Package
28446              and then Has_Visible_State (Item_Id)
28447            then
28448               return True;
28449            end if;
28450
28451            Next_Entity (Item_Id);
28452         end loop;
28453
28454         return False;
28455      end Has_Visible_State;
28456
28457      --  Local variables
28458
28459      Pack_Id   : Entity_Id;
28460      Placement : State_Space_Kind;
28461
28462   --  Start of processing for Check_Missing_Part_Of
28463
28464   begin
28465      --  Do not consider abstract states, variables or package instantiations
28466      --  coming from an instance as those always inherit the Part_Of indicator
28467      --  of the instance itself.
28468
28469      if In_Instance then
28470         return;
28471
28472      --  Do not consider internally generated entities as these can never
28473      --  have a Part_Of indicator.
28474
28475      elsif not Comes_From_Source (Item_Id) then
28476         return;
28477
28478      --  Perform these checks only when SPARK_Mode is enabled as they will
28479      --  interfere with standard Ada rules and produce false positives.
28480
28481      elsif SPARK_Mode /= On then
28482         return;
28483
28484      --  Do not consider constants, because the compiler cannot accurately
28485      --  determine whether they have variable input (SPARK RM 7.1.1(2)) and
28486      --  act as a hidden state of a package.
28487
28488      elsif Ekind (Item_Id) = E_Constant then
28489         return;
28490      end if;
28491
28492      --  Find where the abstract state, variable or package instantiation
28493      --  lives with respect to the state space.
28494
28495      Find_Placement_In_State_Space
28496        (Item_Id   => Item_Id,
28497         Placement => Placement,
28498         Pack_Id   => Pack_Id);
28499
28500      --  Items that appear in a non-package construct (subprogram, block, etc)
28501      --  do not require a Part_Of indicator because they can never act as a
28502      --  hidden state.
28503
28504      if Placement = Not_In_Package then
28505         null;
28506
28507      --  An item declared in the body state space of a package always act as a
28508      --  constituent and does not need explicit Part_Of indicator.
28509
28510      elsif Placement = Body_State_Space then
28511         null;
28512
28513      --  In general an item declared in the visible state space of a package
28514      --  does not require a Part_Of indicator. The only exception is when the
28515      --  related package is a private child unit in which case Part_Of must
28516      --  denote a state in the parent unit or in one of its descendants.
28517
28518      elsif Placement = Visible_State_Space then
28519         if Is_Child_Unit (Pack_Id)
28520           and then Is_Private_Descendant (Pack_Id)
28521         then
28522            --  A package instantiation does not need a Part_Of indicator when
28523            --  the related generic template has no visible state.
28524
28525            if Ekind (Item_Id) = E_Package
28526              and then Is_Generic_Instance (Item_Id)
28527              and then not Has_Visible_State (Item_Id)
28528            then
28529               null;
28530
28531            --  All other cases require Part_Of
28532
28533            else
28534               Error_Msg_N
28535                 ("indicator Part_Of is required in this context "
28536                  & "(SPARK RM 7.2.6(3))", Item_Id);
28537               Error_Msg_Name_1 := Chars (Pack_Id);
28538               Error_Msg_N
28539                 ("\& is declared in the visible part of private child "
28540                  & "unit %", Item_Id);
28541            end if;
28542         end if;
28543
28544      --  When the item appears in the private state space of a package, it
28545      --  must be a part of some state declared by the said package.
28546
28547      else pragma Assert (Placement = Private_State_Space);
28548
28549         --  The related package does not declare a state, the item cannot act
28550         --  as a Part_Of constituent.
28551
28552         if No (Get_Pragma (Pack_Id, Pragma_Abstract_State)) then
28553            null;
28554
28555         --  A package instantiation does not need a Part_Of indicator when the
28556         --  related generic template has no visible state.
28557
28558         elsif Ekind (Pack_Id) = E_Package
28559           and then Is_Generic_Instance (Pack_Id)
28560           and then not Has_Visible_State (Pack_Id)
28561         then
28562            null;
28563
28564         --  All other cases require Part_Of
28565
28566         else
28567            Error_Msg_N
28568              ("indicator Part_Of is required in this context "
28569               & "(SPARK RM 7.2.6(2))", Item_Id);
28570            Error_Msg_Name_1 := Chars (Pack_Id);
28571            Error_Msg_N
28572              ("\& is declared in the private part of package %", Item_Id);
28573         end if;
28574      end if;
28575   end Check_Missing_Part_Of;
28576
28577   ---------------------------------------------------
28578   -- Check_Postcondition_Use_In_Inlined_Subprogram --
28579   ---------------------------------------------------
28580
28581   procedure Check_Postcondition_Use_In_Inlined_Subprogram
28582     (Prag    : Node_Id;
28583      Spec_Id : Entity_Id)
28584   is
28585   begin
28586      if Warn_On_Redundant_Constructs
28587        and then Has_Pragma_Inline_Always (Spec_Id)
28588        and then Assertions_Enabled
28589      then
28590         Error_Msg_Name_1 := Original_Aspect_Pragma_Name (Prag);
28591
28592         if From_Aspect_Specification (Prag) then
28593            Error_Msg_NE
28594              ("aspect % not enforced on inlined subprogram &?r?",
28595               Corresponding_Aspect (Prag), Spec_Id);
28596         else
28597            Error_Msg_NE
28598              ("pragma % not enforced on inlined subprogram &?r?",
28599               Prag, Spec_Id);
28600         end if;
28601      end if;
28602   end Check_Postcondition_Use_In_Inlined_Subprogram;
28603
28604   -------------------------------------
28605   -- Check_State_And_Constituent_Use --
28606   -------------------------------------
28607
28608   procedure Check_State_And_Constituent_Use
28609     (States   : Elist_Id;
28610      Constits : Elist_Id;
28611      Context  : Node_Id)
28612   is
28613      Constit_Elmt : Elmt_Id;
28614      Constit_Id   : Entity_Id;
28615      State_Id     : Entity_Id;
28616
28617   begin
28618      --  Nothing to do if there are no states or constituents
28619
28620      if No (States) or else No (Constits) then
28621         return;
28622      end if;
28623
28624      --  Inspect the list of constituents and try to determine whether its
28625      --  encapsulating state is in list States.
28626
28627      Constit_Elmt := First_Elmt (Constits);
28628      while Present (Constit_Elmt) loop
28629         Constit_Id := Node (Constit_Elmt);
28630
28631         --  Determine whether the constituent is part of an encapsulating
28632         --  state that appears in the same context and if this is the case,
28633         --  emit an error (SPARK RM 7.2.6(7)).
28634
28635         State_Id := Find_Encapsulating_State (States, Constit_Id);
28636
28637         if Present (State_Id) then
28638            Error_Msg_Name_1 := Chars (Constit_Id);
28639            SPARK_Msg_NE
28640              ("cannot mention state & and its constituent % in the same "
28641               & "context", Context, State_Id);
28642            exit;
28643         end if;
28644
28645         Next_Elmt (Constit_Elmt);
28646      end loop;
28647   end Check_State_And_Constituent_Use;
28648
28649   ---------------------------------------------
28650   -- Collect_Inherited_Class_Wide_Conditions --
28651   ---------------------------------------------
28652
28653   procedure Collect_Inherited_Class_Wide_Conditions (Subp : Entity_Id) is
28654      Parent_Subp : constant Entity_Id :=
28655                      Ultimate_Alias (Overridden_Operation (Subp));
28656      --  The Overridden_Operation may itself be inherited and as such have no
28657      --  explicit contract.
28658
28659      Prags        : constant Node_Id := Contract (Parent_Subp);
28660      In_Spec_Expr : Boolean;
28661      Installed    : Boolean;
28662      Prag         : Node_Id;
28663      New_Prag     : Node_Id;
28664
28665   begin
28666      Installed := False;
28667
28668      --  Iterate over the contract of the overridden subprogram to find all
28669      --  inherited class-wide pre- and postconditions.
28670
28671      if Present (Prags) then
28672         Prag := Pre_Post_Conditions (Prags);
28673
28674         while Present (Prag) loop
28675            if Nam_In (Pragma_Name_Unmapped (Prag),
28676                       Name_Precondition, Name_Postcondition)
28677              and then Class_Present (Prag)
28678            then
28679               --  The generated pragma must be analyzed in the context of
28680               --  the subprogram, to make its formals visible. In addition,
28681               --  we must inhibit freezing and full analysis because the
28682               --  controlling type of the subprogram is not frozen yet, and
28683               --  may have further primitives.
28684
28685               if not Installed then
28686                  Installed := True;
28687                  Push_Scope (Subp);
28688                  Install_Formals (Subp);
28689                  In_Spec_Expr := In_Spec_Expression;
28690                  In_Spec_Expression := True;
28691               end if;
28692
28693               New_Prag :=
28694                 Build_Pragma_Check_Equivalent
28695                   (Prag, Subp, Parent_Subp, Keep_Pragma_Id => True);
28696
28697               Insert_After (Unit_Declaration_Node (Subp), New_Prag);
28698               Preanalyze (New_Prag);
28699
28700               --  Prevent further analysis in subsequent processing of the
28701               --  current list of declarations
28702
28703               Set_Analyzed (New_Prag);
28704            end if;
28705
28706            Prag := Next_Pragma (Prag);
28707         end loop;
28708
28709         if Installed then
28710            In_Spec_Expression := In_Spec_Expr;
28711            End_Scope;
28712         end if;
28713      end if;
28714   end Collect_Inherited_Class_Wide_Conditions;
28715
28716   ---------------------------------------
28717   -- Collect_Subprogram_Inputs_Outputs --
28718   ---------------------------------------
28719
28720   procedure Collect_Subprogram_Inputs_Outputs
28721     (Subp_Id      : Entity_Id;
28722      Synthesize   : Boolean := False;
28723      Subp_Inputs  : in out Elist_Id;
28724      Subp_Outputs : in out Elist_Id;
28725      Global_Seen  : out Boolean)
28726   is
28727      procedure Collect_Dependency_Clause (Clause : Node_Id);
28728      --  Collect all relevant items from a dependency clause
28729
28730      procedure Collect_Global_List
28731        (List : Node_Id;
28732         Mode : Name_Id := Name_Input);
28733      --  Collect all relevant items from a global list
28734
28735      -------------------------------
28736      -- Collect_Dependency_Clause --
28737      -------------------------------
28738
28739      procedure Collect_Dependency_Clause (Clause : Node_Id) is
28740         procedure Collect_Dependency_Item
28741           (Item     : Node_Id;
28742            Is_Input : Boolean);
28743         --  Add an item to the proper subprogram input or output collection
28744
28745         -----------------------------
28746         -- Collect_Dependency_Item --
28747         -----------------------------
28748
28749         procedure Collect_Dependency_Item
28750           (Item     : Node_Id;
28751            Is_Input : Boolean)
28752         is
28753            Extra : Node_Id;
28754
28755         begin
28756            --  Nothing to collect when the item is null
28757
28758            if Nkind (Item) = N_Null then
28759               null;
28760
28761            --  Ditto for attribute 'Result
28762
28763            elsif Is_Attribute_Result (Item) then
28764               null;
28765
28766            --  Multiple items appear as an aggregate
28767
28768            elsif Nkind (Item) = N_Aggregate then
28769               Extra := First (Expressions (Item));
28770               while Present (Extra) loop
28771                  Collect_Dependency_Item (Extra, Is_Input);
28772                  Next (Extra);
28773               end loop;
28774
28775            --  Otherwise this is a solitary item
28776
28777            else
28778               if Is_Input then
28779                  Append_New_Elmt (Item, Subp_Inputs);
28780               else
28781                  Append_New_Elmt (Item, Subp_Outputs);
28782               end if;
28783            end if;
28784         end Collect_Dependency_Item;
28785
28786      --  Start of processing for Collect_Dependency_Clause
28787
28788      begin
28789         if Nkind (Clause) = N_Null then
28790            null;
28791
28792         --  A dependency clause appears as component association
28793
28794         elsif Nkind (Clause) = N_Component_Association then
28795            Collect_Dependency_Item
28796              (Item     => Expression (Clause),
28797               Is_Input => True);
28798
28799            Collect_Dependency_Item
28800              (Item     => First (Choices (Clause)),
28801               Is_Input => False);
28802
28803         --  To accommodate partial decoration of disabled SPARK features, this
28804         --  routine may be called with illegal input. If this is the case, do
28805         --  not raise Program_Error.
28806
28807         else
28808            null;
28809         end if;
28810      end Collect_Dependency_Clause;
28811
28812      -------------------------
28813      -- Collect_Global_List --
28814      -------------------------
28815
28816      procedure Collect_Global_List
28817        (List : Node_Id;
28818         Mode : Name_Id := Name_Input)
28819      is
28820         procedure Collect_Global_Item (Item : Node_Id; Mode : Name_Id);
28821         --  Add an item to the proper subprogram input or output collection
28822
28823         -------------------------
28824         -- Collect_Global_Item --
28825         -------------------------
28826
28827         procedure Collect_Global_Item (Item : Node_Id; Mode : Name_Id) is
28828         begin
28829            if Nam_In (Mode, Name_In_Out, Name_Input) then
28830               Append_New_Elmt (Item, Subp_Inputs);
28831            end if;
28832
28833            if Nam_In (Mode, Name_In_Out, Name_Output) then
28834               Append_New_Elmt (Item, Subp_Outputs);
28835            end if;
28836         end Collect_Global_Item;
28837
28838         --  Local variables
28839
28840         Assoc : Node_Id;
28841         Item  : Node_Id;
28842
28843      --  Start of processing for Collect_Global_List
28844
28845      begin
28846         if Nkind (List) = N_Null then
28847            null;
28848
28849         --  Single global item declaration
28850
28851         elsif Nkind_In (List, N_Expanded_Name,
28852                               N_Identifier,
28853                               N_Selected_Component)
28854         then
28855            Collect_Global_Item (List, Mode);
28856
28857         --  Simple global list or moded global list declaration
28858
28859         elsif Nkind (List) = N_Aggregate then
28860            if Present (Expressions (List)) then
28861               Item := First (Expressions (List));
28862               while Present (Item) loop
28863                  Collect_Global_Item (Item, Mode);
28864                  Next (Item);
28865               end loop;
28866
28867            else
28868               Assoc := First (Component_Associations (List));
28869               while Present (Assoc) loop
28870                  Collect_Global_List
28871                    (List => Expression (Assoc),
28872                     Mode => Chars (First (Choices (Assoc))));
28873                  Next (Assoc);
28874               end loop;
28875            end if;
28876
28877         --  To accommodate partial decoration of disabled SPARK features, this
28878         --  routine may be called with illegal input. If this is the case, do
28879         --  not raise Program_Error.
28880
28881         else
28882            null;
28883         end if;
28884      end Collect_Global_List;
28885
28886      --  Local variables
28887
28888      Clause    : Node_Id;
28889      Clauses   : Node_Id;
28890      Depends   : Node_Id;
28891      Formal    : Entity_Id;
28892      Global    : Node_Id;
28893      Spec_Id   : Entity_Id := Empty;
28894      Subp_Decl : Node_Id;
28895      Typ       : Entity_Id;
28896
28897   --  Start of processing for Collect_Subprogram_Inputs_Outputs
28898
28899   begin
28900      Global_Seen := False;
28901
28902      --  Process all formal parameters of entries, [generic] subprograms, and
28903      --  their bodies.
28904
28905      if Ekind_In (Subp_Id, E_Entry,
28906                            E_Entry_Family,
28907                            E_Function,
28908                            E_Generic_Function,
28909                            E_Generic_Procedure,
28910                            E_Procedure,
28911                            E_Subprogram_Body)
28912      then
28913         Subp_Decl := Unit_Declaration_Node (Subp_Id);
28914         Spec_Id   := Unique_Defining_Entity (Subp_Decl);
28915
28916         --  Process all formal parameters
28917
28918         Formal := First_Entity (Spec_Id);
28919         while Present (Formal) loop
28920            if Ekind_In (Formal, E_In_Out_Parameter, E_In_Parameter) then
28921               Append_New_Elmt (Formal, Subp_Inputs);
28922            end if;
28923
28924            if Ekind_In (Formal, E_In_Out_Parameter, E_Out_Parameter) then
28925               Append_New_Elmt (Formal, Subp_Outputs);
28926
28927               --  Out parameters can act as inputs when the related type is
28928               --  tagged, unconstrained array, unconstrained record, or record
28929               --  with unconstrained components.
28930
28931               if Ekind (Formal) = E_Out_Parameter
28932                 and then Is_Unconstrained_Or_Tagged_Item (Formal)
28933               then
28934                  Append_New_Elmt (Formal, Subp_Inputs);
28935               end if;
28936            end if;
28937
28938            Next_Entity (Formal);
28939         end loop;
28940
28941      --  Otherwise the input denotes a task type, a task body, or the
28942      --  anonymous object created for a single task type.
28943
28944      elsif Ekind_In (Subp_Id, E_Task_Type, E_Task_Body)
28945        or else Is_Single_Task_Object (Subp_Id)
28946      then
28947         Subp_Decl := Declaration_Node (Subp_Id);
28948         Spec_Id   := Unique_Defining_Entity (Subp_Decl);
28949      end if;
28950
28951      --  When processing an entry, subprogram or task body, look for pragmas
28952      --  Refined_Depends and Refined_Global as they specify the inputs and
28953      --  outputs.
28954
28955      if Is_Entry_Body (Subp_Id)
28956        or else Ekind_In (Subp_Id, E_Subprogram_Body, E_Task_Body)
28957      then
28958         Depends := Get_Pragma (Subp_Id, Pragma_Refined_Depends);
28959         Global  := Get_Pragma (Subp_Id, Pragma_Refined_Global);
28960
28961      --  Subprogram declaration or stand-alone body case, look for pragmas
28962      --  Depends and Global
28963
28964      else
28965         Depends := Get_Pragma (Spec_Id, Pragma_Depends);
28966         Global  := Get_Pragma (Spec_Id, Pragma_Global);
28967      end if;
28968
28969      --  Pragma [Refined_]Global takes precedence over [Refined_]Depends
28970      --  because it provides finer granularity of inputs and outputs.
28971
28972      if Present (Global) then
28973         Global_Seen := True;
28974         Collect_Global_List (Expression (Get_Argument (Global, Spec_Id)));
28975
28976      --  When the related subprogram lacks pragma [Refined_]Global, fall back
28977      --  to [Refined_]Depends if the caller requests this behavior. Synthesize
28978      --  the inputs and outputs from [Refined_]Depends.
28979
28980      elsif Synthesize and then Present (Depends) then
28981         Clauses := Expression (Get_Argument (Depends, Spec_Id));
28982
28983         --  Multiple dependency clauses appear as an aggregate
28984
28985         if Nkind (Clauses) = N_Aggregate then
28986            Clause := First (Component_Associations (Clauses));
28987            while Present (Clause) loop
28988               Collect_Dependency_Clause (Clause);
28989               Next (Clause);
28990            end loop;
28991
28992         --  Otherwise this is a single dependency clause
28993
28994         else
28995            Collect_Dependency_Clause (Clauses);
28996         end if;
28997      end if;
28998
28999      --  The current instance of a protected type acts as a formal parameter
29000      --  of mode IN for functions and IN OUT for entries and procedures
29001      --  (SPARK RM 6.1.4).
29002
29003      if Ekind (Scope (Spec_Id)) = E_Protected_Type then
29004         Typ := Scope (Spec_Id);
29005
29006         --  Use the anonymous object when the type is single protected
29007
29008         if Is_Single_Concurrent_Type_Declaration (Declaration_Node (Typ)) then
29009            Typ := Anonymous_Object (Typ);
29010         end if;
29011
29012         Append_New_Elmt (Typ, Subp_Inputs);
29013
29014         if Ekind_In (Spec_Id, E_Entry, E_Entry_Family, E_Procedure) then
29015            Append_New_Elmt (Typ, Subp_Outputs);
29016         end if;
29017
29018      --  The current instance of a task type acts as a formal parameter of
29019      --  mode IN OUT (SPARK RM 6.1.4).
29020
29021      elsif Ekind (Spec_Id) = E_Task_Type then
29022         Typ := Spec_Id;
29023
29024         --  Use the anonymous object when the type is single task
29025
29026         if Is_Single_Concurrent_Type_Declaration (Declaration_Node (Typ)) then
29027            Typ := Anonymous_Object (Typ);
29028         end if;
29029
29030         Append_New_Elmt (Typ, Subp_Inputs);
29031         Append_New_Elmt (Typ, Subp_Outputs);
29032
29033      elsif Is_Single_Task_Object (Spec_Id) then
29034         Append_New_Elmt (Spec_Id, Subp_Inputs);
29035         Append_New_Elmt (Spec_Id, Subp_Outputs);
29036      end if;
29037   end Collect_Subprogram_Inputs_Outputs;
29038
29039   ---------------------------
29040   -- Contract_Freeze_Error --
29041   ---------------------------
29042
29043   procedure Contract_Freeze_Error
29044     (Contract_Id : Entity_Id;
29045      Freeze_Id   : Entity_Id)
29046   is
29047   begin
29048      Error_Msg_Name_1 := Chars (Contract_Id);
29049      Error_Msg_Sloc   := Sloc (Freeze_Id);
29050
29051      SPARK_Msg_NE
29052        ("body & declared # freezes the contract of%", Contract_Id, Freeze_Id);
29053      SPARK_Msg_N
29054        ("\all contractual items must be declared before body #", Contract_Id);
29055   end Contract_Freeze_Error;
29056
29057   ---------------------------------
29058   -- Delay_Config_Pragma_Analyze --
29059   ---------------------------------
29060
29061   function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
29062   begin
29063      return Nam_In (Pragma_Name_Unmapped (N),
29064                     Name_Interrupt_State, Name_Priority_Specific_Dispatching);
29065   end Delay_Config_Pragma_Analyze;
29066
29067   -----------------------
29068   -- Duplication_Error --
29069   -----------------------
29070
29071   procedure Duplication_Error (Prag : Node_Id; Prev : Node_Id) is
29072      Prag_From_Asp : constant Boolean := From_Aspect_Specification (Prag);
29073      Prev_From_Asp : constant Boolean := From_Aspect_Specification (Prev);
29074
29075   begin
29076      Error_Msg_Sloc   := Sloc (Prev);
29077      Error_Msg_Name_1 := Original_Aspect_Pragma_Name (Prag);
29078
29079      --  Emit a precise message to distinguish between source pragmas and
29080      --  pragmas generated from aspects. The ordering of the two pragmas is
29081      --  the following:
29082
29083      --    Prev  --  ok
29084      --    Prag  --  duplicate
29085
29086      --  No error is emitted when both pragmas come from aspects because this
29087      --  is already detected by the general aspect analysis mechanism.
29088
29089      if Prag_From_Asp and Prev_From_Asp then
29090         null;
29091      elsif Prag_From_Asp then
29092         Error_Msg_N ("aspect % duplicates pragma declared #", Prag);
29093      elsif Prev_From_Asp then
29094         Error_Msg_N ("pragma % duplicates aspect declared #", Prag);
29095      else
29096         Error_Msg_N ("pragma % duplicates pragma declared #", Prag);
29097      end if;
29098   end Duplication_Error;
29099
29100   ------------------------------
29101   -- Find_Encapsulating_State --
29102   ------------------------------
29103
29104   function Find_Encapsulating_State
29105     (States     : Elist_Id;
29106      Constit_Id : Entity_Id) return Entity_Id
29107   is
29108      State_Id : Entity_Id;
29109
29110   begin
29111      --  Since a constituent may be part of a larger constituent set, climb
29112      --  the encapsulating state chain looking for a state that appears in
29113      --  States.
29114
29115      State_Id := Encapsulating_State (Constit_Id);
29116      while Present (State_Id) loop
29117         if Contains (States, State_Id) then
29118            return State_Id;
29119         end if;
29120
29121         State_Id := Encapsulating_State (State_Id);
29122      end loop;
29123
29124      return Empty;
29125   end Find_Encapsulating_State;
29126
29127   --------------------------
29128   -- Find_Related_Context --
29129   --------------------------
29130
29131   function Find_Related_Context
29132     (Prag      : Node_Id;
29133      Do_Checks : Boolean := False) return Node_Id
29134   is
29135      Stmt : Node_Id;
29136
29137   begin
29138      Stmt := Prev (Prag);
29139      while Present (Stmt) loop
29140
29141         --  Skip prior pragmas, but check for duplicates
29142
29143         if Nkind (Stmt) = N_Pragma then
29144            if Do_Checks
29145              and then Pragma_Name (Stmt) = Pragma_Name (Prag)
29146            then
29147               Duplication_Error
29148                 (Prag => Prag,
29149                  Prev => Stmt);
29150            end if;
29151
29152         --  Skip internally generated code
29153
29154         elsif not Comes_From_Source (Stmt) then
29155
29156            --  The anonymous object created for a single concurrent type is a
29157            --  suitable context.
29158
29159            if Nkind (Stmt) = N_Object_Declaration
29160              and then Is_Single_Concurrent_Object (Defining_Entity (Stmt))
29161            then
29162               return Stmt;
29163            end if;
29164
29165         --  Return the current source construct
29166
29167         else
29168            return Stmt;
29169         end if;
29170
29171         Prev (Stmt);
29172      end loop;
29173
29174      return Empty;
29175   end Find_Related_Context;
29176
29177   --------------------------------------
29178   -- Find_Related_Declaration_Or_Body --
29179   --------------------------------------
29180
29181   function Find_Related_Declaration_Or_Body
29182     (Prag      : Node_Id;
29183      Do_Checks : Boolean := False) return Node_Id
29184   is
29185      Prag_Nam : constant Name_Id := Original_Aspect_Pragma_Name (Prag);
29186
29187      procedure Expression_Function_Error;
29188      --  Emit an error concerning pragma Prag that illegaly applies to an
29189      --  expression function.
29190
29191      -------------------------------
29192      -- Expression_Function_Error --
29193      -------------------------------
29194
29195      procedure Expression_Function_Error is
29196      begin
29197         Error_Msg_Name_1 := Prag_Nam;
29198
29199         --  Emit a precise message to distinguish between source pragmas and
29200         --  pragmas generated from aspects.
29201
29202         if From_Aspect_Specification (Prag) then
29203            Error_Msg_N
29204              ("aspect % cannot apply to a stand alone expression function",
29205               Prag);
29206         else
29207            Error_Msg_N
29208              ("pragma % cannot apply to a stand alone expression function",
29209               Prag);
29210         end if;
29211      end Expression_Function_Error;
29212
29213      --  Local variables
29214
29215      Context : constant Node_Id := Parent (Prag);
29216      Stmt    : Node_Id;
29217
29218      Look_For_Body : constant Boolean :=
29219                        Nam_In (Prag_Nam, Name_Refined_Depends,
29220                                          Name_Refined_Global,
29221                                          Name_Refined_Post,
29222                                          Name_Refined_State);
29223      --  Refinement pragmas must be associated with a subprogram body [stub]
29224
29225   --  Start of processing for Find_Related_Declaration_Or_Body
29226
29227   begin
29228      Stmt := Prev (Prag);
29229      while Present (Stmt) loop
29230
29231         --  Skip prior pragmas, but check for duplicates. Pragmas produced
29232         --  by splitting a complex pre/postcondition are not considered to
29233         --  be duplicates.
29234
29235         if Nkind (Stmt) = N_Pragma then
29236            if Do_Checks
29237              and then not Split_PPC (Stmt)
29238              and then Original_Aspect_Pragma_Name (Stmt) = Prag_Nam
29239            then
29240               Duplication_Error
29241                 (Prag => Prag,
29242                  Prev => Stmt);
29243            end if;
29244
29245         --  Emit an error when a refinement pragma appears on an expression
29246         --  function without a completion.
29247
29248         elsif Do_Checks
29249           and then Look_For_Body
29250           and then Nkind (Stmt) = N_Subprogram_Declaration
29251           and then Nkind (Original_Node (Stmt)) = N_Expression_Function
29252           and then not Has_Completion (Defining_Entity (Stmt))
29253         then
29254            Expression_Function_Error;
29255            return Empty;
29256
29257         --  The refinement pragma applies to a subprogram body stub
29258
29259         elsif Look_For_Body
29260           and then Nkind (Stmt) = N_Subprogram_Body_Stub
29261         then
29262            return Stmt;
29263
29264         --  Skip internally generated code
29265
29266         elsif not Comes_From_Source (Stmt) then
29267
29268            --  The anonymous object created for a single concurrent type is a
29269            --  suitable context.
29270
29271            if Nkind (Stmt) = N_Object_Declaration
29272              and then Is_Single_Concurrent_Object (Defining_Entity (Stmt))
29273            then
29274               return Stmt;
29275
29276            elsif Nkind (Stmt) = N_Subprogram_Declaration then
29277
29278               --  The subprogram declaration is an internally generated spec
29279               --  for an expression function.
29280
29281               if Nkind (Original_Node (Stmt)) = N_Expression_Function then
29282                  return Stmt;
29283
29284               --  The subprogram is actually an instance housed within an
29285               --  anonymous wrapper package.
29286
29287               elsif Present (Generic_Parent (Specification (Stmt))) then
29288                  return Stmt;
29289               end if;
29290            end if;
29291
29292         --  Return the current construct which is either a subprogram body,
29293         --  a subprogram declaration or is illegal.
29294
29295         else
29296            return Stmt;
29297         end if;
29298
29299         Prev (Stmt);
29300      end loop;
29301
29302      --  If we fall through, then the pragma was either the first declaration
29303      --  or it was preceded by other pragmas and no source constructs.
29304
29305      --  The pragma is associated with a library-level subprogram
29306
29307      if Nkind (Context) = N_Compilation_Unit_Aux then
29308         return Unit (Parent (Context));
29309
29310      --  The pragma appears inside the declarations of an entry body
29311
29312      elsif Nkind (Context) = N_Entry_Body then
29313         return Context;
29314
29315      --  The pragma appears inside the statements of a subprogram body. This
29316      --  placement is the result of subprogram contract expansion.
29317
29318      elsif Nkind (Context) = N_Handled_Sequence_Of_Statements then
29319         return Parent (Context);
29320
29321      --  The pragma appears inside the declarative part of a package body
29322
29323      elsif Nkind (Context) = N_Package_Body then
29324         return Context;
29325
29326      --  The pragma appears inside the declarative part of a subprogram body
29327
29328      elsif Nkind (Context) = N_Subprogram_Body then
29329         return Context;
29330
29331      --  The pragma appears inside the declarative part of a task body
29332
29333      elsif Nkind (Context) = N_Task_Body then
29334         return Context;
29335
29336      --  The pragma appears inside the visible part of a package specification
29337
29338      elsif Nkind (Context) = N_Package_Specification then
29339         return Parent (Context);
29340
29341      --  The pragma is a byproduct of aspect expansion, return the related
29342      --  context of the original aspect. This case has a lower priority as
29343      --  the above circuitry pinpoints precisely the related context.
29344
29345      elsif Present (Corresponding_Aspect (Prag)) then
29346         return Parent (Corresponding_Aspect (Prag));
29347
29348      --  No candidate subprogram [body] found
29349
29350      else
29351         return Empty;
29352      end if;
29353   end Find_Related_Declaration_Or_Body;
29354
29355   ----------------------------------
29356   -- Find_Related_Package_Or_Body --
29357   ----------------------------------
29358
29359   function Find_Related_Package_Or_Body
29360     (Prag      : Node_Id;
29361      Do_Checks : Boolean := False) return Node_Id
29362   is
29363      Context  : constant Node_Id := Parent (Prag);
29364      Prag_Nam : constant Name_Id := Pragma_Name (Prag);
29365      Stmt     : Node_Id;
29366
29367   begin
29368      Stmt := Prev (Prag);
29369      while Present (Stmt) loop
29370
29371         --  Skip prior pragmas, but check for duplicates
29372
29373         if Nkind (Stmt) = N_Pragma then
29374            if Do_Checks and then Pragma_Name (Stmt) = Prag_Nam then
29375               Duplication_Error
29376                 (Prag => Prag,
29377                  Prev => Stmt);
29378            end if;
29379
29380         --  Skip internally generated code
29381
29382         elsif not Comes_From_Source (Stmt) then
29383            if Nkind (Stmt) = N_Subprogram_Declaration then
29384
29385               --  The subprogram declaration is an internally generated spec
29386               --  for an expression function.
29387
29388               if Nkind (Original_Node (Stmt)) = N_Expression_Function then
29389                  return Stmt;
29390
29391               --  The subprogram is actually an instance housed within an
29392               --  anonymous wrapper package.
29393
29394               elsif Present (Generic_Parent (Specification (Stmt))) then
29395                  return Stmt;
29396               end if;
29397            end if;
29398
29399         --  Return the current source construct which is illegal
29400
29401         else
29402            return Stmt;
29403         end if;
29404
29405         Prev (Stmt);
29406      end loop;
29407
29408      --  If we fall through, then the pragma was either the first declaration
29409      --  or it was preceded by other pragmas and no source constructs.
29410
29411      --  The pragma is associated with a package. The immediate context in
29412      --  this case is the specification of the package.
29413
29414      if Nkind (Context) = N_Package_Specification then
29415         return Parent (Context);
29416
29417      --  The pragma appears in the declarations of a package body
29418
29419      elsif Nkind (Context) = N_Package_Body then
29420         return Context;
29421
29422      --  The pragma appears in the statements of a package body
29423
29424      elsif Nkind (Context) = N_Handled_Sequence_Of_Statements
29425        and then Nkind (Parent (Context)) = N_Package_Body
29426      then
29427         return Parent (Context);
29428
29429      --  The pragma is a byproduct of aspect expansion, return the related
29430      --  context of the original aspect. This case has a lower priority as
29431      --  the above circuitry pinpoints precisely the related context.
29432
29433      elsif Present (Corresponding_Aspect (Prag)) then
29434         return Parent (Corresponding_Aspect (Prag));
29435
29436      --  No candidate package [body] found
29437
29438      else
29439         return Empty;
29440      end if;
29441   end Find_Related_Package_Or_Body;
29442
29443   ------------------
29444   -- Get_Argument --
29445   ------------------
29446
29447   function Get_Argument
29448     (Prag       : Node_Id;
29449      Context_Id : Entity_Id := Empty) return Node_Id
29450   is
29451      Args : constant List_Id := Pragma_Argument_Associations (Prag);
29452
29453   begin
29454      --  Use the expression of the original aspect when compiling for ASIS or
29455      --  when analyzing the template of a generic unit. In both cases the
29456      --  aspect's tree must be decorated to allow for ASIS queries or to save
29457      --  the global references in the generic context.
29458
29459      if From_Aspect_Specification (Prag)
29460        and then (ASIS_Mode or else (Present (Context_Id)
29461                                      and then Is_Generic_Unit (Context_Id)))
29462      then
29463         return Corresponding_Aspect (Prag);
29464
29465      --  Otherwise use the expression of the pragma
29466
29467      elsif Present (Args) then
29468         return First (Args);
29469
29470      else
29471         return Empty;
29472      end if;
29473   end Get_Argument;
29474
29475   -------------------------
29476   -- Get_Base_Subprogram --
29477   -------------------------
29478
29479   function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
29480      Result : Entity_Id;
29481
29482   begin
29483      --  Follow subprogram renaming chain
29484
29485      Result := Def_Id;
29486
29487      if Is_Subprogram (Result)
29488        and then
29489          Nkind (Parent (Declaration_Node (Result))) =
29490                                         N_Subprogram_Renaming_Declaration
29491        and then Present (Alias (Result))
29492      then
29493         Result := Alias (Result);
29494      end if;
29495
29496      return Result;
29497   end Get_Base_Subprogram;
29498
29499   -----------------------
29500   -- Get_SPARK_Mode_Type --
29501   -----------------------
29502
29503   function Get_SPARK_Mode_Type (N : Name_Id) return SPARK_Mode_Type is
29504   begin
29505      if N = Name_On then
29506         return On;
29507      elsif N = Name_Off then
29508         return Off;
29509
29510      --  Any other argument is illegal. Assume that no SPARK mode applies to
29511      --  avoid potential cascaded errors.
29512
29513      else
29514         return None;
29515      end if;
29516   end Get_SPARK_Mode_Type;
29517
29518   ------------------------------------
29519   -- Get_SPARK_Mode_From_Annotation --
29520   ------------------------------------
29521
29522   function Get_SPARK_Mode_From_Annotation
29523     (N : Node_Id) return SPARK_Mode_Type
29524   is
29525      Mode : Node_Id;
29526
29527   begin
29528      if Nkind (N) = N_Aspect_Specification then
29529         Mode := Expression (N);
29530
29531      else pragma Assert (Nkind (N) = N_Pragma);
29532         Mode := First (Pragma_Argument_Associations (N));
29533
29534         if Present (Mode) then
29535            Mode := Get_Pragma_Arg (Mode);
29536         end if;
29537      end if;
29538
29539      --  Aspect or pragma SPARK_Mode specifies an explicit mode
29540
29541      if Present (Mode) then
29542         if Nkind (Mode) = N_Identifier then
29543            return Get_SPARK_Mode_Type (Chars (Mode));
29544
29545         --  In case of a malformed aspect or pragma, return the default None
29546
29547         else
29548            return None;
29549         end if;
29550
29551      --  Otherwise the lack of an expression defaults SPARK_Mode to On
29552
29553      else
29554         return On;
29555      end if;
29556   end Get_SPARK_Mode_From_Annotation;
29557
29558   ---------------------------
29559   -- Has_Extra_Parentheses --
29560   ---------------------------
29561
29562   function Has_Extra_Parentheses (Clause : Node_Id) return Boolean is
29563      Expr : Node_Id;
29564
29565   begin
29566      --  The aggregate should not have an expression list because a clause
29567      --  is always interpreted as a component association. The only way an
29568      --  expression list can sneak in is by adding extra parentheses around
29569      --  the individual clauses:
29570
29571      --    Depends  (Output => Input)   --  proper form
29572      --    Depends ((Output => Input))  --  extra parentheses
29573
29574      --  Since the extra parentheses are not allowed by the syntax of the
29575      --  pragma, flag them now to avoid emitting misleading errors down the
29576      --  line.
29577
29578      if Nkind (Clause) = N_Aggregate
29579        and then Present (Expressions (Clause))
29580      then
29581         Expr := First (Expressions (Clause));
29582         while Present (Expr) loop
29583
29584            --  A dependency clause surrounded by extra parentheses appears
29585            --  as an aggregate of component associations with an optional
29586            --  Paren_Count set.
29587
29588            if Nkind (Expr) = N_Aggregate
29589              and then Present (Component_Associations (Expr))
29590            then
29591               SPARK_Msg_N
29592                 ("dependency clause contains extra parentheses", Expr);
29593
29594            --  Otherwise the expression is a malformed construct
29595
29596            else
29597               SPARK_Msg_N ("malformed dependency clause", Expr);
29598            end if;
29599
29600            Next (Expr);
29601         end loop;
29602
29603         return True;
29604      end if;
29605
29606      return False;
29607   end Has_Extra_Parentheses;
29608
29609   ----------------
29610   -- Initialize --
29611   ----------------
29612
29613   procedure Initialize is
29614   begin
29615      Externals.Init;
29616   end Initialize;
29617
29618   --------
29619   -- ip --
29620   --------
29621
29622   procedure ip is
29623   begin
29624      Dummy := Dummy + 1;
29625   end ip;
29626
29627   -----------------------------
29628   -- Is_Config_Static_String --
29629   -----------------------------
29630
29631   function Is_Config_Static_String (Arg : Node_Id) return Boolean is
29632
29633      function Add_Config_Static_String (Arg : Node_Id) return Boolean;
29634      --  This is an internal recursive function that is just like the outer
29635      --  function except that it adds the string to the name buffer rather
29636      --  than placing the string in the name buffer.
29637
29638      ------------------------------
29639      -- Add_Config_Static_String --
29640      ------------------------------
29641
29642      function Add_Config_Static_String (Arg : Node_Id) return Boolean is
29643         N : Node_Id;
29644         C : Char_Code;
29645
29646      begin
29647         N := Arg;
29648
29649         if Nkind (N) = N_Op_Concat then
29650            if Add_Config_Static_String (Left_Opnd (N)) then
29651               N := Right_Opnd (N);
29652            else
29653               return False;
29654            end if;
29655         end if;
29656
29657         if Nkind (N) /= N_String_Literal then
29658            Error_Msg_N ("string literal expected for pragma argument", N);
29659            return False;
29660
29661         else
29662            for J in 1 .. String_Length (Strval (N)) loop
29663               C := Get_String_Char (Strval (N), J);
29664
29665               if not In_Character_Range (C) then
29666                  Error_Msg
29667                    ("string literal contains invalid wide character",
29668                     Sloc (N) + 1 + Source_Ptr (J));
29669                  return False;
29670               end if;
29671
29672               Add_Char_To_Name_Buffer (Get_Character (C));
29673            end loop;
29674         end if;
29675
29676         return True;
29677      end Add_Config_Static_String;
29678
29679   --  Start of processing for Is_Config_Static_String
29680
29681   begin
29682      Name_Len := 0;
29683
29684      return Add_Config_Static_String (Arg);
29685   end Is_Config_Static_String;
29686
29687   -------------------------------
29688   -- Is_Elaboration_SPARK_Mode --
29689   -------------------------------
29690
29691   function Is_Elaboration_SPARK_Mode (N : Node_Id) return Boolean is
29692   begin
29693      pragma Assert
29694        (Nkind (N) = N_Pragma
29695          and then Pragma_Name (N) = Name_SPARK_Mode
29696          and then Is_List_Member (N));
29697
29698      --  Pragma SPARK_Mode affects the elaboration of a package body when it
29699      --  appears in the statement part of the body.
29700
29701      return
29702         Present (Parent (N))
29703           and then Nkind (Parent (N)) = N_Handled_Sequence_Of_Statements
29704           and then List_Containing (N) = Statements (Parent (N))
29705           and then Present (Parent (Parent (N)))
29706           and then Nkind (Parent (Parent (N))) = N_Package_Body;
29707   end Is_Elaboration_SPARK_Mode;
29708
29709   -----------------------
29710   -- Is_Enabled_Pragma --
29711   -----------------------
29712
29713   function Is_Enabled_Pragma (Prag : Node_Id) return Boolean is
29714      Arg : Node_Id;
29715
29716   begin
29717      if Present (Prag) then
29718         Arg := First (Pragma_Argument_Associations (Prag));
29719
29720         if Present (Arg) then
29721            return Is_True (Expr_Value (Get_Pragma_Arg (Arg)));
29722
29723         --  The lack of a Boolean argument automatically enables the pragma
29724
29725         else
29726            return True;
29727         end if;
29728
29729      --  The pragma is missing, therefore it is not enabled
29730
29731      else
29732         return False;
29733      end if;
29734   end Is_Enabled_Pragma;
29735
29736   -----------------------------------------
29737   -- Is_Non_Significant_Pragma_Reference --
29738   -----------------------------------------
29739
29740   --  This function makes use of the following static table which indicates
29741   --  whether appearance of some name in a given pragma is to be considered
29742   --  as a reference for the purposes of warnings about unreferenced objects.
29743
29744   --  -1  indicates that appearence in any argument is significant
29745   --  0   indicates that appearance in any argument is not significant
29746   --  +n  indicates that appearance as argument n is significant, but all
29747   --      other arguments are not significant
29748   --  9n  arguments from n on are significant, before n insignificant
29749
29750   Sig_Flags : constant array (Pragma_Id) of Int :=
29751     (Pragma_Abort_Defer                    => -1,
29752      Pragma_Abstract_State                 => -1,
29753      Pragma_Ada_83                         => -1,
29754      Pragma_Ada_95                         => -1,
29755      Pragma_Ada_05                         => -1,
29756      Pragma_Ada_2005                       => -1,
29757      Pragma_Ada_12                         => -1,
29758      Pragma_Ada_2012                       => -1,
29759      Pragma_Ada_2020                       => -1,
29760      Pragma_All_Calls_Remote               => -1,
29761      Pragma_Allow_Integer_Address          => -1,
29762      Pragma_Annotate                       => 93,
29763      Pragma_Assert                         => -1,
29764      Pragma_Assert_And_Cut                 => -1,
29765      Pragma_Assertion_Policy               =>  0,
29766      Pragma_Assume                         => -1,
29767      Pragma_Assume_No_Invalid_Values       =>  0,
29768      Pragma_Async_Readers                  =>  0,
29769      Pragma_Async_Writers                  =>  0,
29770      Pragma_Asynchronous                   =>  0,
29771      Pragma_Atomic                         =>  0,
29772      Pragma_Atomic_Components              =>  0,
29773      Pragma_Attach_Handler                 => -1,
29774      Pragma_Attribute_Definition           => 92,
29775      Pragma_Check                          => -1,
29776      Pragma_Check_Float_Overflow           =>  0,
29777      Pragma_Check_Name                     =>  0,
29778      Pragma_Check_Policy                   =>  0,
29779      Pragma_CPP_Class                      =>  0,
29780      Pragma_CPP_Constructor                =>  0,
29781      Pragma_CPP_Virtual                    =>  0,
29782      Pragma_CPP_Vtable                     =>  0,
29783      Pragma_CPU                            => -1,
29784      Pragma_C_Pass_By_Copy                 =>  0,
29785      Pragma_Comment                        => -1,
29786      Pragma_Common_Object                  =>  0,
29787      Pragma_Compile_Time_Error             => -1,
29788      Pragma_Compile_Time_Warning           => -1,
29789      Pragma_Compiler_Unit                  => -1,
29790      Pragma_Compiler_Unit_Warning          => -1,
29791      Pragma_Complete_Representation        =>  0,
29792      Pragma_Complex_Representation         =>  0,
29793      Pragma_Component_Alignment            =>  0,
29794      Pragma_Constant_After_Elaboration     =>  0,
29795      Pragma_Contract_Cases                 => -1,
29796      Pragma_Controlled                     =>  0,
29797      Pragma_Convention                     =>  0,
29798      Pragma_Convention_Identifier          =>  0,
29799      Pragma_Deadline_Floor                 => -1,
29800      Pragma_Debug                          => -1,
29801      Pragma_Debug_Policy                   =>  0,
29802      Pragma_Detect_Blocking                =>  0,
29803      Pragma_Default_Initial_Condition      => -1,
29804      Pragma_Default_Scalar_Storage_Order   =>  0,
29805      Pragma_Default_Storage_Pool           =>  0,
29806      Pragma_Depends                        => -1,
29807      Pragma_Disable_Atomic_Synchronization =>  0,
29808      Pragma_Discard_Names                  =>  0,
29809      Pragma_Dispatching_Domain             => -1,
29810      Pragma_Effective_Reads                =>  0,
29811      Pragma_Effective_Writes               =>  0,
29812      Pragma_Elaborate                      =>  0,
29813      Pragma_Elaborate_All                  =>  0,
29814      Pragma_Elaborate_Body                 =>  0,
29815      Pragma_Elaboration_Checks             =>  0,
29816      Pragma_Eliminate                      =>  0,
29817      Pragma_Enable_Atomic_Synchronization  =>  0,
29818      Pragma_Export                         => -1,
29819      Pragma_Export_Function                => -1,
29820      Pragma_Export_Object                  => -1,
29821      Pragma_Export_Procedure               => -1,
29822      Pragma_Export_Value                   => -1,
29823      Pragma_Export_Valued_Procedure        => -1,
29824      Pragma_Extend_System                  => -1,
29825      Pragma_Extensions_Allowed             =>  0,
29826      Pragma_Extensions_Visible             =>  0,
29827      Pragma_External                       => -1,
29828      Pragma_Favor_Top_Level                =>  0,
29829      Pragma_External_Name_Casing           =>  0,
29830      Pragma_Fast_Math                      =>  0,
29831      Pragma_Finalize_Storage_Only          =>  0,
29832      Pragma_Ghost                          =>  0,
29833      Pragma_Global                         => -1,
29834      Pragma_Ident                          => -1,
29835      Pragma_Ignore_Pragma                  =>  0,
29836      Pragma_Implementation_Defined         => -1,
29837      Pragma_Implemented                    => -1,
29838      Pragma_Implicit_Packing               =>  0,
29839      Pragma_Import                         => 93,
29840      Pragma_Import_Function                =>  0,
29841      Pragma_Import_Object                  =>  0,
29842      Pragma_Import_Procedure               =>  0,
29843      Pragma_Import_Valued_Procedure        =>  0,
29844      Pragma_Independent                    =>  0,
29845      Pragma_Independent_Components         =>  0,
29846      Pragma_Initial_Condition              => -1,
29847      Pragma_Initialize_Scalars             =>  0,
29848      Pragma_Initializes                    => -1,
29849      Pragma_Inline                         =>  0,
29850      Pragma_Inline_Always                  =>  0,
29851      Pragma_Inline_Generic                 =>  0,
29852      Pragma_Inspection_Point               => -1,
29853      Pragma_Interface                      => 92,
29854      Pragma_Interface_Name                 =>  0,
29855      Pragma_Interrupt_Handler              => -1,
29856      Pragma_Interrupt_Priority             => -1,
29857      Pragma_Interrupt_State                => -1,
29858      Pragma_Invariant                      => -1,
29859      Pragma_Keep_Names                     =>  0,
29860      Pragma_License                        =>  0,
29861      Pragma_Link_With                      => -1,
29862      Pragma_Linker_Alias                   => -1,
29863      Pragma_Linker_Constructor             => -1,
29864      Pragma_Linker_Destructor              => -1,
29865      Pragma_Linker_Options                 => -1,
29866      Pragma_Linker_Section                 => -1,
29867      Pragma_List                           =>  0,
29868      Pragma_Lock_Free                      =>  0,
29869      Pragma_Locking_Policy                 =>  0,
29870      Pragma_Loop_Invariant                 => -1,
29871      Pragma_Loop_Optimize                  =>  0,
29872      Pragma_Loop_Variant                   => -1,
29873      Pragma_Machine_Attribute              => -1,
29874      Pragma_Main                           => -1,
29875      Pragma_Main_Storage                   => -1,
29876      Pragma_Max_Queue_Length               =>  0,
29877      Pragma_Memory_Size                    =>  0,
29878      Pragma_No_Return                      =>  0,
29879      Pragma_No_Body                        =>  0,
29880      Pragma_No_Component_Reordering        => -1,
29881      Pragma_No_Elaboration_Code_All        =>  0,
29882      Pragma_No_Heap_Finalization           =>  0,
29883      Pragma_No_Inline                      =>  0,
29884      Pragma_No_Run_Time                    => -1,
29885      Pragma_No_Strict_Aliasing             => -1,
29886      Pragma_No_Tagged_Streams              =>  0,
29887      Pragma_Normalize_Scalars              =>  0,
29888      Pragma_Obsolescent                    =>  0,
29889      Pragma_Optimize                       =>  0,
29890      Pragma_Optimize_Alignment             =>  0,
29891      Pragma_Overflow_Mode                  =>  0,
29892      Pragma_Overriding_Renamings           =>  0,
29893      Pragma_Ordered                        =>  0,
29894      Pragma_Pack                           =>  0,
29895      Pragma_Page                           =>  0,
29896      Pragma_Part_Of                        =>  0,
29897      Pragma_Partition_Elaboration_Policy   =>  0,
29898      Pragma_Passive                        =>  0,
29899      Pragma_Persistent_BSS                 =>  0,
29900      Pragma_Polling                        =>  0,
29901      Pragma_Prefix_Exception_Messages      =>  0,
29902      Pragma_Post                           => -1,
29903      Pragma_Postcondition                  => -1,
29904      Pragma_Post_Class                     => -1,
29905      Pragma_Pre                            => -1,
29906      Pragma_Precondition                   => -1,
29907      Pragma_Predicate                      => -1,
29908      Pragma_Predicate_Failure              => -1,
29909      Pragma_Preelaborable_Initialization   => -1,
29910      Pragma_Preelaborate                   =>  0,
29911      Pragma_Pre_Class                      => -1,
29912      Pragma_Priority                       => -1,
29913      Pragma_Priority_Specific_Dispatching  =>  0,
29914      Pragma_Profile                        =>  0,
29915      Pragma_Profile_Warnings               =>  0,
29916      Pragma_Propagate_Exceptions           =>  0,
29917      Pragma_Provide_Shift_Operators        =>  0,
29918      Pragma_Psect_Object                   =>  0,
29919      Pragma_Pure                           =>  0,
29920      Pragma_Pure_Function                  =>  0,
29921      Pragma_Queuing_Policy                 =>  0,
29922      Pragma_Rational                       =>  0,
29923      Pragma_Ravenscar                      =>  0,
29924      Pragma_Refined_Depends                => -1,
29925      Pragma_Refined_Global                 => -1,
29926      Pragma_Refined_Post                   => -1,
29927      Pragma_Refined_State                  => -1,
29928      Pragma_Relative_Deadline              =>  0,
29929      Pragma_Rename_Pragma                  =>  0,
29930      Pragma_Remote_Access_Type             => -1,
29931      Pragma_Remote_Call_Interface          => -1,
29932      Pragma_Remote_Types                   => -1,
29933      Pragma_Restricted_Run_Time            =>  0,
29934      Pragma_Restriction_Warnings           =>  0,
29935      Pragma_Restrictions                   =>  0,
29936      Pragma_Reviewable                     => -1,
29937      Pragma_Secondary_Stack_Size           => -1,
29938      Pragma_Short_Circuit_And_Or           =>  0,
29939      Pragma_Share_Generic                  =>  0,
29940      Pragma_Shared                         =>  0,
29941      Pragma_Shared_Passive                 =>  0,
29942      Pragma_Short_Descriptors              =>  0,
29943      Pragma_Simple_Storage_Pool_Type       =>  0,
29944      Pragma_Source_File_Name               =>  0,
29945      Pragma_Source_File_Name_Project       =>  0,
29946      Pragma_Source_Reference               =>  0,
29947      Pragma_SPARK_Mode                     =>  0,
29948      Pragma_Storage_Size                   => -1,
29949      Pragma_Storage_Unit                   =>  0,
29950      Pragma_Static_Elaboration_Desired     =>  0,
29951      Pragma_Stream_Convert                 =>  0,
29952      Pragma_Style_Checks                   =>  0,
29953      Pragma_Subtitle                       =>  0,
29954      Pragma_Suppress                       =>  0,
29955      Pragma_Suppress_Exception_Locations   =>  0,
29956      Pragma_Suppress_All                   =>  0,
29957      Pragma_Suppress_Debug_Info            =>  0,
29958      Pragma_Suppress_Initialization        =>  0,
29959      Pragma_System_Name                    =>  0,
29960      Pragma_Task_Dispatching_Policy        =>  0,
29961      Pragma_Task_Info                      => -1,
29962      Pragma_Task_Name                      => -1,
29963      Pragma_Task_Storage                   => -1,
29964      Pragma_Test_Case                      => -1,
29965      Pragma_Thread_Local_Storage           => -1,
29966      Pragma_Time_Slice                     => -1,
29967      Pragma_Title                          =>  0,
29968      Pragma_Type_Invariant                 => -1,
29969      Pragma_Type_Invariant_Class           => -1,
29970      Pragma_Unchecked_Union                =>  0,
29971      Pragma_Unevaluated_Use_Of_Old         =>  0,
29972      Pragma_Unimplemented_Unit             =>  0,
29973      Pragma_Universal_Aliasing             =>  0,
29974      Pragma_Universal_Data                 =>  0,
29975      Pragma_Unmodified                     =>  0,
29976      Pragma_Unreferenced                   =>  0,
29977      Pragma_Unreferenced_Objects           =>  0,
29978      Pragma_Unreserve_All_Interrupts       =>  0,
29979      Pragma_Unsuppress                     =>  0,
29980      Pragma_Unused                         =>  0,
29981      Pragma_Use_VADS_Size                  =>  0,
29982      Pragma_Validity_Checks                =>  0,
29983      Pragma_Volatile                       =>  0,
29984      Pragma_Volatile_Components            =>  0,
29985      Pragma_Volatile_Full_Access           =>  0,
29986      Pragma_Volatile_Function              =>  0,
29987      Pragma_Warning_As_Error               =>  0,
29988      Pragma_Warnings                       =>  0,
29989      Pragma_Weak_External                  =>  0,
29990      Pragma_Wide_Character_Encoding        =>  0,
29991      Unknown_Pragma                        =>  0);
29992
29993   function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
29994      Id : Pragma_Id;
29995      P  : Node_Id;
29996      C  : Int;
29997      AN : Nat;
29998
29999      function Arg_No return Nat;
30000      --  Returns an integer showing what argument we are in. A value of
30001      --  zero means we are not in any of the arguments.
30002
30003      ------------
30004      -- Arg_No --
30005      ------------
30006
30007      function Arg_No return Nat is
30008         A : Node_Id;
30009         N : Nat;
30010
30011      begin
30012         A := First (Pragma_Argument_Associations (Parent (P)));
30013         N := 1;
30014         loop
30015            if No (A) then
30016               return 0;
30017            elsif A = P then
30018               return N;
30019            end if;
30020
30021            Next (A);
30022            N := N + 1;
30023         end loop;
30024      end Arg_No;
30025
30026   --  Start of processing for Non_Significant_Pragma_Reference
30027
30028   begin
30029      P := Parent (N);
30030
30031      if Nkind (P) /= N_Pragma_Argument_Association then
30032         return False;
30033
30034      else
30035         Id := Get_Pragma_Id (Parent (P));
30036         C := Sig_Flags (Id);
30037         AN := Arg_No;
30038
30039         if AN = 0 then
30040            return False;
30041         end if;
30042
30043         case C is
30044            when -1 =>
30045               return False;
30046
30047            when 0 =>
30048               return True;
30049
30050            when 92 .. 99 =>
30051               return AN < (C - 90);
30052
30053            when others =>
30054               return AN /= C;
30055         end case;
30056      end if;
30057   end Is_Non_Significant_Pragma_Reference;
30058
30059   ------------------------------
30060   -- Is_Pragma_String_Literal --
30061   ------------------------------
30062
30063   --  This function returns true if the corresponding pragma argument is a
30064   --  static string expression. These are the only cases in which string
30065   --  literals can appear as pragma arguments. We also allow a string literal
30066   --  as the first argument to pragma Assert (although it will of course
30067   --  always generate a type error).
30068
30069   function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
30070      Pragn : constant Node_Id := Parent (Par);
30071      Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
30072      Pname : constant Name_Id := Pragma_Name (Pragn);
30073      Argn  : Natural;
30074      N     : Node_Id;
30075
30076   begin
30077      Argn := 1;
30078      N := First (Assoc);
30079      loop
30080         exit when N = Par;
30081         Argn := Argn + 1;
30082         Next (N);
30083      end loop;
30084
30085      if Pname = Name_Assert then
30086         return True;
30087
30088      elsif Pname = Name_Export then
30089         return Argn > 2;
30090
30091      elsif Pname = Name_Ident then
30092         return Argn = 1;
30093
30094      elsif Pname = Name_Import then
30095         return Argn > 2;
30096
30097      elsif Pname = Name_Interface_Name then
30098         return Argn > 1;
30099
30100      elsif Pname = Name_Linker_Alias then
30101         return Argn = 2;
30102
30103      elsif Pname = Name_Linker_Section then
30104         return Argn = 2;
30105
30106      elsif Pname = Name_Machine_Attribute then
30107         return Argn = 2;
30108
30109      elsif Pname = Name_Source_File_Name then
30110         return True;
30111
30112      elsif Pname = Name_Source_Reference then
30113         return Argn = 2;
30114
30115      elsif Pname = Name_Title then
30116         return True;
30117
30118      elsif Pname = Name_Subtitle then
30119         return True;
30120
30121      else
30122         return False;
30123      end if;
30124   end Is_Pragma_String_Literal;
30125
30126   ---------------------------
30127   -- Is_Private_SPARK_Mode --
30128   ---------------------------
30129
30130   function Is_Private_SPARK_Mode (N : Node_Id) return Boolean is
30131   begin
30132      pragma Assert
30133        (Nkind (N) = N_Pragma
30134          and then Pragma_Name (N) = Name_SPARK_Mode
30135          and then Is_List_Member (N));
30136
30137      --  For pragma SPARK_Mode to be private, it has to appear in the private
30138      --  declarations of a package.
30139
30140      return
30141        Present (Parent (N))
30142          and then Nkind (Parent (N)) = N_Package_Specification
30143          and then List_Containing (N) = Private_Declarations (Parent (N));
30144   end Is_Private_SPARK_Mode;
30145
30146   -------------------------------------
30147   -- Is_Unconstrained_Or_Tagged_Item --
30148   -------------------------------------
30149
30150   function Is_Unconstrained_Or_Tagged_Item
30151     (Item : Entity_Id) return Boolean
30152   is
30153      function Has_Unconstrained_Component (Typ : Entity_Id) return Boolean;
30154      --  Determine whether record type Typ has at least one unconstrained
30155      --  component.
30156
30157      ---------------------------------
30158      -- Has_Unconstrained_Component --
30159      ---------------------------------
30160
30161      function Has_Unconstrained_Component (Typ : Entity_Id) return Boolean is
30162         Comp : Entity_Id;
30163
30164      begin
30165         Comp := First_Component (Typ);
30166         while Present (Comp) loop
30167            if Is_Unconstrained_Or_Tagged_Item (Comp) then
30168               return True;
30169            end if;
30170
30171            Next_Component (Comp);
30172         end loop;
30173
30174         return False;
30175      end Has_Unconstrained_Component;
30176
30177      --  Local variables
30178
30179      Typ : constant Entity_Id := Etype (Item);
30180
30181   --  Start of processing for Is_Unconstrained_Or_Tagged_Item
30182
30183   begin
30184      if Is_Tagged_Type (Typ) then
30185         return True;
30186
30187      elsif Is_Array_Type (Typ) and then not Is_Constrained (Typ) then
30188         return True;
30189
30190      elsif Is_Record_Type (Typ) then
30191         if Has_Discriminants (Typ) and then not Is_Constrained (Typ) then
30192            return True;
30193         else
30194            return Has_Unconstrained_Component (Typ);
30195         end if;
30196
30197      elsif Is_Private_Type (Typ) and then Has_Discriminants (Typ) then
30198         return True;
30199
30200      else
30201         return False;
30202      end if;
30203   end Is_Unconstrained_Or_Tagged_Item;
30204
30205   -----------------------------
30206   -- Is_Valid_Assertion_Kind --
30207   -----------------------------
30208
30209   function Is_Valid_Assertion_Kind (Nam : Name_Id) return Boolean is
30210   begin
30211      case Nam is
30212         when
30213            --  RM defined
30214
30215              Name_Assert
30216            | Name_Assertion_Policy
30217            | Name_Static_Predicate
30218            | Name_Dynamic_Predicate
30219            | Name_Pre
30220            | Name_uPre
30221            | Name_Post
30222            | Name_uPost
30223            | Name_Type_Invariant
30224            | Name_uType_Invariant
30225
30226            --  Impl defined
30227
30228            | Name_Assert_And_Cut
30229            | Name_Assume
30230            | Name_Contract_Cases
30231            | Name_Debug
30232            | Name_Default_Initial_Condition
30233            | Name_Ghost
30234            | Name_Initial_Condition
30235            | Name_Invariant
30236            | Name_uInvariant
30237            | Name_Loop_Invariant
30238            | Name_Loop_Variant
30239            | Name_Postcondition
30240            | Name_Precondition
30241            | Name_Predicate
30242            | Name_Refined_Post
30243            | Name_Statement_Assertions
30244         =>
30245            return True;
30246
30247         when others =>
30248            return False;
30249      end case;
30250   end Is_Valid_Assertion_Kind;
30251
30252   --------------------------------------
30253   -- Process_Compilation_Unit_Pragmas --
30254   --------------------------------------
30255
30256   procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
30257   begin
30258      --  A special check for pragma Suppress_All, a very strange DEC pragma,
30259      --  strange because it comes at the end of the unit. Rational has the
30260      --  same name for a pragma, but treats it as a program unit pragma, In
30261      --  GNAT we just decide to allow it anywhere at all. If it appeared then
30262      --  the flag Has_Pragma_Suppress_All was set on the compilation unit
30263      --  node, and we insert a pragma Suppress (All_Checks) at the start of
30264      --  the context clause to ensure the correct processing.
30265
30266      if Has_Pragma_Suppress_All (N) then
30267         Prepend_To (Context_Items (N),
30268           Make_Pragma (Sloc (N),
30269             Chars                        => Name_Suppress,
30270             Pragma_Argument_Associations => New_List (
30271               Make_Pragma_Argument_Association (Sloc (N),
30272                 Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
30273      end if;
30274
30275      --  Nothing else to do at the current time
30276
30277   end Process_Compilation_Unit_Pragmas;
30278
30279   -------------------------------------------
30280   -- Process_Compile_Time_Warning_Or_Error --
30281   -------------------------------------------
30282
30283   procedure Process_Compile_Time_Warning_Or_Error
30284     (N     : Node_Id;
30285      Eloc  : Source_Ptr)
30286   is
30287      Arg1  : constant Node_Id := First (Pragma_Argument_Associations (N));
30288      Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
30289      Arg2  : constant Node_Id := Next (Arg1);
30290
30291   begin
30292      Analyze_And_Resolve (Arg1x, Standard_Boolean);
30293
30294      if Compile_Time_Known_Value (Arg1x) then
30295         if Is_True (Expr_Value (Arg1x)) then
30296            declare
30297               Cent    : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
30298               Pname   : constant Name_Id   := Pragma_Name_Unmapped (N);
30299               Prag_Id : constant Pragma_Id := Get_Pragma_Id (Pname);
30300               Str     : constant String_Id := Strval (Get_Pragma_Arg (Arg2));
30301               Str_Len : constant Nat       := String_Length (Str);
30302
30303               Force : constant Boolean :=
30304                         Prag_Id = Pragma_Compile_Time_Warning
30305                           and then Is_Spec_Name (Unit_Name (Current_Sem_Unit))
30306                           and then (Ekind (Cent) /= E_Package
30307                                      or else not In_Private_Part (Cent));
30308               --  Set True if this is the warning case, and we are in the
30309               --  visible part of a package spec, or in a subprogram spec,
30310               --  in which case we want to force the client to see the
30311               --  warning, even though it is not in the main unit.
30312
30313               C    : Character;
30314               CC   : Char_Code;
30315               Cont : Boolean;
30316               Ptr  : Nat;
30317
30318            begin
30319               --  Loop through segments of message separated by line feeds.
30320               --  We output these segments as separate messages with
30321               --  continuation marks for all but the first.
30322
30323               Cont := False;
30324               Ptr  := 1;
30325               loop
30326                  Error_Msg_Strlen := 0;
30327
30328                  --  Loop to copy characters from argument to error message
30329                  --  string buffer.
30330
30331                  loop
30332                     exit when Ptr > Str_Len;
30333                     CC := Get_String_Char (Str, Ptr);
30334                     Ptr := Ptr + 1;
30335
30336                     --  Ignore wide chars ??? else store character
30337
30338                     if In_Character_Range (CC) then
30339                        C := Get_Character (CC);
30340                        exit when C = ASCII.LF;
30341                        Error_Msg_Strlen := Error_Msg_Strlen + 1;
30342                        Error_Msg_String (Error_Msg_Strlen) := C;
30343                     end if;
30344                  end loop;
30345
30346                  --  Here with one line ready to go
30347
30348                  Error_Msg_Warn := Prag_Id = Pragma_Compile_Time_Warning;
30349
30350                  --  If this is a warning in a spec, then we want clients
30351                  --  to see the warning, so mark the message with the
30352                  --  special sequence !! to force the warning. In the case
30353                  --  of a package spec, we do not force this if we are in
30354                  --  the private part of the spec.
30355
30356                  if Force then
30357                     if Cont = False then
30358                        Error_Msg ("<<~!!", Eloc);
30359                        Cont := True;
30360                     else
30361                        Error_Msg ("\<<~!!", Eloc);
30362                     end if;
30363
30364                  --  Error, rather than warning, or in a body, so we do not
30365                  --  need to force visibility for client (error will be
30366                  --  output in any case, and this is the situation in which
30367                  --  we do not want a client to get a warning, since the
30368                  --  warning is in the body or the spec private part).
30369
30370                  else
30371                     if Cont = False then
30372                        Error_Msg ("<<~", Eloc);
30373                        Cont := True;
30374                     else
30375                        Error_Msg ("\<<~", Eloc);
30376                     end if;
30377                  end if;
30378
30379                  exit when Ptr > Str_Len;
30380               end loop;
30381            end;
30382         end if;
30383      end if;
30384   end Process_Compile_Time_Warning_Or_Error;
30385
30386   ------------------------------------
30387   -- Record_Possible_Body_Reference --
30388   ------------------------------------
30389
30390   procedure Record_Possible_Body_Reference
30391     (State_Id : Entity_Id;
30392      Ref      : Node_Id)
30393   is
30394      Context : Node_Id;
30395      Spec_Id : Entity_Id;
30396
30397   begin
30398      --  Ensure that we are dealing with a reference to a state
30399
30400      pragma Assert (Ekind (State_Id) = E_Abstract_State);
30401
30402      --  Climb the tree starting from the reference looking for a package body
30403      --  whose spec declares the referenced state. This criteria automatically
30404      --  excludes references in package specs which are legal. Note that it is
30405      --  not wise to emit an error now as the package body may lack pragma
30406      --  Refined_State or the referenced state may not be mentioned in the
30407      --  refinement. This approach avoids the generation of misleading errors.
30408
30409      Context := Ref;
30410      while Present (Context) loop
30411         if Nkind (Context) = N_Package_Body then
30412            Spec_Id := Corresponding_Spec (Context);
30413
30414            if Present (Abstract_States (Spec_Id))
30415              and then Contains (Abstract_States (Spec_Id), State_Id)
30416            then
30417               if No (Body_References (State_Id)) then
30418                  Set_Body_References (State_Id, New_Elmt_List);
30419               end if;
30420
30421               Append_Elmt (Ref, To => Body_References (State_Id));
30422               exit;
30423            end if;
30424         end if;
30425
30426         Context := Parent (Context);
30427      end loop;
30428   end Record_Possible_Body_Reference;
30429
30430   ------------------------------------------
30431   -- Relocate_Pragmas_To_Anonymous_Object --
30432   ------------------------------------------
30433
30434   procedure Relocate_Pragmas_To_Anonymous_Object
30435     (Typ_Decl : Node_Id;
30436      Obj_Decl : Node_Id)
30437   is
30438      Decl      : Node_Id;
30439      Def       : Node_Id;
30440      Next_Decl : Node_Id;
30441
30442   begin
30443      if Nkind (Typ_Decl) = N_Protected_Type_Declaration then
30444         Def := Protected_Definition (Typ_Decl);
30445      else
30446         pragma Assert (Nkind (Typ_Decl) = N_Task_Type_Declaration);
30447         Def := Task_Definition (Typ_Decl);
30448      end if;
30449
30450      --  The concurrent definition has a visible declaration list. Inspect it
30451      --  and relocate all canidate pragmas.
30452
30453      if Present (Def) and then Present (Visible_Declarations (Def)) then
30454         Decl := First (Visible_Declarations (Def));
30455         while Present (Decl) loop
30456
30457            --  Preserve the following declaration for iteration purposes due
30458            --  to possible relocation of a pragma.
30459
30460            Next_Decl := Next (Decl);
30461
30462            if Nkind (Decl) = N_Pragma
30463              and then Pragma_On_Anonymous_Object_OK (Get_Pragma_Id (Decl))
30464            then
30465               Remove (Decl);
30466               Insert_After (Obj_Decl, Decl);
30467
30468            --  Skip internally generated code
30469
30470            elsif not Comes_From_Source (Decl) then
30471               null;
30472
30473            --  No candidate pragmas are available for relocation
30474
30475            else
30476               exit;
30477            end if;
30478
30479            Decl := Next_Decl;
30480         end loop;
30481      end if;
30482   end Relocate_Pragmas_To_Anonymous_Object;
30483
30484   ------------------------------
30485   -- Relocate_Pragmas_To_Body --
30486   ------------------------------
30487
30488   procedure Relocate_Pragmas_To_Body
30489     (Subp_Body   : Node_Id;
30490      Target_Body : Node_Id := Empty)
30491   is
30492      procedure Relocate_Pragma (Prag : Node_Id);
30493      --  Remove a single pragma from its current list and add it to the
30494      --  declarations of the proper body (either Subp_Body or Target_Body).
30495
30496      ---------------------
30497      -- Relocate_Pragma --
30498      ---------------------
30499
30500      procedure Relocate_Pragma (Prag : Node_Id) is
30501         Decls  : List_Id;
30502         Target : Node_Id;
30503
30504      begin
30505         --  When subprogram stubs or expression functions are involves, the
30506         --  destination declaration list belongs to the proper body.
30507
30508         if Present (Target_Body) then
30509            Target := Target_Body;
30510         else
30511            Target := Subp_Body;
30512         end if;
30513
30514         Decls := Declarations (Target);
30515
30516         if No (Decls) then
30517            Decls := New_List;
30518            Set_Declarations (Target, Decls);
30519         end if;
30520
30521         --  Unhook the pragma from its current list
30522
30523         Remove  (Prag);
30524         Prepend (Prag, Decls);
30525      end Relocate_Pragma;
30526
30527      --  Local variables
30528
30529      Body_Id   : constant Entity_Id :=
30530                    Defining_Unit_Name (Specification (Subp_Body));
30531      Next_Stmt : Node_Id;
30532      Stmt      : Node_Id;
30533
30534   --  Start of processing for Relocate_Pragmas_To_Body
30535
30536   begin
30537      --  Do not process a body that comes from a separate unit as no construct
30538      --  can possibly follow it.
30539
30540      if not Is_List_Member (Subp_Body) then
30541         return;
30542
30543      --  Do not relocate pragmas that follow a stub if the stub does not have
30544      --  a proper body.
30545
30546      elsif Nkind (Subp_Body) = N_Subprogram_Body_Stub
30547        and then No (Target_Body)
30548      then
30549         return;
30550
30551      --  Do not process internally generated routine _Postconditions
30552
30553      elsif Ekind (Body_Id) = E_Procedure
30554        and then Chars (Body_Id) = Name_uPostconditions
30555      then
30556         return;
30557      end if;
30558
30559      --  Look at what is following the body. We are interested in certain kind
30560      --  of pragmas (either from source or byproducts of expansion) that can
30561      --  apply to a body [stub].
30562
30563      Stmt := Next (Subp_Body);
30564      while Present (Stmt) loop
30565
30566         --  Preserve the following statement for iteration purposes due to a
30567         --  possible relocation of a pragma.
30568
30569         Next_Stmt := Next (Stmt);
30570
30571         --  Move a candidate pragma following the body to the declarations of
30572         --  the body.
30573
30574         if Nkind (Stmt) = N_Pragma
30575           and then Pragma_On_Body_Or_Stub_OK (Get_Pragma_Id (Stmt))
30576         then
30577
30578            --  If a source pragma Warnings follows the body, it applies to
30579            --  following statements and does not belong in the body.
30580
30581            if Get_Pragma_Id (Stmt) = Pragma_Warnings
30582              and then Comes_From_Source (Stmt)
30583            then
30584               null;
30585            else
30586               Relocate_Pragma (Stmt);
30587            end if;
30588
30589         --  Skip internally generated code
30590
30591         elsif not Comes_From_Source (Stmt) then
30592            null;
30593
30594         --  No candidate pragmas are available for relocation
30595
30596         else
30597            exit;
30598         end if;
30599
30600         Stmt := Next_Stmt;
30601      end loop;
30602   end Relocate_Pragmas_To_Body;
30603
30604   -------------------
30605   -- Resolve_State --
30606   -------------------
30607
30608   procedure Resolve_State (N : Node_Id) is
30609      Func  : Entity_Id;
30610      State : Entity_Id;
30611
30612   begin
30613      if Is_Entity_Name (N) and then Present (Entity (N)) then
30614         Func := Entity (N);
30615
30616         --  Handle overloading of state names by functions. Traverse the
30617         --  homonym chain looking for an abstract state.
30618
30619         if Ekind (Func) = E_Function and then Has_Homonym (Func) then
30620            pragma Assert (Is_Overloaded (N));
30621
30622            State := Homonym (Func);
30623            while Present (State) loop
30624               if Ekind (State) = E_Abstract_State then
30625
30626                  --  Resolve the overloading by setting the proper entity of
30627                  --  the reference to that of the state.
30628
30629                  Set_Etype         (N, Standard_Void_Type);
30630                  Set_Entity        (N, State);
30631                  Set_Is_Overloaded (N, False);
30632
30633                  Generate_Reference (State, N);
30634                  return;
30635               end if;
30636
30637               State := Homonym (State);
30638            end loop;
30639
30640            --  A function can never act as a state. If the homonym chain does
30641            --  not contain a corresponding state, then something went wrong in
30642            --  the overloading mechanism.
30643
30644            raise Program_Error;
30645         end if;
30646      end if;
30647   end Resolve_State;
30648
30649   ----------------------------
30650   -- Rewrite_Assertion_Kind --
30651   ----------------------------
30652
30653   procedure Rewrite_Assertion_Kind
30654     (N           : Node_Id;
30655      From_Policy : Boolean := False)
30656   is
30657      Nam : Name_Id;
30658
30659   begin
30660      Nam := No_Name;
30661      if Nkind (N) = N_Attribute_Reference
30662        and then Attribute_Name (N) = Name_Class
30663        and then Nkind (Prefix (N)) = N_Identifier
30664      then
30665         case Chars (Prefix (N)) is
30666            when Name_Pre =>
30667               Nam := Name_uPre;
30668
30669            when Name_Post =>
30670               Nam := Name_uPost;
30671
30672            when Name_Type_Invariant =>
30673               Nam := Name_uType_Invariant;
30674
30675            when Name_Invariant =>
30676               Nam := Name_uInvariant;
30677
30678            when others =>
30679               return;
30680         end case;
30681
30682      --  Recommend standard use of aspect names Pre/Post
30683
30684      elsif Nkind (N) = N_Identifier
30685        and then From_Policy
30686        and then Serious_Errors_Detected = 0
30687        and then not ASIS_Mode
30688      then
30689         if Chars (N) = Name_Precondition
30690           or else Chars (N) = Name_Postcondition
30691         then
30692            Error_Msg_N ("Check_Policy is a non-standard pragma??", N);
30693            Error_Msg_N
30694              ("\use Assertion_Policy and aspect names Pre/Post for "
30695               & "Ada2012 conformance?", N);
30696         end if;
30697
30698         return;
30699      end if;
30700
30701      if Nam /= No_Name then
30702         Rewrite (N, Make_Identifier (Sloc (N), Chars => Nam));
30703      end if;
30704   end Rewrite_Assertion_Kind;
30705
30706   --------
30707   -- rv --
30708   --------
30709
30710   procedure rv is
30711   begin
30712      Dummy := Dummy + 1;
30713   end rv;
30714
30715   --------------------------------
30716   -- Set_Encoded_Interface_Name --
30717   --------------------------------
30718
30719   procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
30720      Str : constant String_Id := Strval (S);
30721      Len : constant Nat       := String_Length (Str);
30722      CC  : Char_Code;
30723      C   : Character;
30724      J   : Pos;
30725
30726      Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
30727
30728      procedure Encode;
30729      --  Stores encoded value of character code CC. The encoding we use an
30730      --  underscore followed by four lower case hex digits.
30731
30732      ------------
30733      -- Encode --
30734      ------------
30735
30736      procedure Encode is
30737      begin
30738         Store_String_Char (Get_Char_Code ('_'));
30739         Store_String_Char
30740           (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
30741         Store_String_Char
30742           (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
30743         Store_String_Char
30744           (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
30745         Store_String_Char
30746           (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
30747      end Encode;
30748
30749   --  Start of processing for Set_Encoded_Interface_Name
30750
30751   begin
30752      --  If first character is asterisk, this is a link name, and we leave it
30753      --  completely unmodified. We also ignore null strings (the latter case
30754      --  happens only in error cases).
30755
30756      if Len = 0
30757        or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
30758      then
30759         Set_Interface_Name (E, S);
30760
30761      else
30762         J := 1;
30763         loop
30764            CC := Get_String_Char (Str, J);
30765
30766            exit when not In_Character_Range (CC);
30767
30768            C := Get_Character (CC);
30769
30770            exit when C /= '_' and then C /= '$'
30771              and then C not in '0' .. '9'
30772              and then C not in 'a' .. 'z'
30773              and then C not in 'A' .. 'Z';
30774
30775            if J = Len then
30776               Set_Interface_Name (E, S);
30777               return;
30778
30779            else
30780               J := J + 1;
30781            end if;
30782         end loop;
30783
30784         --  Here we need to encode. The encoding we use as follows:
30785         --     three underscores  + four hex digits (lower case)
30786
30787         Start_String;
30788
30789         for J in 1 .. String_Length (Str) loop
30790            CC := Get_String_Char (Str, J);
30791
30792            if not In_Character_Range (CC) then
30793               Encode;
30794            else
30795               C := Get_Character (CC);
30796
30797               if C = '_' or else C = '$'
30798                 or else C in '0' .. '9'
30799                 or else C in 'a' .. 'z'
30800                 or else C in 'A' .. 'Z'
30801               then
30802                  Store_String_Char (CC);
30803               else
30804                  Encode;
30805               end if;
30806            end if;
30807         end loop;
30808
30809         Set_Interface_Name (E,
30810           Make_String_Literal (Sloc (S),
30811             Strval => End_String));
30812      end if;
30813   end Set_Encoded_Interface_Name;
30814
30815   ------------------------
30816   -- Set_Elab_Unit_Name --
30817   ------------------------
30818
30819   procedure Set_Elab_Unit_Name (N : Node_Id; With_Item : Node_Id) is
30820      Pref : Node_Id;
30821      Scop : Entity_Id;
30822
30823   begin
30824      if Nkind (N) = N_Identifier
30825        and then Nkind (With_Item) = N_Identifier
30826      then
30827         Set_Entity (N, Entity (With_Item));
30828
30829      elsif Nkind (N) = N_Selected_Component then
30830         Change_Selected_Component_To_Expanded_Name (N);
30831         Set_Entity (N, Entity (With_Item));
30832         Set_Entity (Selector_Name (N), Entity (N));
30833
30834         Pref := Prefix (N);
30835         Scop := Scope (Entity (N));
30836         while Nkind (Pref) = N_Selected_Component loop
30837            Change_Selected_Component_To_Expanded_Name (Pref);
30838            Set_Entity (Selector_Name (Pref), Scop);
30839            Set_Entity (Pref, Scop);
30840            Pref := Prefix (Pref);
30841            Scop := Scope (Scop);
30842         end loop;
30843
30844         Set_Entity (Pref, Scop);
30845      end if;
30846
30847      Generate_Reference (Entity (With_Item), N, Set_Ref => False);
30848   end Set_Elab_Unit_Name;
30849
30850   -------------------
30851   -- Test_Case_Arg --
30852   -------------------
30853
30854   function Test_Case_Arg
30855     (Prag        : Node_Id;
30856      Arg_Nam     : Name_Id;
30857      From_Aspect : Boolean := False) return Node_Id
30858   is
30859      Aspect : constant Node_Id := Corresponding_Aspect (Prag);
30860      Arg    : Node_Id;
30861      Args   : Node_Id;
30862
30863   begin
30864      pragma Assert (Nam_In (Arg_Nam, Name_Ensures,
30865                                      Name_Mode,
30866                                      Name_Name,
30867                                      Name_Requires));
30868
30869      --  The caller requests the aspect argument
30870
30871      if From_Aspect then
30872         if Present (Aspect)
30873           and then Nkind (Expression (Aspect)) = N_Aggregate
30874         then
30875            Args := Expression (Aspect);
30876
30877            --  "Name" and "Mode" may appear without an identifier as a
30878            --  positional association.
30879
30880            if Present (Expressions (Args)) then
30881               Arg := First (Expressions (Args));
30882
30883               if Present (Arg) and then Arg_Nam = Name_Name then
30884                  return Arg;
30885               end if;
30886
30887               --  Skip "Name"
30888
30889               Arg := Next (Arg);
30890
30891               if Present (Arg) and then Arg_Nam = Name_Mode then
30892                  return Arg;
30893               end if;
30894            end if;
30895
30896            --  Some or all arguments may appear as component associatons
30897
30898            if Present (Component_Associations (Args)) then
30899               Arg := First (Component_Associations (Args));
30900               while Present (Arg) loop
30901                  if Chars (First (Choices (Arg))) = Arg_Nam then
30902                     return Arg;
30903                  end if;
30904
30905                  Next (Arg);
30906               end loop;
30907            end if;
30908         end if;
30909
30910      --  Otherwise retrieve the argument directly from the pragma
30911
30912      else
30913         Arg := First (Pragma_Argument_Associations (Prag));
30914
30915         if Present (Arg) and then Arg_Nam = Name_Name then
30916            return Arg;
30917         end if;
30918
30919         --  Skip argument "Name"
30920
30921         Arg := Next (Arg);
30922
30923         if Present (Arg) and then Arg_Nam = Name_Mode then
30924            return Arg;
30925         end if;
30926
30927         --  Skip argument "Mode"
30928
30929         Arg := Next (Arg);
30930
30931         --  Arguments "Requires" and "Ensures" are optional and may not be
30932         --  present at all.
30933
30934         while Present (Arg) loop
30935            if Chars (Arg) = Arg_Nam then
30936               return Arg;
30937            end if;
30938
30939            Next (Arg);
30940         end loop;
30941      end if;
30942
30943      return Empty;
30944   end Test_Case_Arg;
30945
30946end Sem_Prag;
30947