OSDN Git Service

* exp_disp.adb (Expand_Dispatching_Call): Propagate the convention on
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_prag.adb
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-2012, 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
32 with Aspects;  use Aspects;
33 with Atree;    use Atree;
34 with Casing;   use Casing;
35 with Checks;   use Checks;
36 with Csets;    use Csets;
37 with Debug;    use Debug;
38 with Einfo;    use Einfo;
39 with Elists;   use Elists;
40 with Errout;   use Errout;
41 with Exp_Dist; use Exp_Dist;
42 with Exp_Util; use Exp_Util;
43 with Freeze;   use Freeze;
44 with Lib;      use Lib;
45 with Lib.Writ; use Lib.Writ;
46 with Lib.Xref; use Lib.Xref;
47 with Namet.Sp; use Namet.Sp;
48 with Nlists;   use Nlists;
49 with Nmake;    use Nmake;
50 with Opt;      use Opt;
51 with Output;   use Output;
52 with Par_SCO;  use Par_SCO;
53 with Restrict; use Restrict;
54 with Rident;   use Rident;
55 with Rtsfind;  use Rtsfind;
56 with Sem;      use Sem;
57 with Sem_Aux;  use Sem_Aux;
58 with Sem_Ch3;  use Sem_Ch3;
59 with Sem_Ch6;  use Sem_Ch6;
60 with Sem_Ch8;  use Sem_Ch8;
61 with Sem_Ch12; use Sem_Ch12;
62 with Sem_Ch13; use Sem_Ch13;
63 with Sem_Disp; use Sem_Disp;
64 with Sem_Dist; use Sem_Dist;
65 with Sem_Elim; use Sem_Elim;
66 with Sem_Eval; use Sem_Eval;
67 with Sem_Intr; use Sem_Intr;
68 with Sem_Mech; use Sem_Mech;
69 with Sem_Res;  use Sem_Res;
70 with Sem_Type; use Sem_Type;
71 with Sem_Util; use Sem_Util;
72 with Sem_VFpt; use Sem_VFpt;
73 with Sem_Warn; use Sem_Warn;
74 with Stand;    use Stand;
75 with Sinfo;    use Sinfo;
76 with Sinfo.CN; use Sinfo.CN;
77 with Sinput;   use Sinput;
78 with Snames;   use Snames;
79 with Stringt;  use Stringt;
80 with Stylesw;  use Stylesw;
81 with Table;
82 with Targparm; use Targparm;
83 with Tbuild;   use Tbuild;
84 with Ttypes;
85 with Uintp;    use Uintp;
86 with Uname;    use Uname;
87 with Urealp;   use Urealp;
88 with Validsw;  use Validsw;
89 with Warnsw;   use Warnsw;
90
91 package body Sem_Prag is
92
93    ----------------------------------------------
94    -- Common Handling of Import-Export Pragmas --
95    ----------------------------------------------
96
97    --  In the following section, a number of Import_xxx and Export_xxx pragmas
98    --  are defined by GNAT. These are compatible with the DEC pragmas of the
99    --  same name, and all have the following common form and processing:
100
101    --  pragma Export_xxx
102    --        [Internal                 =>] LOCAL_NAME
103    --     [, [External                 =>] EXTERNAL_SYMBOL]
104    --     [, other optional parameters   ]);
105
106    --  pragma Import_xxx
107    --        [Internal                 =>] LOCAL_NAME
108    --     [, [External                 =>] EXTERNAL_SYMBOL]
109    --     [, other optional parameters   ]);
110
111    --   EXTERNAL_SYMBOL ::=
112    --     IDENTIFIER
113    --   | static_string_EXPRESSION
114
115    --  The internal LOCAL_NAME designates the entity that is imported or
116    --  exported, and must refer to an entity in the current declarative
117    --  part (as required by the rules for LOCAL_NAME).
118
119    --  The external linker name is designated by the External parameter if
120    --  given, or the Internal parameter if not (if there is no External
121    --  parameter, the External parameter is a copy of the Internal name).
122
123    --  If the External parameter is given as a string, then this string is
124    --  treated as an external name (exactly as though it had been given as an
125    --  External_Name parameter for a normal Import pragma).
126
127    --  If the External parameter is given as an identifier (or there is no
128    --  External parameter, so that the Internal identifier is used), then
129    --  the external name is the characters of the identifier, translated
130    --  to all upper case letters for OpenVMS versions of GNAT, and to all
131    --  lower case letters for all other versions
132
133    --  Note: the external name specified or implied by any of these special
134    --  Import_xxx or Export_xxx pragmas override an external or link name
135    --  specified in a previous Import or Export pragma.
136
137    --  Note: these and all other DEC-compatible GNAT pragmas allow full use of
138    --  named notation, following the standard rules for subprogram calls, i.e.
139    --  parameters can be given in any order if named notation is used, and
140    --  positional and named notation can be mixed, subject to the rule that all
141    --  positional parameters must appear first.
142
143    --  Note: All these pragmas are implemented exactly following the DEC design
144    --  and implementation and are intended to be fully compatible with the use
145    --  of these pragmas in the DEC Ada compiler.
146
147    --------------------------------------------
148    -- Checking for Duplicated External Names --
149    --------------------------------------------
150
151    --  It is suspicious if two separate Export pragmas use the same external
152    --  name. The following table is used to diagnose this situation so that
153    --  an appropriate warning can be issued.
154
155    --  The Node_Id stored is for the N_String_Literal node created to hold
156    --  the value of the external name. The Sloc of this node is used to
157    --  cross-reference the location of the duplication.
158
159    package Externals is new Table.Table (
160      Table_Component_Type => Node_Id,
161      Table_Index_Type     => Int,
162      Table_Low_Bound      => 0,
163      Table_Initial        => 100,
164      Table_Increment      => 100,
165      Table_Name           => "Name_Externals");
166
167    -------------------------------------
168    -- Local Subprograms and Variables --
169    -------------------------------------
170
171    function Adjust_External_Name_Case (N : Node_Id) return Node_Id;
172    --  This routine is used for possible casing adjustment of an explicit
173    --  external name supplied as a string literal (the node N), according to
174    --  the casing requirement of Opt.External_Name_Casing. If this is set to
175    --  As_Is, then the string literal is returned unchanged, but if it is set
176    --  to Uppercase or Lowercase, then a new string literal with appropriate
177    --  casing is constructed.
178
179    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id;
180    --  If Def_Id refers to a renamed subprogram, then the base subprogram (the
181    --  original one, following the renaming chain) is returned. Otherwise the
182    --  entity is returned unchanged. Should be in Einfo???
183
184    procedure Preanalyze_TC_Args (N, Arg_Req, Arg_Ens : Node_Id);
185    --  Preanalyze the boolean expressions in the Requires and Ensures arguments
186    --  of a Test_Case pragma if present (possibly Empty). We treat these as
187    --  spec expressions (i.e. similar to a default expression).
188
189    procedure rv;
190    --  This is a dummy function called by the processing for pragma Reviewable.
191    --  It is there for assisting front end debugging. By placing a Reviewable
192    --  pragma in the source program, a breakpoint on rv catches this place in
193    --  the source, allowing convenient stepping to the point of interest.
194
195    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id);
196    --  Place semantic information on the argument of an Elaborate/Elaborate_All
197    --  pragma. Entity name for unit and its parents is taken from item in
198    --  previous with_clause that mentions the unit.
199
200    -------------------------------
201    -- Adjust_External_Name_Case --
202    -------------------------------
203
204    function Adjust_External_Name_Case (N : Node_Id) return Node_Id is
205       CC : Char_Code;
206
207    begin
208       --  Adjust case of literal if required
209
210       if Opt.External_Name_Exp_Casing = As_Is then
211          return N;
212
213       else
214          --  Copy existing string
215
216          Start_String;
217
218          --  Set proper casing
219
220          for J in 1 .. String_Length (Strval (N)) loop
221             CC := Get_String_Char (Strval (N), J);
222
223             if Opt.External_Name_Exp_Casing = Uppercase
224               and then CC >= Get_Char_Code ('a')
225               and then CC <= Get_Char_Code ('z')
226             then
227                Store_String_Char (CC - 32);
228
229             elsif Opt.External_Name_Exp_Casing = Lowercase
230               and then CC >= Get_Char_Code ('A')
231               and then CC <= Get_Char_Code ('Z')
232             then
233                Store_String_Char (CC + 32);
234
235             else
236                Store_String_Char (CC);
237             end if;
238          end loop;
239
240          return
241            Make_String_Literal (Sloc (N),
242              Strval => End_String);
243       end if;
244    end Adjust_External_Name_Case;
245
246    ------------------------------
247    -- Analyze_PPC_In_Decl_Part --
248    ------------------------------
249
250    procedure Analyze_PPC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
251       Arg1 : constant Node_Id := First (Pragma_Argument_Associations (N));
252
253    begin
254       --  Install formals and push subprogram spec onto scope stack so that we
255       --  can see the formals from the pragma.
256
257       Install_Formals (S);
258       Push_Scope (S);
259
260       --  Preanalyze the boolean expression, we treat this as a spec expression
261       --  (i.e. similar to a default expression).
262
263       Preanalyze_Spec_Expression (Get_Pragma_Arg (Arg1), Standard_Boolean);
264
265       --  In ASIS mode, for a pragma generated from a source aspect, also
266       --  analyze the original aspect expression.
267
268       if ASIS_Mode
269         and then Present (Corresponding_Aspect (N))
270       then
271          Preanalyze_Spec_Expression
272            (Expression (Corresponding_Aspect (N)), Standard_Boolean);
273       end if;
274
275       --  For a class-wide condition, a reference to a controlling formal must
276       --  be interpreted as having the class-wide type (or an access to such)
277       --  so that the inherited condition can be properly applied to any
278       --  overriding operation (see ARM12 6.6.1 (7)).
279
280       if Class_Present (N) then
281          Class_Wide_Condition : declare
282             T   : constant Entity_Id := Find_Dispatching_Type (S);
283
284             ACW : Entity_Id := Empty;
285             --  Access to T'class, created if there is a controlling formal
286             --  that is an access parameter.
287
288             function Get_ACW return Entity_Id;
289             --  If the expression has a reference to an controlling access
290             --  parameter, create an access to T'class for the necessary
291             --  conversions if one does not exist.
292
293             function Process (N : Node_Id) return Traverse_Result;
294             --  ARM 6.1.1: Within the expression for a Pre'Class or Post'Class
295             --  aspect for a primitive subprogram of a tagged type T, a name
296             --  that denotes a formal parameter of type T is interpreted as
297             --  having type T'Class. Similarly, a name that denotes a formal
298             --  accessparameter of type access-to-T is interpreted as having
299             --  type access-to-T'Class. This ensures the expression is well-
300             --  defined for a primitive subprogram of a type descended from T.
301
302             -------------
303             -- Get_ACW --
304             -------------
305
306             function Get_ACW return Entity_Id is
307                Loc  : constant Source_Ptr := Sloc (N);
308                Decl : Node_Id;
309
310             begin
311                if No (ACW) then
312                   Decl := Make_Full_Type_Declaration (Loc,
313                     Defining_Identifier => Make_Temporary (Loc, 'T'),
314                     Type_Definition =>
315                        Make_Access_To_Object_Definition (Loc,
316                        Subtype_Indication =>
317                          New_Occurrence_Of (Class_Wide_Type (T), Loc),
318                        All_Present => True));
319
320                   Insert_Before (Unit_Declaration_Node (S), Decl);
321                   Analyze (Decl);
322                   ACW := Defining_Identifier (Decl);
323                   Freeze_Before (Unit_Declaration_Node (S), ACW);
324                end if;
325
326                return ACW;
327             end Get_ACW;
328
329             -------------
330             -- Process --
331             -------------
332
333             function Process (N : Node_Id) return Traverse_Result is
334                Loc : constant Source_Ptr := Sloc (N);
335                Typ : Entity_Id;
336
337             begin
338                if Is_Entity_Name (N)
339                  and then Is_Formal (Entity (N))
340                  and then Nkind (Parent (N)) /= N_Type_Conversion
341                then
342                   if Etype (Entity (N)) = T then
343                      Typ := Class_Wide_Type (T);
344
345                   elsif Is_Access_Type (Etype (Entity (N)))
346                     and then Designated_Type (Etype (Entity (N))) = T
347                   then
348                      Typ := Get_ACW;
349                   else
350                      Typ := Empty;
351                   end if;
352
353                   if Present (Typ) then
354                      Rewrite (N,
355                        Make_Type_Conversion (Loc,
356                          Subtype_Mark =>
357                            New_Occurrence_Of (Typ, Loc),
358                          Expression  => New_Occurrence_Of (Entity (N), Loc)));
359                      Set_Etype (N, Typ);
360                   end if;
361                end if;
362
363                return OK;
364             end Process;
365
366             procedure Replace_Type is new Traverse_Proc (Process);
367
368          --  Start of processing for Class_Wide_Condition
369
370          begin
371             if not Present (T) then
372                Error_Msg_Name_1 :=
373                  Chars (Identifier (Corresponding_Aspect (N)));
374
375                Error_Msg_Name_2 := Name_Class;
376
377                Error_Msg_N
378                  ("aspect `%''%` can only be specified for a primitive " &
379                   "operation of a tagged type",
380                   Corresponding_Aspect (N));
381             end if;
382
383             Replace_Type (Get_Pragma_Arg (Arg1));
384          end Class_Wide_Condition;
385       end if;
386
387       --  Remove the subprogram from the scope stack now that the pre-analysis
388       --  of the precondition/postcondition is done.
389
390       End_Scope;
391    end Analyze_PPC_In_Decl_Part;
392
393    --------------------
394    -- Analyze_Pragma --
395    --------------------
396
397    procedure Analyze_Pragma (N : Node_Id) is
398       Loc     : constant Source_Ptr := Sloc (N);
399       Prag_Id : Pragma_Id;
400
401       Pname : Name_Id;
402       --  Name of the source pragma, or name of the corresponding aspect for
403       --  pragmas which originate in a source aspect. In the latter case, the
404       --  name may be different from the pragma name.
405
406       Pragma_Exit : exception;
407       --  This exception is used to exit pragma processing completely. It is
408       --  used when an error is detected, and no further processing is
409       --  required. It is also used if an earlier error has left the tree in
410       --  a state where the pragma should not be processed.
411
412       Arg_Count : Nat;
413       --  Number of pragma argument associations
414
415       Arg1 : Node_Id;
416       Arg2 : Node_Id;
417       Arg3 : Node_Id;
418       Arg4 : Node_Id;
419       --  First four pragma arguments (pragma argument association nodes, or
420       --  Empty if the corresponding argument does not exist).
421
422       type Name_List is array (Natural range <>) of Name_Id;
423       type Args_List is array (Natural range <>) of Node_Id;
424       --  Types used for arguments to Check_Arg_Order and Gather_Associations
425
426       procedure Ada_2005_Pragma;
427       --  Called for pragmas defined in Ada 2005, that are not in Ada 95. In
428       --  Ada 95 mode, these are implementation defined pragmas, so should be
429       --  caught by the No_Implementation_Pragmas restriction.
430
431       procedure Ada_2012_Pragma;
432       --  Called for pragmas defined in Ada 2012, that are not in Ada 95 or 05.
433       --  In Ada 95 or 05 mode, these are implementation defined pragmas, so
434       --  should be caught by the No_Implementation_Pragmas restriction.
435
436       procedure Check_Ada_83_Warning;
437       --  Issues a warning message for the current pragma if operating in Ada
438       --  83 mode (used for language pragmas that are not a standard part of
439       --  Ada 83). This procedure does not raise Error_Pragma. Also notes use
440       --  of 95 pragma.
441
442       procedure Check_Arg_Count (Required : Nat);
443       --  Check argument count for pragma is equal to given parameter. If not,
444       --  then issue an error message and raise Pragma_Exit.
445
446       --  Note: all routines whose name is Check_Arg_Is_xxx take an argument
447       --  Arg which can either be a pragma argument association, in which case
448       --  the check is applied to the expression of the association or an
449       --  expression directly.
450
451       procedure Check_Arg_Is_External_Name (Arg : Node_Id);
452       --  Check that an argument has the right form for an EXTERNAL_NAME
453       --  parameter of an extended import/export pragma. The rule is that the
454       --  name must be an identifier or string literal (in Ada 83 mode) or a
455       --  static string expression (in Ada 95 mode).
456
457       procedure Check_Arg_Is_Identifier (Arg : Node_Id);
458       --  Check the specified argument Arg to make sure that it is an
459       --  identifier. If not give error and raise Pragma_Exit.
460
461       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id);
462       --  Check the specified argument Arg to make sure that it is an integer
463       --  literal. If not give error and raise Pragma_Exit.
464
465       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id);
466       --  Check the specified argument Arg to make sure that it has the proper
467       --  syntactic form for a local name and meets the semantic requirements
468       --  for a local name. The local name is analyzed as part of the
469       --  processing for this call. In addition, the local name is required
470       --  to represent an entity at the library level.
471
472       procedure Check_Arg_Is_Local_Name (Arg : Node_Id);
473       --  Check the specified argument Arg to make sure that it has the proper
474       --  syntactic form for a local name and meets the semantic requirements
475       --  for a local name. The local name is analyzed as part of the
476       --  processing for this call.
477
478       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id);
479       --  Check the specified argument Arg to make sure that it is a valid
480       --  locking policy name. If not give error and raise Pragma_Exit.
481
482       procedure Check_Arg_Is_One_Of
483         (Arg                : Node_Id;
484          N1, N2             : Name_Id);
485       procedure Check_Arg_Is_One_Of
486         (Arg                : Node_Id;
487          N1, N2, N3         : Name_Id);
488       procedure Check_Arg_Is_One_Of
489         (Arg                : Node_Id;
490          N1, N2, N3, N4     : Name_Id);
491       procedure Check_Arg_Is_One_Of
492         (Arg                : Node_Id;
493          N1, N2, N3, N4, N5 : Name_Id);
494       --  Check the specified argument Arg to make sure that it is an
495       --  identifier whose name matches either N1 or N2 (or N3, N4, N5 if
496       --  present). If not then give error and raise Pragma_Exit.
497
498       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id);
499       --  Check the specified argument Arg to make sure that it is a valid
500       --  queuing policy name. If not give error and raise Pragma_Exit.
501
502       procedure Check_Arg_Is_Static_Expression
503         (Arg : Node_Id;
504          Typ : Entity_Id := Empty);
505       --  Check the specified argument Arg to make sure that it is a static
506       --  expression of the given type (i.e. it will be analyzed and resolved
507       --  using this type, which can be any valid argument to Resolve, e.g.
508       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
509       --  Typ is left Empty, then any static expression is allowed.
510
511       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id);
512       --  Check the specified argument Arg to make sure that it is a valid task
513       --  dispatching policy name. If not give error and raise Pragma_Exit.
514
515       procedure Check_Arg_Order (Names : Name_List);
516       --  Checks for an instance of two arguments with identifiers for the
517       --  current pragma which are not in the sequence indicated by Names,
518       --  and if so, generates a fatal message about bad order of arguments.
519
520       procedure Check_At_Least_N_Arguments (N : Nat);
521       --  Check there are at least N arguments present
522
523       procedure Check_At_Most_N_Arguments (N : Nat);
524       --  Check there are no more than N arguments present
525
526       procedure Check_Component
527         (Comp            : Node_Id;
528          UU_Typ          : Entity_Id;
529          In_Variant_Part : Boolean := False);
530       --  Examine an Unchecked_Union component for correct use of per-object
531       --  constrained subtypes, and for restrictions on finalizable components.
532       --  UU_Typ is the related Unchecked_Union type. Flag In_Variant_Part
533       --  should be set when Comp comes from a record variant.
534
535       procedure Check_Duplicate_Pragma (E : Entity_Id);
536       --  Check if a pragma of the same name as the current pragma is already
537       --  chained as a rep pragma to the given entity. If so give a message
538       --  about the duplicate, and then raise Pragma_Exit so does not return.
539       --  Also checks for delayed aspect specification node in the chain.
540
541       procedure Check_Duplicated_Export_Name (Nam : Node_Id);
542       --  Nam is an N_String_Literal node containing the external name set by
543       --  an Import or Export pragma (or extended Import or Export pragma).
544       --  This procedure checks for possible duplications if this is the export
545       --  case, and if found, issues an appropriate error message.
546
547       procedure Check_Expr_Is_Static_Expression
548         (Expr : Node_Id;
549          Typ  : Entity_Id := Empty);
550       --  Check the specified expression Expr to make sure that it is a static
551       --  expression of the given type (i.e. it will be analyzed and resolved
552       --  using this type, which can be any valid argument to Resolve, e.g.
553       --  Any_Integer is OK). If not, given error and raise Pragma_Exit. If
554       --  Typ is left Empty, then any static expression is allowed.
555
556       procedure Check_First_Subtype (Arg : Node_Id);
557       --  Checks that Arg, whose expression is an entity name, references a
558       --  first subtype.
559
560       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id);
561       --  Checks that the given argument has an identifier, and if so, requires
562       --  it to match the given identifier name. If there is no identifier, or
563       --  a non-matching identifier, then an error message is given and
564       --  Pragma_Exit is raised.
565
566       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id);
567       --  Checks that the given argument has an identifier, and if so, requires
568       --  it to match one of the given identifier names. If there is no
569       --  identifier, or a non-matching identifier, then an error message is
570       --  given and Pragma_Exit is raised.
571
572       procedure Check_In_Main_Program;
573       --  Common checks for pragmas that appear within a main program
574       --  (Priority, Main_Storage, Time_Slice, Relative_Deadline, CPU).
575
576       procedure Check_Interrupt_Or_Attach_Handler;
577       --  Common processing for first argument of pragma Interrupt_Handler or
578       --  pragma Attach_Handler.
579
580       procedure Check_Is_In_Decl_Part_Or_Package_Spec;
581       --  Check that pragma appears in a declarative part, or in a package
582       --  specification, i.e. that it does not occur in a statement sequence
583       --  in a body.
584
585       procedure Check_No_Identifier (Arg : Node_Id);
586       --  Checks that the given argument does not have an identifier. If
587       --  an identifier is present, then an error message is issued, and
588       --  Pragma_Exit is raised.
589
590       procedure Check_No_Identifiers;
591       --  Checks that none of the arguments to the pragma has an identifier.
592       --  If any argument has an identifier, then an error message is issued,
593       --  and Pragma_Exit is raised.
594
595       procedure Check_No_Link_Name;
596       --  Checks that no link name is specified
597
598       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id);
599       --  Checks if the given argument has an identifier, and if so, requires
600       --  it to match the given identifier name. If there is a non-matching
601       --  identifier, then an error message is given and Pragma_Exit is raised.
602
603       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String);
604       --  Checks if the given argument has an identifier, and if so, requires
605       --  it to match the given identifier name. If there is a non-matching
606       --  identifier, then an error message is given and Pragma_Exit is raised.
607       --  In this version of the procedure, the identifier name is given as
608       --  a string with lower case letters.
609
610       procedure Check_Precondition_Postcondition (In_Body : out Boolean);
611       --  Called to process a precondition or postcondition pragma. There are
612       --  three cases:
613       --
614       --    The pragma appears after a subprogram spec
615       --
616       --      If the corresponding check is not enabled, the pragma is analyzed
617       --      but otherwise ignored and control returns with In_Body set False.
618       --
619       --      If the check is enabled, then the first step is to analyze the
620       --      pragma, but this is skipped if the subprogram spec appears within
621       --      a package specification (because this is the case where we delay
622       --      analysis till the end of the spec). Then (whether or not it was
623       --      analyzed), the pragma is chained to the subprogram in question
624       --      (using Spec_PPC_List and Next_Pragma) and control returns to the
625       --      caller with In_Body set False.
626       --
627       --    The pragma appears at the start of subprogram body declarations
628       --
629       --      In this case an immediate return to the caller is made with
630       --      In_Body set True, and the pragma is NOT analyzed.
631       --
632       --    In all other cases, an error message for bad placement is given
633
634       procedure Check_Static_Constraint (Constr : Node_Id);
635       --  Constr is a constraint from an N_Subtype_Indication node from a
636       --  component constraint in an Unchecked_Union type. This routine checks
637       --  that the constraint is static as required by the restrictions for
638       --  Unchecked_Union.
639
640       procedure Check_Test_Case;
641       --  Called to process a test-case pragma. The treatment is similar to the
642       --  one for pre- and postcondition in Check_Precondition_Postcondition,
643       --  except the placement rules for the test-case pragma are stricter.
644       --  This pragma may only occur after a subprogram spec declared directly
645       --  in a package spec unit. In this case, the pragma is chained to the
646       --  subprogram in question (using Spec_TC_List and Next_Pragma) and
647       --  analysis of the pragma is delayed till the end of the spec. In
648       --  all other cases, an error message for bad placement is given.
649
650       procedure Check_Valid_Configuration_Pragma;
651       --  Legality checks for placement of a configuration pragma
652
653       procedure Check_Valid_Library_Unit_Pragma;
654       --  Legality checks for library unit pragmas. A special case arises for
655       --  pragmas in generic instances that come from copies of the original
656       --  library unit pragmas in the generic templates. In the case of other
657       --  than library level instantiations these can appear in contexts which
658       --  would normally be invalid (they only apply to the original template
659       --  and to library level instantiations), and they are simply ignored,
660       --  which is implemented by rewriting them as null statements.
661
662       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id);
663       --  Check an Unchecked_Union variant for lack of nested variants and
664       --  presence of at least one component. UU_Typ is the related Unchecked_
665       --  Union type.
666
667       procedure Error_Pragma (Msg : String);
668       pragma No_Return (Error_Pragma);
669       --  Outputs error message for current pragma. The message contains a %
670       --  that will be replaced with the pragma name, and the flag is placed
671       --  on the pragma itself. Pragma_Exit is then raised.
672
673       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id);
674       pragma No_Return (Error_Pragma_Arg);
675       --  Outputs error message for current pragma. The message may contain
676       --  a % that will be replaced with the pragma name. The parameter Arg
677       --  may either be a pragma argument association, in which case the flag
678       --  is placed on the expression of this association, or an expression,
679       --  in which case the flag is placed directly on the expression. The
680       --  message is placed using Error_Msg_N, so the message may also contain
681       --  an & insertion character which will reference the given Arg value.
682       --  After placing the message, Pragma_Exit is raised.
683
684       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id);
685       pragma No_Return (Error_Pragma_Arg);
686       --  Similar to above form of Error_Pragma_Arg except that two messages
687       --  are provided, the second is a continuation comment starting with \.
688
689       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id);
690       pragma No_Return (Error_Pragma_Arg_Ident);
691       --  Outputs error message for current pragma. The message may contain
692       --  a % that will be replaced with the pragma name. The parameter Arg
693       --  must be a pragma argument association with a non-empty identifier
694       --  (i.e. its Chars field must be set), and the error message is placed
695       --  on the identifier. The message is placed using Error_Msg_N so
696       --  the message may also contain an & insertion character which will
697       --  reference the identifier. After placing the message, Pragma_Exit
698       --  is raised.
699
700       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id);
701       pragma No_Return (Error_Pragma_Ref);
702       --  Outputs error message for current pragma. The message may contain
703       --  a % that will be replaced with the pragma name. The parameter Ref
704       --  must be an entity whose name can be referenced by & and sloc by #.
705       --  After placing the message, Pragma_Exit is raised.
706
707       function Find_Lib_Unit_Name return Entity_Id;
708       --  Used for a library unit pragma to find the entity to which the
709       --  library unit pragma applies, returns the entity found.
710
711       procedure Find_Program_Unit_Name (Id : Node_Id);
712       --  If the pragma is a compilation unit pragma, the id must denote the
713       --  compilation unit in the same compilation, and the pragma must appear
714       --  in the list of preceding or trailing pragmas. If it is a program
715       --  unit pragma that is not a compilation unit pragma, then the
716       --  identifier must be visible.
717
718       function Find_Unique_Parameterless_Procedure
719         (Name : Entity_Id;
720          Arg  : Node_Id) return Entity_Id;
721       --  Used for a procedure pragma to find the unique parameterless
722       --  procedure identified by Name, returns it if it exists, otherwise
723       --  errors out and uses Arg as the pragma argument for the message.
724
725       procedure Fix_Error (Msg : in out String);
726       --  This is called prior to issuing an error message. Msg is a string
727       --  that typically contains the substring "pragma". If the current pragma
728       --  comes from an aspect, each such "pragma" substring is replaced with
729       --  the characters "aspect", and if Error_Msg_Name_1 is Name_Precondition
730       --  (resp Name_Postcondition) it is changed to Name_Pre (resp Name_Post).
731
732       procedure Gather_Associations
733         (Names : Name_List;
734          Args  : out Args_List);
735       --  This procedure is used to gather the arguments for a pragma that
736       --  permits arbitrary ordering of parameters using the normal rules
737       --  for named and positional parameters. The Names argument is a list
738       --  of Name_Id values that corresponds to the allowed pragma argument
739       --  association identifiers in order. The result returned in Args is
740       --  a list of corresponding expressions that are the pragma arguments.
741       --  Note that this is a list of expressions, not of pragma argument
742       --  associations (Gather_Associations has completely checked all the
743       --  optional identifiers when it returns). An entry in Args is Empty
744       --  on return if the corresponding argument is not present.
745
746       procedure GNAT_Pragma;
747       --  Called for all GNAT defined pragmas to check the relevant restriction
748       --  (No_Implementation_Pragmas).
749
750       function Is_Before_First_Decl
751         (Pragma_Node : Node_Id;
752          Decls       : List_Id) return Boolean;
753       --  Return True if Pragma_Node is before the first declarative item in
754       --  Decls where Decls is the list of declarative items.
755
756       function Is_Configuration_Pragma return Boolean;
757       --  Determines if the placement of the current pragma is appropriate
758       --  for a configuration pragma.
759
760       function Is_In_Context_Clause return Boolean;
761       --  Returns True if pragma appears within the context clause of a unit,
762       --  and False for any other placement (does not generate any messages).
763
764       function Is_Static_String_Expression (Arg : Node_Id) return Boolean;
765       --  Analyzes the argument, and determines if it is a static string
766       --  expression, returns True if so, False if non-static or not String.
767
768       procedure Pragma_Misplaced;
769       pragma No_Return (Pragma_Misplaced);
770       --  Issue fatal error message for misplaced pragma
771
772       procedure Process_Atomic_Shared_Volatile;
773       --  Common processing for pragmas Atomic, Shared, Volatile. Note that
774       --  Shared is an obsolete Ada 83 pragma, treated as being identical
775       --  in effect to pragma Atomic.
776
777       procedure Process_Compile_Time_Warning_Or_Error;
778       --  Common processing for Compile_Time_Error and Compile_Time_Warning
779
780       procedure Process_Convention
781         (C   : out Convention_Id;
782          Ent : out Entity_Id);
783       --  Common processing for Convention, Interface, Import and Export.
784       --  Checks first two arguments of pragma, and sets the appropriate
785       --  convention value in the specified entity or entities. On return
786       --  C is the convention, Ent is the referenced entity.
787
788       procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id);
789       --  Common processing for Disable/Enable_Atomic_Synchronization. Nam is
790       --  Name_Suppress for Disable and Name_Unsuppress for Enable.
791
792       procedure Process_Extended_Import_Export_Exception_Pragma
793         (Arg_Internal : Node_Id;
794          Arg_External : Node_Id;
795          Arg_Form     : Node_Id;
796          Arg_Code     : Node_Id);
797       --  Common processing for the pragmas Import/Export_Exception. The three
798       --  arguments correspond to the three named parameters of the pragma. An
799       --  argument is empty if the corresponding parameter is not present in
800       --  the pragma.
801
802       procedure Process_Extended_Import_Export_Object_Pragma
803         (Arg_Internal : Node_Id;
804          Arg_External : Node_Id;
805          Arg_Size     : Node_Id);
806       --  Common processing for the pragmas Import/Export_Object. The three
807       --  arguments correspond to the three named parameters of the pragmas. An
808       --  argument is empty if the corresponding parameter is not present in
809       --  the pragma.
810
811       procedure Process_Extended_Import_Export_Internal_Arg
812         (Arg_Internal : Node_Id := Empty);
813       --  Common processing for all extended Import and Export pragmas. The
814       --  argument is the pragma parameter for the Internal argument. If
815       --  Arg_Internal is empty or inappropriate, an error message is posted.
816       --  Otherwise, on normal return, the Entity_Field of Arg_Internal is
817       --  set to identify the referenced entity.
818
819       procedure Process_Extended_Import_Export_Subprogram_Pragma
820         (Arg_Internal                 : Node_Id;
821          Arg_External                 : Node_Id;
822          Arg_Parameter_Types          : Node_Id;
823          Arg_Result_Type              : Node_Id := Empty;
824          Arg_Mechanism                : Node_Id;
825          Arg_Result_Mechanism         : Node_Id := Empty;
826          Arg_First_Optional_Parameter : Node_Id := Empty);
827       --  Common processing for all extended Import and Export pragmas applying
828       --  to subprograms. The caller omits any arguments that do not apply to
829       --  the pragma in question (for example, Arg_Result_Type can be non-Empty
830       --  only in the Import_Function and Export_Function cases). The argument
831       --  names correspond to the allowed pragma association identifiers.
832
833       procedure Process_Generic_List;
834       --  Common processing for Share_Generic and Inline_Generic
835
836       procedure Process_Import_Or_Interface;
837       --  Common processing for Import of Interface
838
839       procedure Process_Import_Predefined_Type;
840       --  Processing for completing a type with pragma Import. This is used
841       --  to declare types that match predefined C types, especially for cases
842       --  without corresponding Ada predefined type.
843
844       procedure Process_Inline (Active : Boolean);
845       --  Common processing for Inline and Inline_Always. The parameter
846       --  indicates if the inline pragma is active, i.e. if it should actually
847       --  cause inlining to occur.
848
849       procedure Process_Interface_Name
850         (Subprogram_Def : Entity_Id;
851          Ext_Arg        : Node_Id;
852          Link_Arg       : Node_Id);
853       --  Given the last two arguments of pragma Import, pragma Export, or
854       --  pragma Interface_Name, performs validity checks and sets the
855       --  Interface_Name field of the given subprogram entity to the
856       --  appropriate external or link name, depending on the arguments given.
857       --  Ext_Arg is always present, but Link_Arg may be missing. Note that
858       --  Ext_Arg may represent the Link_Name if Link_Arg is missing, and
859       --  appropriate named notation is used for Ext_Arg. If neither Ext_Arg
860       --  nor Link_Arg is present, the interface name is set to the default
861       --  from the subprogram name.
862
863       procedure Process_Interrupt_Or_Attach_Handler;
864       --  Common processing for Interrupt and Attach_Handler pragmas
865
866       procedure Process_Restrictions_Or_Restriction_Warnings (Warn : Boolean);
867       --  Common processing for Restrictions and Restriction_Warnings pragmas.
868       --  Warn is True for Restriction_Warnings, or for Restrictions if the
869       --  flag Treat_Restrictions_As_Warnings is set, and False if this flag
870       --  is not set in the Restrictions case.
871
872       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean);
873       --  Common processing for Suppress and Unsuppress. The boolean parameter
874       --  Suppress_Case is True for the Suppress case, and False for the
875       --  Unsuppress case.
876
877       procedure Set_Exported (E : Entity_Id; Arg : Node_Id);
878       --  This procedure sets the Is_Exported flag for the given entity,
879       --  checking that the entity was not previously imported. Arg is
880       --  the argument that specified the entity. A check is also made
881       --  for exporting inappropriate entities.
882
883       procedure Set_Extended_Import_Export_External_Name
884         (Internal_Ent : Entity_Id;
885          Arg_External : Node_Id);
886       --  Common processing for all extended import export pragmas. The first
887       --  argument, Internal_Ent, is the internal entity, which has already
888       --  been checked for validity by the caller. Arg_External is from the
889       --  Import or Export pragma, and may be null if no External parameter
890       --  was present. If Arg_External is present and is a non-null string
891       --  (a null string is treated as the default), then the Interface_Name
892       --  field of Internal_Ent is set appropriately.
893
894       procedure Set_Imported (E : Entity_Id);
895       --  This procedure sets the Is_Imported flag for the given entity,
896       --  checking that it is not previously exported or imported.
897
898       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id);
899       --  Mech is a parameter passing mechanism (see Import_Function syntax
900       --  for MECHANISM_NAME). This routine checks that the mechanism argument
901       --  has the right form, and if not issues an error message. If the
902       --  argument has the right form then the Mechanism field of Ent is
903       --  set appropriately.
904
905       procedure Set_Ravenscar_Profile (N : Node_Id);
906       --  Activate the set of configuration pragmas and restrictions that make
907       --  up the Ravenscar Profile. N is the corresponding pragma node, which
908       --  is used for error messages on any constructs that violate the
909       --  profile.
910
911       ---------------------
912       -- Ada_2005_Pragma --
913       ---------------------
914
915       procedure Ada_2005_Pragma is
916       begin
917          if Ada_Version <= Ada_95 then
918             Check_Restriction (No_Implementation_Pragmas, N);
919          end if;
920       end Ada_2005_Pragma;
921
922       ---------------------
923       -- Ada_2012_Pragma --
924       ---------------------
925
926       procedure Ada_2012_Pragma is
927       begin
928          if Ada_Version <= Ada_2005 then
929             Check_Restriction (No_Implementation_Pragmas, N);
930          end if;
931       end Ada_2012_Pragma;
932
933       --------------------------
934       -- Check_Ada_83_Warning --
935       --------------------------
936
937       procedure Check_Ada_83_Warning is
938       begin
939          if Ada_Version = Ada_83 and then Comes_From_Source (N) then
940             Error_Msg_N ("(Ada 83) pragma& is non-standard?", N);
941          end if;
942       end Check_Ada_83_Warning;
943
944       ---------------------
945       -- Check_Arg_Count --
946       ---------------------
947
948       procedure Check_Arg_Count (Required : Nat) is
949       begin
950          if Arg_Count /= Required then
951             Error_Pragma ("wrong number of arguments for pragma%");
952          end if;
953       end Check_Arg_Count;
954
955       --------------------------------
956       -- Check_Arg_Is_External_Name --
957       --------------------------------
958
959       procedure Check_Arg_Is_External_Name (Arg : Node_Id) is
960          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
961
962       begin
963          if Nkind (Argx) = N_Identifier then
964             return;
965
966          else
967             Analyze_And_Resolve (Argx, Standard_String);
968
969             if Is_OK_Static_Expression (Argx) then
970                return;
971
972             elsif Etype (Argx) = Any_Type then
973                raise Pragma_Exit;
974
975             --  An interesting special case, if we have a string literal and
976             --  we are in Ada 83 mode, then we allow it even though it will
977             --  not be flagged as static. This allows expected Ada 83 mode
978             --  use of external names which are string literals, even though
979             --  technically these are not static in Ada 83.
980
981             elsif Ada_Version = Ada_83
982               and then Nkind (Argx) = N_String_Literal
983             then
984                return;
985
986             --  Static expression that raises Constraint_Error. This has
987             --  already been flagged, so just exit from pragma processing.
988
989             elsif Is_Static_Expression (Argx) then
990                raise Pragma_Exit;
991
992             --  Here we have a real error (non-static expression)
993
994             else
995                Error_Msg_Name_1 := Pname;
996
997                declare
998                   Msg : String :=
999                           "argument for pragma% must be a identifier or "
1000                           & "static string expression!";
1001                begin
1002                   Fix_Error (Msg);
1003                   Flag_Non_Static_Expr (Msg, Argx);
1004                   raise Pragma_Exit;
1005                end;
1006             end if;
1007          end if;
1008       end Check_Arg_Is_External_Name;
1009
1010       -----------------------------
1011       -- Check_Arg_Is_Identifier --
1012       -----------------------------
1013
1014       procedure Check_Arg_Is_Identifier (Arg : Node_Id) is
1015          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1016       begin
1017          if Nkind (Argx) /= N_Identifier then
1018             Error_Pragma_Arg
1019               ("argument for pragma% must be identifier", Argx);
1020          end if;
1021       end Check_Arg_Is_Identifier;
1022
1023       ----------------------------------
1024       -- Check_Arg_Is_Integer_Literal --
1025       ----------------------------------
1026
1027       procedure Check_Arg_Is_Integer_Literal (Arg : Node_Id) is
1028          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1029       begin
1030          if Nkind (Argx) /= N_Integer_Literal then
1031             Error_Pragma_Arg
1032               ("argument for pragma% must be integer literal", Argx);
1033          end if;
1034       end Check_Arg_Is_Integer_Literal;
1035
1036       -------------------------------------------
1037       -- Check_Arg_Is_Library_Level_Local_Name --
1038       -------------------------------------------
1039
1040       --  LOCAL_NAME ::=
1041       --    DIRECT_NAME
1042       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1043       --  | library_unit_NAME
1044
1045       procedure Check_Arg_Is_Library_Level_Local_Name (Arg : Node_Id) is
1046       begin
1047          Check_Arg_Is_Local_Name (Arg);
1048
1049          if not Is_Library_Level_Entity (Entity (Get_Pragma_Arg (Arg)))
1050            and then Comes_From_Source (N)
1051          then
1052             Error_Pragma_Arg
1053               ("argument for pragma% must be library level entity", Arg);
1054          end if;
1055       end Check_Arg_Is_Library_Level_Local_Name;
1056
1057       -----------------------------
1058       -- Check_Arg_Is_Local_Name --
1059       -----------------------------
1060
1061       --  LOCAL_NAME ::=
1062       --    DIRECT_NAME
1063       --  | DIRECT_NAME'ATTRIBUTE_DESIGNATOR
1064       --  | library_unit_NAME
1065
1066       procedure Check_Arg_Is_Local_Name (Arg : Node_Id) is
1067          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1068
1069       begin
1070          Analyze (Argx);
1071
1072          if Nkind (Argx) not in N_Direct_Name
1073            and then (Nkind (Argx) /= N_Attribute_Reference
1074                       or else Present (Expressions (Argx))
1075                       or else Nkind (Prefix (Argx)) /= N_Identifier)
1076            and then (not Is_Entity_Name (Argx)
1077                       or else not Is_Compilation_Unit (Entity (Argx)))
1078          then
1079             Error_Pragma_Arg ("argument for pragma% must be local name", Argx);
1080          end if;
1081
1082          --  No further check required if not an entity name
1083
1084          if not Is_Entity_Name (Argx) then
1085             null;
1086
1087          else
1088             declare
1089                OK   : Boolean;
1090                Ent  : constant Entity_Id := Entity (Argx);
1091                Scop : constant Entity_Id := Scope (Ent);
1092             begin
1093                --  Case of a pragma applied to a compilation unit: pragma must
1094                --  occur immediately after the program unit in the compilation.
1095
1096                if Is_Compilation_Unit (Ent) then
1097                   declare
1098                      Decl : constant Node_Id := Unit_Declaration_Node (Ent);
1099
1100                   begin
1101                      --  Case of pragma placed immediately after spec
1102
1103                      if Parent (N) = Aux_Decls_Node (Parent (Decl)) then
1104                         OK := True;
1105
1106                      --  Case of pragma placed immediately after body
1107
1108                      elsif Nkind (Decl) = N_Subprogram_Declaration
1109                              and then Present (Corresponding_Body (Decl))
1110                      then
1111                         OK := Parent (N) =
1112                                 Aux_Decls_Node
1113                                   (Parent (Unit_Declaration_Node
1114                                              (Corresponding_Body (Decl))));
1115
1116                      --  All other cases are illegal
1117
1118                      else
1119                         OK := False;
1120                      end if;
1121                   end;
1122
1123                --  Special restricted placement rule from 10.2.1(11.8/2)
1124
1125                elsif Is_Generic_Formal (Ent)
1126                        and then Prag_Id = Pragma_Preelaborable_Initialization
1127                then
1128                   OK := List_Containing (N) =
1129                           Generic_Formal_Declarations
1130                             (Unit_Declaration_Node (Scop));
1131
1132                --  Default case, just check that the pragma occurs in the scope
1133                --  of the entity denoted by the name.
1134
1135                else
1136                   OK := Current_Scope = Scop;
1137                end if;
1138
1139                if not OK then
1140                   Error_Pragma_Arg
1141                     ("pragma% argument must be in same declarative part", Arg);
1142                end if;
1143             end;
1144          end if;
1145       end Check_Arg_Is_Local_Name;
1146
1147       ---------------------------------
1148       -- Check_Arg_Is_Locking_Policy --
1149       ---------------------------------
1150
1151       procedure Check_Arg_Is_Locking_Policy (Arg : Node_Id) is
1152          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1153
1154       begin
1155          Check_Arg_Is_Identifier (Argx);
1156
1157          if not Is_Locking_Policy_Name (Chars (Argx)) then
1158             Error_Pragma_Arg ("& is not a valid locking policy name", Argx);
1159          end if;
1160       end Check_Arg_Is_Locking_Policy;
1161
1162       -------------------------
1163       -- Check_Arg_Is_One_Of --
1164       -------------------------
1165
1166       procedure Check_Arg_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1167          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1168
1169       begin
1170          Check_Arg_Is_Identifier (Argx);
1171
1172          if Chars (Argx) /= N1 and then Chars (Argx) /= N2 then
1173             Error_Msg_Name_2 := N1;
1174             Error_Msg_Name_3 := N2;
1175             Error_Pragma_Arg ("argument for pragma% must be% or%", Argx);
1176          end if;
1177       end Check_Arg_Is_One_Of;
1178
1179       procedure Check_Arg_Is_One_Of
1180         (Arg        : Node_Id;
1181          N1, N2, N3 : Name_Id)
1182       is
1183          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1184
1185       begin
1186          Check_Arg_Is_Identifier (Argx);
1187
1188          if Chars (Argx) /= N1
1189            and then Chars (Argx) /= N2
1190            and then Chars (Argx) /= N3
1191          then
1192             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1193          end if;
1194       end Check_Arg_Is_One_Of;
1195
1196       procedure Check_Arg_Is_One_Of
1197         (Arg                : Node_Id;
1198          N1, N2, N3, N4     : Name_Id)
1199       is
1200          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1201
1202       begin
1203          Check_Arg_Is_Identifier (Argx);
1204
1205          if Chars (Argx) /= N1
1206            and then Chars (Argx) /= N2
1207            and then Chars (Argx) /= N3
1208            and then Chars (Argx) /= N4
1209          then
1210             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1211          end if;
1212       end Check_Arg_Is_One_Of;
1213
1214       procedure Check_Arg_Is_One_Of
1215         (Arg                : Node_Id;
1216          N1, N2, N3, N4, N5 : Name_Id)
1217       is
1218          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1219
1220       begin
1221          Check_Arg_Is_Identifier (Argx);
1222
1223          if Chars (Argx) /= N1
1224            and then Chars (Argx) /= N2
1225            and then Chars (Argx) /= N3
1226            and then Chars (Argx) /= N4
1227            and then Chars (Argx) /= N5
1228          then
1229             Error_Pragma_Arg ("invalid argument for pragma%", Argx);
1230          end if;
1231       end Check_Arg_Is_One_Of;
1232       ---------------------------------
1233       -- Check_Arg_Is_Queuing_Policy --
1234       ---------------------------------
1235
1236       procedure Check_Arg_Is_Queuing_Policy (Arg : Node_Id) is
1237          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1238
1239       begin
1240          Check_Arg_Is_Identifier (Argx);
1241
1242          if not Is_Queuing_Policy_Name (Chars (Argx)) then
1243             Error_Pragma_Arg ("& is not a valid queuing policy name", Argx);
1244          end if;
1245       end Check_Arg_Is_Queuing_Policy;
1246
1247       ------------------------------------
1248       -- Check_Arg_Is_Static_Expression --
1249       ------------------------------------
1250
1251       procedure Check_Arg_Is_Static_Expression
1252         (Arg : Node_Id;
1253          Typ : Entity_Id := Empty)
1254       is
1255       begin
1256          Check_Expr_Is_Static_Expression (Get_Pragma_Arg (Arg), Typ);
1257       end Check_Arg_Is_Static_Expression;
1258
1259       ------------------------------------------
1260       -- Check_Arg_Is_Task_Dispatching_Policy --
1261       ------------------------------------------
1262
1263       procedure Check_Arg_Is_Task_Dispatching_Policy (Arg : Node_Id) is
1264          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1265
1266       begin
1267          Check_Arg_Is_Identifier (Argx);
1268
1269          if not Is_Task_Dispatching_Policy_Name (Chars (Argx)) then
1270             Error_Pragma_Arg
1271               ("& is not a valid task dispatching policy name", Argx);
1272          end if;
1273       end Check_Arg_Is_Task_Dispatching_Policy;
1274
1275       ---------------------
1276       -- Check_Arg_Order --
1277       ---------------------
1278
1279       procedure Check_Arg_Order (Names : Name_List) is
1280          Arg : Node_Id;
1281
1282          Highest_So_Far : Natural := 0;
1283          --  Highest index in Names seen do far
1284
1285       begin
1286          Arg := Arg1;
1287          for J in 1 .. Arg_Count loop
1288             if Chars (Arg) /= No_Name then
1289                for K in Names'Range loop
1290                   if Chars (Arg) = Names (K) then
1291                      if K < Highest_So_Far then
1292                         Error_Msg_Name_1 := Pname;
1293                         Error_Msg_N
1294                           ("parameters out of order for pragma%", Arg);
1295                         Error_Msg_Name_1 := Names (K);
1296                         Error_Msg_Name_2 := Names (Highest_So_Far);
1297                         Error_Msg_N ("\% must appear before %", Arg);
1298                         raise Pragma_Exit;
1299
1300                      else
1301                         Highest_So_Far := K;
1302                      end if;
1303                   end if;
1304                end loop;
1305             end if;
1306
1307             Arg := Next (Arg);
1308          end loop;
1309       end Check_Arg_Order;
1310
1311       --------------------------------
1312       -- Check_At_Least_N_Arguments --
1313       --------------------------------
1314
1315       procedure Check_At_Least_N_Arguments (N : Nat) is
1316       begin
1317          if Arg_Count < N then
1318             Error_Pragma ("too few arguments for pragma%");
1319          end if;
1320       end Check_At_Least_N_Arguments;
1321
1322       -------------------------------
1323       -- Check_At_Most_N_Arguments --
1324       -------------------------------
1325
1326       procedure Check_At_Most_N_Arguments (N : Nat) is
1327          Arg : Node_Id;
1328       begin
1329          if Arg_Count > N then
1330             Arg := Arg1;
1331             for J in 1 .. N loop
1332                Next (Arg);
1333                Error_Pragma_Arg ("too many arguments for pragma%", Arg);
1334             end loop;
1335          end if;
1336       end Check_At_Most_N_Arguments;
1337
1338       ---------------------
1339       -- Check_Component --
1340       ---------------------
1341
1342       procedure Check_Component
1343         (Comp            : Node_Id;
1344          UU_Typ          : Entity_Id;
1345          In_Variant_Part : Boolean := False)
1346       is
1347          Comp_Id : constant Entity_Id := Defining_Identifier (Comp);
1348          Sindic  : constant Node_Id :=
1349                      Subtype_Indication (Component_Definition (Comp));
1350          Typ     : constant Entity_Id := Etype (Comp_Id);
1351
1352       begin
1353          --  Ada 2005 (AI-216): If a component subtype is subject to a per-
1354          --  object constraint, then the component type shall be an Unchecked_
1355          --  Union.
1356
1357          if Nkind (Sindic) = N_Subtype_Indication
1358            and then Has_Per_Object_Constraint (Comp_Id)
1359            and then not Is_Unchecked_Union (Etype (Subtype_Mark (Sindic)))
1360          then
1361             Error_Msg_N
1362               ("component subtype subject to per-object constraint " &
1363                "must be an Unchecked_Union", Comp);
1364
1365          --  Ada 2012 (AI05-0026): For an unchecked union type declared within
1366          --  the body of a generic unit, or within the body of any of its
1367          --  descendant library units, no part of the type of a component
1368          --  declared in a variant_part of the unchecked union type shall be of
1369          --  a formal private type or formal private extension declared within
1370          --  the formal part of the generic unit.
1371
1372          elsif Ada_Version >= Ada_2012
1373            and then In_Generic_Body (UU_Typ)
1374            and then In_Variant_Part
1375            and then Is_Private_Type (Typ)
1376            and then Is_Generic_Type (Typ)
1377          then
1378             Error_Msg_N
1379               ("component of Unchecked_Union cannot be of generic type", Comp);
1380
1381          elsif Needs_Finalization (Typ) then
1382             Error_Msg_N
1383               ("component of Unchecked_Union cannot be controlled", Comp);
1384
1385          elsif Has_Task (Typ) then
1386             Error_Msg_N
1387               ("component of Unchecked_Union cannot have tasks", Comp);
1388          end if;
1389       end Check_Component;
1390
1391       ----------------------------
1392       -- Check_Duplicate_Pragma --
1393       ----------------------------
1394
1395       procedure Check_Duplicate_Pragma (E : Entity_Id) is
1396          P : Node_Id;
1397
1398       begin
1399          --  Nothing to do if this pragma comes from an aspect specification,
1400          --  since we could not be duplicating a pragma, and we dealt with the
1401          --  case of duplicated aspects in Analyze_Aspect_Specifications.
1402
1403          if From_Aspect_Specification (N) then
1404             return;
1405          end if;
1406
1407          --  Otherwise current pragma may duplicate previous pragma or a
1408          --  previously given aspect specification for the same pragma.
1409
1410          P := Get_Rep_Item_For_Entity (E, Pragma_Name (N));
1411
1412          if Present (P) then
1413             Error_Msg_Name_1 := Pragma_Name (N);
1414             Error_Msg_Sloc := Sloc (P);
1415
1416             if Nkind (P) = N_Aspect_Specification
1417               or else From_Aspect_Specification (P)
1418             then
1419                Error_Msg_NE ("aspect% for & previously given#", N, E);
1420             else
1421                Error_Msg_NE ("pragma% for & duplicates pragma#", N, E);
1422             end if;
1423
1424             raise Pragma_Exit;
1425          end if;
1426       end Check_Duplicate_Pragma;
1427
1428       ----------------------------------
1429       -- Check_Duplicated_Export_Name --
1430       ----------------------------------
1431
1432       procedure Check_Duplicated_Export_Name (Nam : Node_Id) is
1433          String_Val : constant String_Id := Strval (Nam);
1434
1435       begin
1436          --  We are only interested in the export case, and in the case of
1437          --  generics, it is the instance, not the template, that is the
1438          --  problem (the template will generate a warning in any case).
1439
1440          if not Inside_A_Generic
1441            and then (Prag_Id = Pragma_Export
1442                        or else
1443                      Prag_Id = Pragma_Export_Procedure
1444                        or else
1445                      Prag_Id = Pragma_Export_Valued_Procedure
1446                        or else
1447                      Prag_Id = Pragma_Export_Function)
1448          then
1449             for J in Externals.First .. Externals.Last loop
1450                if String_Equal (String_Val, Strval (Externals.Table (J))) then
1451                   Error_Msg_Sloc := Sloc (Externals.Table (J));
1452                   Error_Msg_N ("external name duplicates name given#", Nam);
1453                   exit;
1454                end if;
1455             end loop;
1456
1457             Externals.Append (Nam);
1458          end if;
1459       end Check_Duplicated_Export_Name;
1460
1461       -------------------------------------
1462       -- Check_Expr_Is_Static_Expression --
1463       -------------------------------------
1464
1465       procedure Check_Expr_Is_Static_Expression
1466         (Expr : Node_Id;
1467          Typ  : Entity_Id := Empty)
1468       is
1469       begin
1470          if Present (Typ) then
1471             Analyze_And_Resolve (Expr, Typ);
1472          else
1473             Analyze_And_Resolve (Expr);
1474          end if;
1475
1476          if Is_OK_Static_Expression (Expr) then
1477             return;
1478
1479          elsif Etype (Expr) = Any_Type then
1480             raise Pragma_Exit;
1481
1482          --  An interesting special case, if we have a string literal and we
1483          --  are in Ada 83 mode, then we allow it even though it will not be
1484          --  flagged as static. This allows the use of Ada 95 pragmas like
1485          --  Import in Ada 83 mode. They will of course be flagged with
1486          --  warnings as usual, but will not cause errors.
1487
1488          elsif Ada_Version = Ada_83
1489            and then Nkind (Expr) = N_String_Literal
1490          then
1491             return;
1492
1493          --  Static expression that raises Constraint_Error. This has already
1494          --  been flagged, so just exit from pragma processing.
1495
1496          elsif Is_Static_Expression (Expr) then
1497             raise Pragma_Exit;
1498
1499          --  Finally, we have a real error
1500
1501          else
1502             Error_Msg_Name_1 := Pname;
1503
1504             declare
1505                Msg : String :=
1506                        "argument for pragma% must be a static expression!";
1507             begin
1508                Fix_Error (Msg);
1509                Flag_Non_Static_Expr (Msg, Expr);
1510             end;
1511
1512             raise Pragma_Exit;
1513          end if;
1514       end Check_Expr_Is_Static_Expression;
1515
1516       -------------------------
1517       -- Check_First_Subtype --
1518       -------------------------
1519
1520       procedure Check_First_Subtype (Arg : Node_Id) is
1521          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
1522          Ent  : constant Entity_Id := Entity (Argx);
1523
1524       begin
1525          if Is_First_Subtype (Ent) then
1526             null;
1527
1528          elsif Is_Type (Ent) then
1529             Error_Pragma_Arg
1530               ("pragma% cannot apply to subtype", Argx);
1531
1532          elsif Is_Object (Ent) then
1533             Error_Pragma_Arg
1534               ("pragma% cannot apply to object, requires a type", Argx);
1535
1536          else
1537             Error_Pragma_Arg
1538               ("pragma% cannot apply to&, requires a type", Argx);
1539          end if;
1540       end Check_First_Subtype;
1541
1542       ----------------------
1543       -- Check_Identifier --
1544       ----------------------
1545
1546       procedure Check_Identifier (Arg : Node_Id; Id : Name_Id) is
1547       begin
1548          if Present (Arg)
1549            and then Nkind (Arg) = N_Pragma_Argument_Association
1550          then
1551             if Chars (Arg) = No_Name or else Chars (Arg) /= Id then
1552                Error_Msg_Name_1 := Pname;
1553                Error_Msg_Name_2 := Id;
1554                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1555                raise Pragma_Exit;
1556             end if;
1557          end if;
1558       end Check_Identifier;
1559
1560       --------------------------------
1561       -- Check_Identifier_Is_One_Of --
1562       --------------------------------
1563
1564       procedure Check_Identifier_Is_One_Of (Arg : Node_Id; N1, N2 : Name_Id) is
1565       begin
1566          if Present (Arg)
1567            and then Nkind (Arg) = N_Pragma_Argument_Association
1568          then
1569             if Chars (Arg) = No_Name then
1570                Error_Msg_Name_1 := Pname;
1571                Error_Msg_N ("pragma% argument expects an identifier", Arg);
1572                raise Pragma_Exit;
1573
1574             elsif Chars (Arg) /= N1
1575               and then Chars (Arg) /= N2
1576             then
1577                Error_Msg_Name_1 := Pname;
1578                Error_Msg_N ("invalid identifier for pragma% argument", Arg);
1579                raise Pragma_Exit;
1580             end if;
1581          end if;
1582       end Check_Identifier_Is_One_Of;
1583
1584       ---------------------------
1585       -- Check_In_Main_Program --
1586       ---------------------------
1587
1588       procedure Check_In_Main_Program is
1589          P : constant Node_Id := Parent (N);
1590
1591       begin
1592          --  Must be at in subprogram body
1593
1594          if Nkind (P) /= N_Subprogram_Body then
1595             Error_Pragma ("% pragma allowed only in subprogram");
1596
1597          --  Otherwise warn if obviously not main program
1598
1599          elsif Present (Parameter_Specifications (Specification (P)))
1600            or else not Is_Compilation_Unit (Defining_Entity (P))
1601          then
1602             Error_Msg_Name_1 := Pname;
1603             Error_Msg_N
1604               ("?pragma% is only effective in main program", N);
1605          end if;
1606       end Check_In_Main_Program;
1607
1608       ---------------------------------------
1609       -- Check_Interrupt_Or_Attach_Handler --
1610       ---------------------------------------
1611
1612       procedure Check_Interrupt_Or_Attach_Handler is
1613          Arg1_X : constant Node_Id := Get_Pragma_Arg (Arg1);
1614          Handler_Proc, Proc_Scope : Entity_Id;
1615
1616       begin
1617          Analyze (Arg1_X);
1618
1619          if Prag_Id = Pragma_Interrupt_Handler then
1620             Check_Restriction (No_Dynamic_Attachment, N);
1621          end if;
1622
1623          Handler_Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
1624          Proc_Scope := Scope (Handler_Proc);
1625
1626          --  On AAMP only, a pragma Interrupt_Handler is supported for
1627          --  nonprotected parameterless procedures.
1628
1629          if not AAMP_On_Target
1630            or else Prag_Id = Pragma_Attach_Handler
1631          then
1632             if Ekind (Proc_Scope) /= E_Protected_Type then
1633                Error_Pragma_Arg
1634                  ("argument of pragma% must be protected procedure", Arg1);
1635             end if;
1636
1637             if Parent (N) /= Protected_Definition (Parent (Proc_Scope)) then
1638                Error_Pragma ("pragma% must be in protected definition");
1639             end if;
1640          end if;
1641
1642          if not Is_Library_Level_Entity (Proc_Scope)
1643            or else (AAMP_On_Target
1644                      and then not Is_Library_Level_Entity (Handler_Proc))
1645          then
1646             Error_Pragma_Arg
1647               ("argument for pragma% must be library level entity", Arg1);
1648          end if;
1649
1650          --  AI05-0033: A pragma cannot appear within a generic body, because
1651          --  instance can be in a nested scope. The check that protected type
1652          --  is itself a library-level declaration is done elsewhere.
1653
1654          --  Note: we omit this check in Codepeer mode to properly handle code
1655          --  prior to AI-0033 (pragmas don't matter to codepeer in any case).
1656
1657          if Inside_A_Generic then
1658             if Ekind (Scope (Current_Scope)) = E_Generic_Package
1659               and then In_Package_Body (Scope (Current_Scope))
1660               and then not CodePeer_Mode
1661             then
1662                Error_Pragma ("pragma% cannot be used inside a generic");
1663             end if;
1664          end if;
1665       end Check_Interrupt_Or_Attach_Handler;
1666
1667       -------------------------------------------
1668       -- Check_Is_In_Decl_Part_Or_Package_Spec --
1669       -------------------------------------------
1670
1671       procedure Check_Is_In_Decl_Part_Or_Package_Spec is
1672          P : Node_Id;
1673
1674       begin
1675          P := Parent (N);
1676          loop
1677             if No (P) then
1678                exit;
1679
1680             elsif Nkind (P) = N_Handled_Sequence_Of_Statements then
1681                exit;
1682
1683             elsif Nkind_In (P, N_Package_Specification,
1684                                N_Block_Statement)
1685             then
1686                return;
1687
1688             --  Note: the following tests seem a little peculiar, because
1689             --  they test for bodies, but if we were in the statement part
1690             --  of the body, we would already have hit the handled statement
1691             --  sequence, so the only way we get here is by being in the
1692             --  declarative part of the body.
1693
1694             elsif Nkind_In (P, N_Subprogram_Body,
1695                                N_Package_Body,
1696                                N_Task_Body,
1697                                N_Entry_Body)
1698             then
1699                return;
1700             end if;
1701
1702             P := Parent (P);
1703          end loop;
1704
1705          Error_Pragma ("pragma% is not in declarative part or package spec");
1706       end Check_Is_In_Decl_Part_Or_Package_Spec;
1707
1708       -------------------------
1709       -- Check_No_Identifier --
1710       -------------------------
1711
1712       procedure Check_No_Identifier (Arg : Node_Id) is
1713       begin
1714          if Nkind (Arg) = N_Pragma_Argument_Association
1715            and then Chars (Arg) /= No_Name
1716          then
1717             Error_Pragma_Arg_Ident
1718               ("pragma% does not permit identifier& here", Arg);
1719          end if;
1720       end Check_No_Identifier;
1721
1722       --------------------------
1723       -- Check_No_Identifiers --
1724       --------------------------
1725
1726       procedure Check_No_Identifiers is
1727          Arg_Node : Node_Id;
1728       begin
1729          if Arg_Count > 0 then
1730             Arg_Node := Arg1;
1731             while Present (Arg_Node) loop
1732                Check_No_Identifier (Arg_Node);
1733                Next (Arg_Node);
1734             end loop;
1735          end if;
1736       end Check_No_Identifiers;
1737
1738       ------------------------
1739       -- Check_No_Link_Name --
1740       ------------------------
1741
1742       procedure Check_No_Link_Name is
1743       begin
1744          if Present (Arg3)
1745            and then Chars (Arg3) = Name_Link_Name
1746          then
1747             Arg4 := Arg3;
1748          end if;
1749
1750          if Present (Arg4) then
1751             Error_Pragma_Arg
1752               ("Link_Name argument not allowed for Import Intrinsic", Arg4);
1753          end if;
1754       end Check_No_Link_Name;
1755
1756       -------------------------------
1757       -- Check_Optional_Identifier --
1758       -------------------------------
1759
1760       procedure Check_Optional_Identifier (Arg : Node_Id; Id : Name_Id) is
1761       begin
1762          if Present (Arg)
1763            and then Nkind (Arg) = N_Pragma_Argument_Association
1764            and then Chars (Arg) /= No_Name
1765          then
1766             if Chars (Arg) /= Id then
1767                Error_Msg_Name_1 := Pname;
1768                Error_Msg_Name_2 := Id;
1769                Error_Msg_N ("pragma% argument expects identifier%", Arg);
1770                raise Pragma_Exit;
1771             end if;
1772          end if;
1773       end Check_Optional_Identifier;
1774
1775       procedure Check_Optional_Identifier (Arg : Node_Id; Id : String) is
1776       begin
1777          Name_Buffer (1 .. Id'Length) := Id;
1778          Name_Len := Id'Length;
1779          Check_Optional_Identifier (Arg, Name_Find);
1780       end Check_Optional_Identifier;
1781
1782       --------------------------------------
1783       -- Check_Precondition_Postcondition --
1784       --------------------------------------
1785
1786       procedure Check_Precondition_Postcondition (In_Body : out Boolean) is
1787          P  : Node_Id;
1788          PO : Node_Id;
1789
1790          procedure Chain_PPC (PO : Node_Id);
1791          --  If PO is an entry or a [generic] subprogram declaration node, then
1792          --  the precondition/postcondition applies to this subprogram and the
1793          --  processing for the pragma is completed. Otherwise the pragma is
1794          --  misplaced.
1795
1796          ---------------
1797          -- Chain_PPC --
1798          ---------------
1799
1800          procedure Chain_PPC (PO : Node_Id) is
1801             S   : Entity_Id;
1802             P   : Node_Id;
1803
1804          begin
1805             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
1806                if not From_Aspect_Specification (N) then
1807                   Error_Pragma
1808                     ("pragma% cannot be applied to abstract subprogram");
1809
1810                elsif Class_Present (N) then
1811                   null;
1812
1813                else
1814                   Error_Pragma
1815                     ("aspect % requires ''Class for abstract subprogram");
1816                end if;
1817
1818             --  AI05-0230: The same restriction applies to null procedures. For
1819             --  compatibility with earlier uses of the Ada pragma, apply this
1820             --  rule only to aspect specifications.
1821
1822             --  The above discrpency needs documentation. Robert is dubious
1823             --  about whether it is a good idea ???
1824
1825             elsif Nkind (PO) = N_Subprogram_Declaration
1826               and then Nkind (Specification (PO)) = N_Procedure_Specification
1827               and then Null_Present (Specification (PO))
1828               and then From_Aspect_Specification (N)
1829               and then not Class_Present (N)
1830             then
1831                Error_Pragma
1832                  ("aspect % requires ''Class for null procedure");
1833
1834             elsif not Nkind_In (PO, N_Subprogram_Declaration,
1835                                     N_Expression_Function,
1836                                     N_Generic_Subprogram_Declaration,
1837                                     N_Entry_Declaration)
1838             then
1839                Pragma_Misplaced;
1840             end if;
1841
1842             --  Here if we have [generic] subprogram or entry declaration
1843
1844             if Nkind (PO) = N_Entry_Declaration then
1845                S := Defining_Entity (PO);
1846             else
1847                S := Defining_Unit_Name (Specification (PO));
1848             end if;
1849
1850             --  Make sure we do not have the case of a precondition pragma when
1851             --  the Pre'Class aspect is present.
1852
1853             --  We do this by looking at pragmas already chained to the entity
1854             --  since the aspect derived pragma will be put on this list first.
1855
1856             if Pragma_Name (N) = Name_Precondition then
1857                if not From_Aspect_Specification (N) then
1858                   P := Spec_PPC_List (Contract (S));
1859                   while Present (P) loop
1860                      if Pragma_Name (P) = Name_Precondition
1861                        and then From_Aspect_Specification (P)
1862                        and then Class_Present (P)
1863                      then
1864                         Error_Msg_Sloc := Sloc (P);
1865                         Error_Pragma
1866                           ("pragma% not allowed, `Pre''Class` aspect given#");
1867                      end if;
1868
1869                      P := Next_Pragma (P);
1870                   end loop;
1871                end if;
1872             end if;
1873
1874             --  Similarly check for Pre with inherited Pre'Class. Note that
1875             --  we cover the aspect case as well here.
1876
1877             if Pragma_Name (N) = Name_Precondition
1878               and then not Class_Present (N)
1879             then
1880                declare
1881                   Inherited : constant Subprogram_List :=
1882                                 Inherited_Subprograms (S);
1883                   P         : Node_Id;
1884
1885                begin
1886                   for J in Inherited'Range loop
1887                      P := Spec_PPC_List (Contract (Inherited (J)));
1888                      while Present (P) loop
1889                         if Pragma_Name (P) = Name_Precondition
1890                           and then Class_Present (P)
1891                         then
1892                            Error_Msg_Sloc := Sloc (P);
1893                            Error_Pragma
1894                              ("pragma% not allowed, `Pre''Class` "
1895                               & "aspect inherited from#");
1896                         end if;
1897
1898                         P := Next_Pragma (P);
1899                      end loop;
1900                   end loop;
1901                end;
1902             end if;
1903
1904             --  Note: we do not analyze the pragma at this point. Instead we
1905             --  delay this analysis until the end of the declarative part in
1906             --  which the pragma appears. This implements the required delay
1907             --  in this analysis, allowing forward references. The analysis
1908             --  happens at the end of Analyze_Declarations.
1909
1910             --  Chain spec PPC pragma to list for subprogram
1911
1912             Set_Next_Pragma (N, Spec_PPC_List (Contract (S)));
1913             Set_Spec_PPC_List (Contract (S), N);
1914
1915             --  Return indicating spec case
1916
1917             In_Body := False;
1918             return;
1919          end Chain_PPC;
1920
1921       --  Start of processing for Check_Precondition_Postcondition
1922
1923       begin
1924          if not Is_List_Member (N) then
1925             Pragma_Misplaced;
1926          end if;
1927
1928          --  Preanalyze message argument if present. Visibility in this
1929          --  argument is established at the point of pragma occurrence.
1930
1931          if Arg_Count = 2 then
1932             Check_Optional_Identifier (Arg2, Name_Message);
1933             Preanalyze_Spec_Expression
1934               (Get_Pragma_Arg (Arg2), Standard_String);
1935          end if;
1936
1937          --  Record if pragma is disabled
1938
1939          if Check_Enabled (Pname) then
1940             Set_SCO_Pragma_Enabled (Loc);
1941          end if;
1942
1943          --  If we are within an inlined body, the legality of the pragma
1944          --  has been checked already.
1945
1946          if In_Inlined_Body then
1947             In_Body := True;
1948             return;
1949          end if;
1950
1951          --  Search prior declarations
1952
1953          P := N;
1954          while Present (Prev (P)) loop
1955             P := Prev (P);
1956
1957             --  If the previous node is a generic subprogram, do not go to to
1958             --  the original node, which is the unanalyzed tree: we need to
1959             --  attach the pre/postconditions to the analyzed version at this
1960             --  point. They get propagated to the original tree when analyzing
1961             --  the corresponding body.
1962
1963             if Nkind (P) not in N_Generic_Declaration then
1964                PO := Original_Node (P);
1965             else
1966                PO := P;
1967             end if;
1968
1969             --  Skip past prior pragma
1970
1971             if Nkind (PO) = N_Pragma then
1972                null;
1973
1974             --  Skip stuff not coming from source
1975
1976             elsif not Comes_From_Source (PO) then
1977
1978                --  The condition may apply to a subprogram instantiation
1979
1980                if Nkind (PO) = N_Subprogram_Declaration
1981                  and then Present (Generic_Parent (Specification (PO)))
1982                then
1983                   Chain_PPC (PO);
1984                   return;
1985
1986                elsif Nkind (PO) = N_Subprogram_Declaration
1987                  and then In_Instance
1988                then
1989                   Chain_PPC (PO);
1990                   return;
1991
1992                --  For all other cases of non source code, do nothing
1993
1994                else
1995                   null;
1996                end if;
1997
1998             --  Only remaining possibility is subprogram declaration
1999
2000             else
2001                Chain_PPC (PO);
2002                return;
2003             end if;
2004          end loop;
2005
2006          --  If we fall through loop, pragma is at start of list, so see if it
2007          --  is at the start of declarations of a subprogram body.
2008
2009          if Nkind (Parent (N)) = N_Subprogram_Body
2010            and then List_Containing (N) = Declarations (Parent (N))
2011          then
2012             if Operating_Mode /= Generate_Code
2013               or else Inside_A_Generic
2014             then
2015                --  Analyze pragma expression for correctness and for ASIS use
2016
2017                Preanalyze_Spec_Expression
2018                  (Get_Pragma_Arg (Arg1), Standard_Boolean);
2019
2020                --  In ASIS mode, for a pragma generated from a source aspect,
2021                --  also analyze the original aspect expression.
2022
2023                if ASIS_Mode
2024                  and then Present (Corresponding_Aspect (N))
2025                then
2026                   Preanalyze_Spec_Expression
2027                     (Expression (Corresponding_Aspect (N)), Standard_Boolean);
2028                end if;
2029             end if;
2030
2031             In_Body := True;
2032             return;
2033
2034          --  See if it is in the pragmas after a library level subprogram
2035
2036          elsif Nkind (Parent (N)) = N_Compilation_Unit_Aux then
2037
2038             --  In formal verification mode, analyze pragma expression for
2039             --  correctness, as it is not expanded later.
2040
2041             if Alfa_Mode then
2042                Analyze_PPC_In_Decl_Part
2043                  (N, Defining_Entity (Unit (Parent (Parent (N)))));
2044             end if;
2045
2046             Chain_PPC (Unit (Parent (Parent (N))));
2047             return;
2048          end if;
2049
2050          --  If we fall through, pragma was misplaced
2051
2052          Pragma_Misplaced;
2053       end Check_Precondition_Postcondition;
2054
2055       -----------------------------
2056       -- Check_Static_Constraint --
2057       -----------------------------
2058
2059       --  Note: for convenience in writing this procedure, in addition to
2060       --  the officially (i.e. by spec) allowed argument which is always a
2061       --  constraint, it also allows ranges and discriminant associations.
2062       --  Above is not clear ???
2063
2064       procedure Check_Static_Constraint (Constr : Node_Id) is
2065
2066          procedure Require_Static (E : Node_Id);
2067          --  Require given expression to be static expression
2068
2069          --------------------
2070          -- Require_Static --
2071          --------------------
2072
2073          procedure Require_Static (E : Node_Id) is
2074          begin
2075             if not Is_OK_Static_Expression (E) then
2076                Flag_Non_Static_Expr
2077                  ("non-static constraint not allowed in Unchecked_Union!", E);
2078                raise Pragma_Exit;
2079             end if;
2080          end Require_Static;
2081
2082       --  Start of processing for Check_Static_Constraint
2083
2084       begin
2085          case Nkind (Constr) is
2086             when N_Discriminant_Association =>
2087                Require_Static (Expression (Constr));
2088
2089             when N_Range =>
2090                Require_Static (Low_Bound (Constr));
2091                Require_Static (High_Bound (Constr));
2092
2093             when N_Attribute_Reference =>
2094                Require_Static (Type_Low_Bound  (Etype (Prefix (Constr))));
2095                Require_Static (Type_High_Bound (Etype (Prefix (Constr))));
2096
2097             when N_Range_Constraint =>
2098                Check_Static_Constraint (Range_Expression (Constr));
2099
2100             when N_Index_Or_Discriminant_Constraint =>
2101                declare
2102                   IDC : Entity_Id;
2103                begin
2104                   IDC := First (Constraints (Constr));
2105                   while Present (IDC) loop
2106                      Check_Static_Constraint (IDC);
2107                      Next (IDC);
2108                   end loop;
2109                end;
2110
2111             when others =>
2112                null;
2113          end case;
2114       end Check_Static_Constraint;
2115
2116       ---------------------
2117       -- Check_Test_Case --
2118       ---------------------
2119
2120       procedure Check_Test_Case is
2121          P  : Node_Id;
2122          PO : Node_Id;
2123
2124          procedure Chain_TC (PO : Node_Id);
2125          --  If PO is a [generic] subprogram declaration node, then the
2126          --  test-case applies to this subprogram and the processing for the
2127          --  pragma is completed. Otherwise the pragma is misplaced.
2128
2129          --------------
2130          -- Chain_TC --
2131          --------------
2132
2133          procedure Chain_TC (PO : Node_Id) is
2134             S   : Entity_Id;
2135
2136          begin
2137             if Nkind (PO) = N_Abstract_Subprogram_Declaration then
2138                if From_Aspect_Specification (N) then
2139                   Error_Pragma
2140                     ("aspect% cannot be applied to abstract subprogram");
2141                else
2142                   Error_Pragma
2143                     ("pragma% cannot be applied to abstract subprogram");
2144                end if;
2145
2146             elsif Nkind (PO) = N_Entry_Declaration then
2147                if From_Aspect_Specification (N) then
2148                   Error_Pragma ("aspect% cannot be applied to entry");
2149                else
2150                   Error_Pragma ("pragma% cannot be applied to entry");
2151                end if;
2152
2153             elsif not Nkind_In (PO, N_Subprogram_Declaration,
2154                                     N_Generic_Subprogram_Declaration)
2155             then
2156                Pragma_Misplaced;
2157             end if;
2158
2159             --  Here if we have [generic] subprogram declaration
2160
2161             S := Defining_Unit_Name (Specification (PO));
2162
2163             --  Note: we do not analyze the pragma at this point. Instead we
2164             --  delay this analysis until the end of the declarative part in
2165             --  which the pragma appears. This implements the required delay
2166             --  in this analysis, allowing forward references. The analysis
2167             --  happens at the end of Analyze_Declarations.
2168
2169             --  There should not be another test case with the same name
2170             --  associated to this subprogram.
2171
2172             declare
2173                Name : constant String_Id := Get_Name_From_Test_Case_Pragma (N);
2174                TC   : Node_Id;
2175
2176             begin
2177                TC := Spec_TC_List (Contract (S));
2178                while Present (TC) loop
2179
2180                   if String_Equal
2181                     (Name, Get_Name_From_Test_Case_Pragma (TC))
2182                   then
2183                      Error_Msg_Sloc := Sloc (TC);
2184
2185                      if From_Aspect_Specification (N) then
2186                         Error_Pragma ("name for aspect% is already used#");
2187                      else
2188                         Error_Pragma ("name for pragma% is already used#");
2189                      end if;
2190                   end if;
2191
2192                   TC := Next_Pragma (TC);
2193                end loop;
2194             end;
2195
2196             --  Chain spec TC pragma to list for subprogram
2197
2198             Set_Next_Pragma (N, Spec_TC_List (Contract (S)));
2199             Set_Spec_TC_List (Contract (S), N);
2200          end Chain_TC;
2201
2202       --  Start of processing for Check_Test_Case
2203
2204       begin
2205          if not Is_List_Member (N) then
2206             Pragma_Misplaced;
2207          end if;
2208
2209          --  Test cases should only appear in package spec unit
2210
2211          if Get_Source_Unit (N) = No_Unit
2212            or else not Nkind_In (Sinfo.Unit (Cunit (Get_Source_Unit (N))),
2213                                  N_Package_Declaration,
2214                                  N_Generic_Package_Declaration)
2215          then
2216             Pragma_Misplaced;
2217          end if;
2218
2219          --  Search prior declarations
2220
2221          P := N;
2222          while Present (Prev (P)) loop
2223             P := Prev (P);
2224
2225             --  If the previous node is a generic subprogram, do not go to to
2226             --  the original node, which is the unanalyzed tree: we need to
2227             --  attach the test-case to the analyzed version at this point.
2228             --  They get propagated to the original tree when analyzing the
2229             --  corresponding body.
2230
2231             if Nkind (P) not in N_Generic_Declaration then
2232                PO := Original_Node (P);
2233             else
2234                PO := P;
2235             end if;
2236
2237             --  Skip past prior pragma
2238
2239             if Nkind (PO) = N_Pragma then
2240                null;
2241
2242             --  Skip stuff not coming from source
2243
2244             elsif not Comes_From_Source (PO) then
2245                null;
2246
2247             --  Only remaining possibility is subprogram declaration. First
2248             --  check that it is declared directly in a package declaration.
2249             --  This may be either the package declaration for the current unit
2250             --  being defined or a local package declaration.
2251
2252             elsif not Present (Parent (Parent (PO)))
2253               or else not Present (Parent (Parent (Parent (PO))))
2254               or else not Nkind_In (Parent (Parent (PO)),
2255                                     N_Package_Declaration,
2256                                     N_Generic_Package_Declaration)
2257             then
2258                Pragma_Misplaced;
2259
2260             else
2261                Chain_TC (PO);
2262                return;
2263             end if;
2264          end loop;
2265
2266          --  If we fall through, pragma was misplaced
2267
2268          Pragma_Misplaced;
2269       end Check_Test_Case;
2270
2271       --------------------------------------
2272       -- Check_Valid_Configuration_Pragma --
2273       --------------------------------------
2274
2275       --  A configuration pragma must appear in the context clause of a
2276       --  compilation unit, and only other pragmas may precede it. Note that
2277       --  the test also allows use in a configuration pragma file.
2278
2279       procedure Check_Valid_Configuration_Pragma is
2280       begin
2281          if not Is_Configuration_Pragma then
2282             Error_Pragma ("incorrect placement for configuration pragma%");
2283          end if;
2284       end Check_Valid_Configuration_Pragma;
2285
2286       -------------------------------------
2287       -- Check_Valid_Library_Unit_Pragma --
2288       -------------------------------------
2289
2290       procedure Check_Valid_Library_Unit_Pragma is
2291          Plist       : List_Id;
2292          Parent_Node : Node_Id;
2293          Unit_Name   : Entity_Id;
2294          Unit_Kind   : Node_Kind;
2295          Unit_Node   : Node_Id;
2296          Sindex      : Source_File_Index;
2297
2298       begin
2299          if not Is_List_Member (N) then
2300             Pragma_Misplaced;
2301
2302          else
2303             Plist := List_Containing (N);
2304             Parent_Node := Parent (Plist);
2305
2306             if Parent_Node = Empty then
2307                Pragma_Misplaced;
2308
2309             --  Case of pragma appearing after a compilation unit. In this case
2310             --  it must have an argument with the corresponding name and must
2311             --  be part of the following pragmas of its parent.
2312
2313             elsif Nkind (Parent_Node) = N_Compilation_Unit_Aux then
2314                if Plist /= Pragmas_After (Parent_Node) then
2315                   Pragma_Misplaced;
2316
2317                elsif Arg_Count = 0 then
2318                   Error_Pragma
2319                     ("argument required if outside compilation unit");
2320
2321                else
2322                   Check_No_Identifiers;
2323                   Check_Arg_Count (1);
2324                   Unit_Node := Unit (Parent (Parent_Node));
2325                   Unit_Kind := Nkind (Unit_Node);
2326
2327                   Analyze (Get_Pragma_Arg (Arg1));
2328
2329                   if Unit_Kind = N_Generic_Subprogram_Declaration
2330                     or else Unit_Kind = N_Subprogram_Declaration
2331                   then
2332                      Unit_Name := Defining_Entity (Unit_Node);
2333
2334                   elsif Unit_Kind in N_Generic_Instantiation then
2335                      Unit_Name := Defining_Entity (Unit_Node);
2336
2337                   else
2338                      Unit_Name := Cunit_Entity (Current_Sem_Unit);
2339                   end if;
2340
2341                   if Chars (Unit_Name) /=
2342                      Chars (Entity (Get_Pragma_Arg (Arg1)))
2343                   then
2344                      Error_Pragma_Arg
2345                        ("pragma% argument is not current unit name", Arg1);
2346                   end if;
2347
2348                   if Ekind (Unit_Name) = E_Package
2349                     and then Present (Renamed_Entity (Unit_Name))
2350                   then
2351                      Error_Pragma ("pragma% not allowed for renamed package");
2352                   end if;
2353                end if;
2354
2355             --  Pragma appears other than after a compilation unit
2356
2357             else
2358                --  Here we check for the generic instantiation case and also
2359                --  for the case of processing a generic formal package. We
2360                --  detect these cases by noting that the Sloc on the node
2361                --  does not belong to the current compilation unit.
2362
2363                Sindex := Source_Index (Current_Sem_Unit);
2364
2365                if Loc not in Source_First (Sindex) .. Source_Last (Sindex) then
2366                   Rewrite (N, Make_Null_Statement (Loc));
2367                   return;
2368
2369                --  If before first declaration, the pragma applies to the
2370                --  enclosing unit, and the name if present must be this name.
2371
2372                elsif Is_Before_First_Decl (N, Plist) then
2373                   Unit_Node := Unit_Declaration_Node (Current_Scope);
2374                   Unit_Kind := Nkind (Unit_Node);
2375
2376                   if Nkind (Parent (Unit_Node)) /= N_Compilation_Unit then
2377                      Pragma_Misplaced;
2378
2379                   elsif Unit_Kind = N_Subprogram_Body
2380                     and then not Acts_As_Spec (Unit_Node)
2381                   then
2382                      Pragma_Misplaced;
2383
2384                   elsif Nkind (Parent_Node) = N_Package_Body then
2385                      Pragma_Misplaced;
2386
2387                   elsif Nkind (Parent_Node) = N_Package_Specification
2388                     and then Plist = Private_Declarations (Parent_Node)
2389                   then
2390                      Pragma_Misplaced;
2391
2392                   elsif (Nkind (Parent_Node) = N_Generic_Package_Declaration
2393                            or else Nkind (Parent_Node) =
2394                                              N_Generic_Subprogram_Declaration)
2395                     and then Plist = Generic_Formal_Declarations (Parent_Node)
2396                   then
2397                      Pragma_Misplaced;
2398
2399                   elsif Arg_Count > 0 then
2400                      Analyze (Get_Pragma_Arg (Arg1));
2401
2402                      if Entity (Get_Pragma_Arg (Arg1)) /= Current_Scope then
2403                         Error_Pragma_Arg
2404                           ("name in pragma% must be enclosing unit", Arg1);
2405                      end if;
2406
2407                   --  It is legal to have no argument in this context
2408
2409                   else
2410                      return;
2411                   end if;
2412
2413                --  Error if not before first declaration. This is because a
2414                --  library unit pragma argument must be the name of a library
2415                --  unit (RM 10.1.5(7)), but the only names permitted in this
2416                --  context are (RM 10.1.5(6)) names of subprogram declarations,
2417                --  generic subprogram declarations or generic instantiations.
2418
2419                else
2420                   Error_Pragma
2421                     ("pragma% misplaced, must be before first declaration");
2422                end if;
2423             end if;
2424          end if;
2425       end Check_Valid_Library_Unit_Pragma;
2426
2427       -------------------
2428       -- Check_Variant --
2429       -------------------
2430
2431       procedure Check_Variant (Variant : Node_Id; UU_Typ : Entity_Id) is
2432          Clist : constant Node_Id := Component_List (Variant);
2433          Comp  : Node_Id;
2434
2435       begin
2436          if not Is_Non_Empty_List (Component_Items (Clist)) then
2437             Error_Msg_N
2438               ("Unchecked_Union may not have empty component list",
2439                Variant);
2440             return;
2441          end if;
2442
2443          Comp := First (Component_Items (Clist));
2444          while Present (Comp) loop
2445             Check_Component (Comp, UU_Typ, In_Variant_Part => True);
2446             Next (Comp);
2447          end loop;
2448       end Check_Variant;
2449
2450       ------------------
2451       -- Error_Pragma --
2452       ------------------
2453
2454       procedure Error_Pragma (Msg : String) is
2455          MsgF : String := Msg;
2456       begin
2457          Error_Msg_Name_1 := Pname;
2458          Fix_Error (MsgF);
2459          Error_Msg_N (MsgF, N);
2460          raise Pragma_Exit;
2461       end Error_Pragma;
2462
2463       ----------------------
2464       -- Error_Pragma_Arg --
2465       ----------------------
2466
2467       procedure Error_Pragma_Arg (Msg : String; Arg : Node_Id) is
2468          MsgF : String := Msg;
2469       begin
2470          Error_Msg_Name_1 := Pname;
2471          Fix_Error (MsgF);
2472          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2473          raise Pragma_Exit;
2474       end Error_Pragma_Arg;
2475
2476       procedure Error_Pragma_Arg (Msg1, Msg2 : String; Arg : Node_Id) is
2477          MsgF : String := Msg1;
2478       begin
2479          Error_Msg_Name_1 := Pname;
2480          Fix_Error (MsgF);
2481          Error_Msg_N (MsgF, Get_Pragma_Arg (Arg));
2482          Error_Pragma_Arg (Msg2, Arg);
2483       end Error_Pragma_Arg;
2484
2485       ----------------------------
2486       -- Error_Pragma_Arg_Ident --
2487       ----------------------------
2488
2489       procedure Error_Pragma_Arg_Ident (Msg : String; Arg : Node_Id) is
2490          MsgF : String := Msg;
2491       begin
2492          Error_Msg_Name_1 := Pname;
2493          Fix_Error (MsgF);
2494          Error_Msg_N (MsgF, Arg);
2495          raise Pragma_Exit;
2496       end Error_Pragma_Arg_Ident;
2497
2498       ----------------------
2499       -- Error_Pragma_Ref --
2500       ----------------------
2501
2502       procedure Error_Pragma_Ref (Msg : String; Ref : Entity_Id) is
2503          MsgF : String := Msg;
2504       begin
2505          Error_Msg_Name_1 := Pname;
2506          Fix_Error (MsgF);
2507          Error_Msg_Sloc   := Sloc (Ref);
2508          Error_Msg_NE (MsgF, N, Ref);
2509          raise Pragma_Exit;
2510       end Error_Pragma_Ref;
2511
2512       ------------------------
2513       -- Find_Lib_Unit_Name --
2514       ------------------------
2515
2516       function Find_Lib_Unit_Name return Entity_Id is
2517       begin
2518          --  Return inner compilation unit entity, for case of nested
2519          --  categorization pragmas. This happens in generic unit.
2520
2521          if Nkind (Parent (N)) = N_Package_Specification
2522            and then Defining_Entity (Parent (N)) /= Current_Scope
2523          then
2524             return Defining_Entity (Parent (N));
2525          else
2526             return Current_Scope;
2527          end if;
2528       end Find_Lib_Unit_Name;
2529
2530       ----------------------------
2531       -- Find_Program_Unit_Name --
2532       ----------------------------
2533
2534       procedure Find_Program_Unit_Name (Id : Node_Id) is
2535          Unit_Name : Entity_Id;
2536          Unit_Kind : Node_Kind;
2537          P         : constant Node_Id := Parent (N);
2538
2539       begin
2540          if Nkind (P) = N_Compilation_Unit then
2541             Unit_Kind := Nkind (Unit (P));
2542
2543             if Unit_Kind = N_Subprogram_Declaration
2544               or else Unit_Kind = N_Package_Declaration
2545               or else Unit_Kind in N_Generic_Declaration
2546             then
2547                Unit_Name := Defining_Entity (Unit (P));
2548
2549                if Chars (Id) = Chars (Unit_Name) then
2550                   Set_Entity (Id, Unit_Name);
2551                   Set_Etype (Id, Etype (Unit_Name));
2552                else
2553                   Set_Etype (Id, Any_Type);
2554                   Error_Pragma
2555                     ("cannot find program unit referenced by pragma%");
2556                end if;
2557
2558             else
2559                Set_Etype (Id, Any_Type);
2560                Error_Pragma ("pragma% inapplicable to this unit");
2561             end if;
2562
2563          else
2564             Analyze (Id);
2565          end if;
2566       end Find_Program_Unit_Name;
2567
2568       -----------------------------------------
2569       -- Find_Unique_Parameterless_Procedure --
2570       -----------------------------------------
2571
2572       function Find_Unique_Parameterless_Procedure
2573         (Name : Entity_Id;
2574          Arg  : Node_Id) return Entity_Id
2575       is
2576          Proc : Entity_Id := Empty;
2577
2578       begin
2579          --  The body of this procedure needs some comments ???
2580
2581          if not Is_Entity_Name (Name) then
2582             Error_Pragma_Arg
2583               ("argument of pragma% must be entity name", Arg);
2584
2585          elsif not Is_Overloaded (Name) then
2586             Proc := Entity (Name);
2587
2588             if Ekind (Proc) /= E_Procedure
2589               or else Present (First_Formal (Proc))
2590             then
2591                Error_Pragma_Arg
2592                  ("argument of pragma% must be parameterless procedure", Arg);
2593             end if;
2594
2595          else
2596             declare
2597                Found : Boolean := False;
2598                It    : Interp;
2599                Index : Interp_Index;
2600
2601             begin
2602                Get_First_Interp (Name, Index, It);
2603                while Present (It.Nam) loop
2604                   Proc := It.Nam;
2605
2606                   if Ekind (Proc) = E_Procedure
2607                     and then No (First_Formal (Proc))
2608                   then
2609                      if not Found then
2610                         Found := True;
2611                         Set_Entity (Name, Proc);
2612                         Set_Is_Overloaded (Name, False);
2613                      else
2614                         Error_Pragma_Arg
2615                           ("ambiguous handler name for pragma% ", Arg);
2616                      end if;
2617                   end if;
2618
2619                   Get_Next_Interp (Index, It);
2620                end loop;
2621
2622                if not Found then
2623                   Error_Pragma_Arg
2624                     ("argument of pragma% must be parameterless procedure",
2625                      Arg);
2626                else
2627                   Proc := Entity (Name);
2628                end if;
2629             end;
2630          end if;
2631
2632          return Proc;
2633       end Find_Unique_Parameterless_Procedure;
2634
2635       ---------------
2636       -- Fix_Error --
2637       ---------------
2638
2639       procedure Fix_Error (Msg : in out String) is
2640       begin
2641          if From_Aspect_Specification (N) then
2642             for J in Msg'First .. Msg'Last - 5 loop
2643                if Msg (J .. J + 5) = "pragma" then
2644                   Msg (J .. J + 5) := "aspect";
2645                end if;
2646             end loop;
2647
2648             if Error_Msg_Name_1 = Name_Precondition then
2649                Error_Msg_Name_1 := Name_Pre;
2650             elsif Error_Msg_Name_1 = Name_Postcondition then
2651                Error_Msg_Name_1 := Name_Post;
2652             end if;
2653          end if;
2654       end Fix_Error;
2655
2656       -------------------------
2657       -- Gather_Associations --
2658       -------------------------
2659
2660       procedure Gather_Associations
2661         (Names : Name_List;
2662          Args  : out Args_List)
2663       is
2664          Arg : Node_Id;
2665
2666       begin
2667          --  Initialize all parameters to Empty
2668
2669          for J in Args'Range loop
2670             Args (J) := Empty;
2671          end loop;
2672
2673          --  That's all we have to do if there are no argument associations
2674
2675          if No (Pragma_Argument_Associations (N)) then
2676             return;
2677          end if;
2678
2679          --  Otherwise first deal with any positional parameters present
2680
2681          Arg := First (Pragma_Argument_Associations (N));
2682          for Index in Args'Range loop
2683             exit when No (Arg) or else Chars (Arg) /= No_Name;
2684             Args (Index) := Get_Pragma_Arg (Arg);
2685             Next (Arg);
2686          end loop;
2687
2688          --  Positional parameters all processed, if any left, then we
2689          --  have too many positional parameters.
2690
2691          if Present (Arg) and then Chars (Arg) = No_Name then
2692             Error_Pragma_Arg
2693               ("too many positional associations for pragma%", Arg);
2694          end if;
2695
2696          --  Process named parameters if any are present
2697
2698          while Present (Arg) loop
2699             if Chars (Arg) = No_Name then
2700                Error_Pragma_Arg
2701                  ("positional association cannot follow named association",
2702                   Arg);
2703
2704             else
2705                for Index in Names'Range loop
2706                   if Names (Index) = Chars (Arg) then
2707                      if Present (Args (Index)) then
2708                         Error_Pragma_Arg
2709                           ("duplicate argument association for pragma%", Arg);
2710                      else
2711                         Args (Index) := Get_Pragma_Arg (Arg);
2712                         exit;
2713                      end if;
2714                   end if;
2715
2716                   if Index = Names'Last then
2717                      Error_Msg_Name_1 := Pname;
2718                      Error_Msg_N ("pragma% does not allow & argument", Arg);
2719
2720                      --  Check for possible misspelling
2721
2722                      for Index1 in Names'Range loop
2723                         if Is_Bad_Spelling_Of
2724                              (Chars (Arg), Names (Index1))
2725                         then
2726                            Error_Msg_Name_1 := Names (Index1);
2727                            Error_Msg_N -- CODEFIX
2728                              ("\possible misspelling of%", Arg);
2729                            exit;
2730                         end if;
2731                      end loop;
2732
2733                      raise Pragma_Exit;
2734                   end if;
2735                end loop;
2736             end if;
2737
2738             Next (Arg);
2739          end loop;
2740       end Gather_Associations;
2741
2742       -----------------
2743       -- GNAT_Pragma --
2744       -----------------
2745
2746       procedure GNAT_Pragma is
2747       begin
2748          --  We need to check the No_Implementation_Pragmas restriction for
2749          --  the case of a pragma from source. Note that the case of aspects
2750          --  generating corresponding pragmas marks these pragmas as not being
2751          --  from source, so this test also catches that case.
2752
2753          if Comes_From_Source (N) then
2754             Check_Restriction (No_Implementation_Pragmas, N);
2755          end if;
2756       end GNAT_Pragma;
2757
2758       --------------------------
2759       -- Is_Before_First_Decl --
2760       --------------------------
2761
2762       function Is_Before_First_Decl
2763         (Pragma_Node : Node_Id;
2764          Decls       : List_Id) return Boolean
2765       is
2766          Item : Node_Id := First (Decls);
2767
2768       begin
2769          --  Only other pragmas can come before this pragma
2770
2771          loop
2772             if No (Item) or else Nkind (Item) /= N_Pragma then
2773                return False;
2774
2775             elsif Item = Pragma_Node then
2776                return True;
2777             end if;
2778
2779             Next (Item);
2780          end loop;
2781       end Is_Before_First_Decl;
2782
2783       -----------------------------
2784       -- Is_Configuration_Pragma --
2785       -----------------------------
2786
2787       --  A configuration pragma must appear in the context clause of a
2788       --  compilation unit, and only other pragmas may precede it. Note that
2789       --  the test below also permits use in a configuration pragma file.
2790
2791       function Is_Configuration_Pragma return Boolean is
2792          Lis : constant List_Id := List_Containing (N);
2793          Par : constant Node_Id := Parent (N);
2794          Prg : Node_Id;
2795
2796       begin
2797          --  If no parent, then we are in the configuration pragma file,
2798          --  so the placement is definitely appropriate.
2799
2800          if No (Par) then
2801             return True;
2802
2803          --  Otherwise we must be in the context clause of a compilation unit
2804          --  and the only thing allowed before us in the context list is more
2805          --  configuration pragmas.
2806
2807          elsif Nkind (Par) = N_Compilation_Unit
2808            and then Context_Items (Par) = Lis
2809          then
2810             Prg := First (Lis);
2811
2812             loop
2813                if Prg = N then
2814                   return True;
2815                elsif Nkind (Prg) /= N_Pragma then
2816                   return False;
2817                end if;
2818
2819                Next (Prg);
2820             end loop;
2821
2822          else
2823             return False;
2824          end if;
2825       end Is_Configuration_Pragma;
2826
2827       --------------------------
2828       -- Is_In_Context_Clause --
2829       --------------------------
2830
2831       function Is_In_Context_Clause return Boolean is
2832          Plist       : List_Id;
2833          Parent_Node : Node_Id;
2834
2835       begin
2836          if not Is_List_Member (N) then
2837             return False;
2838
2839          else
2840             Plist := List_Containing (N);
2841             Parent_Node := Parent (Plist);
2842
2843             if Parent_Node = Empty
2844               or else Nkind (Parent_Node) /= N_Compilation_Unit
2845               or else Context_Items (Parent_Node) /= Plist
2846             then
2847                return False;
2848             end if;
2849          end if;
2850
2851          return True;
2852       end Is_In_Context_Clause;
2853
2854       ---------------------------------
2855       -- Is_Static_String_Expression --
2856       ---------------------------------
2857
2858       function Is_Static_String_Expression (Arg : Node_Id) return Boolean is
2859          Argx : constant Node_Id := Get_Pragma_Arg (Arg);
2860
2861       begin
2862          Analyze_And_Resolve (Argx);
2863          return Is_OK_Static_Expression (Argx)
2864            and then Nkind (Argx) = N_String_Literal;
2865       end Is_Static_String_Expression;
2866
2867       ----------------------
2868       -- Pragma_Misplaced --
2869       ----------------------
2870
2871       procedure Pragma_Misplaced is
2872       begin
2873          Error_Pragma ("incorrect placement of pragma%");
2874       end Pragma_Misplaced;
2875
2876       ------------------------------------
2877       -- Process Atomic_Shared_Volatile --
2878       ------------------------------------
2879
2880       procedure Process_Atomic_Shared_Volatile is
2881          E_Id : Node_Id;
2882          E    : Entity_Id;
2883          D    : Node_Id;
2884          K    : Node_Kind;
2885          Utyp : Entity_Id;
2886
2887          procedure Set_Atomic (E : Entity_Id);
2888          --  Set given type as atomic, and if no explicit alignment was given,
2889          --  set alignment to unknown, since back end knows what the alignment
2890          --  requirements are for atomic arrays. Note: this step is necessary
2891          --  for derived types.
2892
2893          ----------------
2894          -- Set_Atomic --
2895          ----------------
2896
2897          procedure Set_Atomic (E : Entity_Id) is
2898          begin
2899             Set_Is_Atomic (E);
2900
2901             if not Has_Alignment_Clause (E) then
2902                Set_Alignment (E, Uint_0);
2903             end if;
2904          end Set_Atomic;
2905
2906       --  Start of processing for Process_Atomic_Shared_Volatile
2907
2908       begin
2909          Check_Ada_83_Warning;
2910          Check_No_Identifiers;
2911          Check_Arg_Count (1);
2912          Check_Arg_Is_Local_Name (Arg1);
2913          E_Id := Get_Pragma_Arg (Arg1);
2914
2915          if Etype (E_Id) = Any_Type then
2916             return;
2917          end if;
2918
2919          E := Entity (E_Id);
2920          D := Declaration_Node (E);
2921          K := Nkind (D);
2922
2923          --  Check duplicate before we chain ourselves!
2924
2925          Check_Duplicate_Pragma (E);
2926
2927          --  Now check appropriateness of the entity
2928
2929          if Is_Type (E) then
2930             if Rep_Item_Too_Early (E, N)
2931                  or else
2932                Rep_Item_Too_Late (E, N)
2933             then
2934                return;
2935             else
2936                Check_First_Subtype (Arg1);
2937             end if;
2938
2939             if Prag_Id /= Pragma_Volatile then
2940                Set_Atomic (E);
2941                Set_Atomic (Underlying_Type (E));
2942                Set_Atomic (Base_Type (E));
2943             end if;
2944
2945             --  Attribute belongs on the base type. If the view of the type is
2946             --  currently private, it also belongs on the underlying type.
2947
2948             Set_Is_Volatile (Base_Type (E));
2949             Set_Is_Volatile (Underlying_Type (E));
2950
2951             Set_Treat_As_Volatile (E);
2952             Set_Treat_As_Volatile (Underlying_Type (E));
2953
2954          elsif K = N_Object_Declaration
2955            or else (K = N_Component_Declaration
2956                      and then Original_Record_Component (E) = E)
2957          then
2958             if Rep_Item_Too_Late (E, N) then
2959                return;
2960             end if;
2961
2962             if Prag_Id /= Pragma_Volatile then
2963                Set_Is_Atomic (E);
2964
2965                --  If the object declaration has an explicit initialization, a
2966                --  temporary may have to be created to hold the expression, to
2967                --  ensure that access to the object remain atomic.
2968
2969                if Nkind (Parent (E)) = N_Object_Declaration
2970                  and then Present (Expression (Parent (E)))
2971                then
2972                   Set_Has_Delayed_Freeze (E);
2973                end if;
2974
2975                --  An interesting improvement here. If an object of composite
2976                --  type X is declared atomic, and the type X isn't, that's a
2977                --  pity, since it may not have appropriate alignment etc. We
2978                --  can rescue this in the special case where the object and
2979                --  type are in the same unit by just setting the type as
2980                --  atomic, so that the back end will process it as atomic.
2981
2982                --  Note: we used to do this for elementary types as well,
2983                --  but that turns out to be a bad idea and can have unwanted
2984                --  effects, most notably if the type is elementary, the object
2985                --  a simple component within a record, and both are in a spec:
2986                --  every object of this type in the entire program will be
2987                --  treated as atomic, thus incurring a potentially costly
2988                --  synchronization operation for every access.
2989
2990                --  Of course it would be best if the back end could just adjust
2991                --  the alignment etc for the specific object, but that's not
2992                --  something we are capable of doing at this point.
2993
2994                Utyp := Underlying_Type (Etype (E));
2995
2996                if Present (Utyp)
2997                  and then Is_Composite_Type (Utyp)
2998                  and then Sloc (E) > No_Location
2999                  and then Sloc (Utyp) > No_Location
3000                  and then
3001                    Get_Source_File_Index (Sloc (E)) =
3002                    Get_Source_File_Index (Sloc (Underlying_Type (Etype (E))))
3003                then
3004                   Set_Is_Atomic (Underlying_Type (Etype (E)));
3005                end if;
3006             end if;
3007
3008             Set_Is_Volatile (E);
3009             Set_Treat_As_Volatile (E);
3010
3011          else
3012             Error_Pragma_Arg
3013               ("inappropriate entity for pragma%", Arg1);
3014          end if;
3015       end Process_Atomic_Shared_Volatile;
3016
3017       -------------------------------------------
3018       -- Process_Compile_Time_Warning_Or_Error --
3019       -------------------------------------------
3020
3021       procedure Process_Compile_Time_Warning_Or_Error is
3022          Arg1x : constant Node_Id := Get_Pragma_Arg (Arg1);
3023
3024       begin
3025          Check_Arg_Count (2);
3026          Check_No_Identifiers;
3027          Check_Arg_Is_Static_Expression (Arg2, Standard_String);
3028          Analyze_And_Resolve (Arg1x, Standard_Boolean);
3029
3030          if Compile_Time_Known_Value (Arg1x) then
3031             if Is_True (Expr_Value (Get_Pragma_Arg (Arg1))) then
3032                declare
3033                   Str   : constant String_Id :=
3034                             Strval (Get_Pragma_Arg (Arg2));
3035                   Len   : constant Int := String_Length (Str);
3036                   Cont  : Boolean;
3037                   Ptr   : Nat;
3038                   CC    : Char_Code;
3039                   C     : Character;
3040                   Cent  : constant Entity_Id :=
3041                             Cunit_Entity (Current_Sem_Unit);
3042
3043                   Force : constant Boolean :=
3044                             Prag_Id = Pragma_Compile_Time_Warning
3045                               and then
3046                                 Is_Spec_Name (Unit_Name (Current_Sem_Unit))
3047                               and then (Ekind (Cent) /= E_Package
3048                                           or else not In_Private_Part (Cent));
3049                   --  Set True if this is the warning case, and we are in the
3050                   --  visible part of a package spec, or in a subprogram spec,
3051                   --  in which case we want to force the client to see the
3052                   --  warning, even though it is not in the main unit.
3053
3054                begin
3055                   --  Loop through segments of message separated by line feeds.
3056                   --  We output these segments as separate messages with
3057                   --  continuation marks for all but the first.
3058
3059                   Cont := False;
3060                   Ptr := 1;
3061                   loop
3062                      Error_Msg_Strlen := 0;
3063
3064                      --  Loop to copy characters from argument to error message
3065                      --  string buffer.
3066
3067                      loop
3068                         exit when Ptr > Len;
3069                         CC := Get_String_Char (Str, Ptr);
3070                         Ptr := Ptr + 1;
3071
3072                         --  Ignore wide chars ??? else store character
3073
3074                         if In_Character_Range (CC) then
3075                            C := Get_Character (CC);
3076                            exit when C = ASCII.LF;
3077                            Error_Msg_Strlen := Error_Msg_Strlen + 1;
3078                            Error_Msg_String (Error_Msg_Strlen) := C;
3079                         end if;
3080                      end loop;
3081
3082                      --  Here with one line ready to go
3083
3084                      Error_Msg_Warn := Prag_Id = Pragma_Compile_Time_Warning;
3085
3086                      --  If this is a warning in a spec, then we want clients
3087                      --  to see the warning, so mark the message with the
3088                      --  special sequence !! to force the warning. In the case
3089                      --  of a package spec, we do not force this if we are in
3090                      --  the private part of the spec.
3091
3092                      if Force then
3093                         if Cont = False then
3094                            Error_Msg_N ("<~!!", Arg1);
3095                            Cont := True;
3096                         else
3097                            Error_Msg_N ("\<~!!", Arg1);
3098                         end if;
3099
3100                      --  Error, rather than warning, or in a body, so we do not
3101                      --  need to force visibility for client (error will be
3102                      --  output in any case, and this is the situation in which
3103                      --  we do not want a client to get a warning, since the
3104                      --  warning is in the body or the spec private part).
3105
3106                      else
3107                         if Cont = False then
3108                            Error_Msg_N ("<~", Arg1);
3109                            Cont := True;
3110                         else
3111                            Error_Msg_N ("\<~", Arg1);
3112                         end if;
3113                      end if;
3114
3115                      exit when Ptr > Len;
3116                   end loop;
3117                end;
3118             end if;
3119          end if;
3120       end Process_Compile_Time_Warning_Or_Error;
3121
3122       ------------------------
3123       -- Process_Convention --
3124       ------------------------
3125
3126       procedure Process_Convention
3127         (C   : out Convention_Id;
3128          Ent : out Entity_Id)
3129       is
3130          Id        : Node_Id;
3131          E         : Entity_Id;
3132          E1        : Entity_Id;
3133          Cname     : Name_Id;
3134          Comp_Unit : Unit_Number_Type;
3135
3136          procedure Diagnose_Multiple_Pragmas (S : Entity_Id);
3137          --  Called if we have more than one Export/Import/Convention pragma.
3138          --  This is generally illegal, but we have a special case of allowing
3139          --  Import and Interface to coexist if they specify the convention in
3140          --  a consistent manner. We are allowed to do this, since Interface is
3141          --  an implementation defined pragma, and we choose to do it since we
3142          --  know Rational allows this combination. S is the entity id of the
3143          --  subprogram in question. This procedure also sets the special flag
3144          --  Import_Interface_Present in both pragmas in the case where we do
3145          --  have matching Import and Interface pragmas.
3146
3147          procedure Set_Convention_From_Pragma (E : Entity_Id);
3148          --  Set convention in entity E, and also flag that the entity has a
3149          --  convention pragma. If entity is for a private or incomplete type,
3150          --  also set convention and flag on underlying type. This procedure
3151          --  also deals with the special case of C_Pass_By_Copy convention.
3152
3153          -------------------------------
3154          -- Diagnose_Multiple_Pragmas --
3155          -------------------------------
3156
3157          procedure Diagnose_Multiple_Pragmas (S : Entity_Id) is
3158             Pdec : constant Node_Id := Declaration_Node (S);
3159             Decl : Node_Id;
3160             Err  : Boolean;
3161
3162             function Same_Convention (Decl : Node_Id) return Boolean;
3163             --  Decl is a pragma node. This function returns True if this
3164             --  pragma has a first argument that is an identifier with a
3165             --  Chars field corresponding to the Convention_Id C.
3166
3167             function Same_Name (Decl : Node_Id) return Boolean;
3168             --  Decl is a pragma node. This function returns True if this
3169             --  pragma has a second argument that is an identifier with a
3170             --  Chars field that matches the Chars of the current subprogram.
3171
3172             ---------------------
3173             -- Same_Convention --
3174             ---------------------
3175
3176             function Same_Convention (Decl : Node_Id) return Boolean is
3177                Arg1 : constant Node_Id :=
3178                         First (Pragma_Argument_Associations (Decl));
3179
3180             begin
3181                if Present (Arg1) then
3182                   declare
3183                      Arg : constant Node_Id := Get_Pragma_Arg (Arg1);
3184                   begin
3185                      if Nkind (Arg) = N_Identifier
3186                        and then Is_Convention_Name (Chars (Arg))
3187                        and then Get_Convention_Id (Chars (Arg)) = C
3188                      then
3189                         return True;
3190                      end if;
3191                   end;
3192                end if;
3193
3194                return False;
3195             end Same_Convention;
3196
3197             ---------------
3198             -- Same_Name --
3199             ---------------
3200
3201             function Same_Name (Decl : Node_Id) return Boolean is
3202                Arg1 : constant Node_Id :=
3203                         First (Pragma_Argument_Associations (Decl));
3204                Arg2 : Node_Id;
3205
3206             begin
3207                if No (Arg1) then
3208                   return False;
3209                end if;
3210
3211                Arg2 := Next (Arg1);
3212
3213                if No (Arg2) then
3214                   return False;
3215                end if;
3216
3217                declare
3218                   Arg : constant Node_Id := Get_Pragma_Arg (Arg2);
3219                begin
3220                   if Nkind (Arg) = N_Identifier
3221                     and then Chars (Arg) = Chars (S)
3222                   then
3223                      return True;
3224                   end if;
3225                end;
3226
3227                return False;
3228             end Same_Name;
3229
3230          --  Start of processing for Diagnose_Multiple_Pragmas
3231
3232          begin
3233             Err := True;
3234
3235             --  Definitely give message if we have Convention/Export here
3236
3237             if Prag_Id = Pragma_Convention or else Prag_Id = Pragma_Export then
3238                null;
3239
3240                --  If we have an Import or Export, scan back from pragma to
3241                --  find any previous pragma applying to the same procedure.
3242                --  The scan will be terminated by the start of the list, or
3243                --  hitting the subprogram declaration. This won't allow one
3244                --  pragma to appear in the public part and one in the private
3245                --  part, but that seems very unlikely in practice.
3246
3247             else
3248                Decl := Prev (N);
3249                while Present (Decl) and then Decl /= Pdec loop
3250
3251                   --  Look for pragma with same name as us
3252
3253                   if Nkind (Decl) = N_Pragma
3254                     and then Same_Name (Decl)
3255                   then
3256                      --  Give error if same as our pragma or Export/Convention
3257
3258                      if Pragma_Name (Decl) = Name_Export
3259                           or else
3260                         Pragma_Name (Decl) = Name_Convention
3261                           or else
3262                         Pragma_Name (Decl) = Pragma_Name (N)
3263                      then
3264                         exit;
3265
3266                      --  Case of Import/Interface or the other way round
3267
3268                      elsif Pragma_Name (Decl) = Name_Interface
3269                              or else
3270                            Pragma_Name (Decl) = Name_Import
3271                      then
3272                         --  Here we know that we have Import and Interface. It
3273                         --  doesn't matter which way round they are. See if
3274                         --  they specify the same convention. If so, all OK,
3275                         --  and set special flags to stop other messages
3276
3277                         if Same_Convention (Decl) then
3278                            Set_Import_Interface_Present (N);
3279                            Set_Import_Interface_Present (Decl);
3280                            Err := False;
3281
3282                         --  If different conventions, special message
3283
3284                         else
3285                            Error_Msg_Sloc := Sloc (Decl);
3286                            Error_Pragma_Arg
3287                              ("convention differs from that given#", Arg1);
3288                            return;
3289                         end if;
3290                      end if;
3291                   end if;
3292
3293                   Next (Decl);
3294                end loop;
3295             end if;
3296
3297             --  Give message if needed if we fall through those tests
3298
3299             if Err then
3300                Error_Pragma_Arg
3301                  ("at most one Convention/Export/Import pragma is allowed",
3302                   Arg2);
3303             end if;
3304          end Diagnose_Multiple_Pragmas;
3305
3306          --------------------------------
3307          -- Set_Convention_From_Pragma --
3308          --------------------------------
3309
3310          procedure Set_Convention_From_Pragma (E : Entity_Id) is
3311          begin
3312             --  Ada 2005 (AI-430): Check invalid attempt to change convention
3313             --  for an overridden dispatching operation. Technically this is
3314             --  an amendment and should only be done in Ada 2005 mode. However,
3315             --  this is clearly a mistake, since the problem that is addressed
3316             --  by this AI is that there is a clear gap in the RM!
3317
3318             if Is_Dispatching_Operation (E)
3319               and then Present (Overridden_Operation (E))
3320               and then C /= Convention (Overridden_Operation (E))
3321             then
3322                Error_Pragma_Arg
3323                  ("cannot change convention for " &
3324                   "overridden dispatching operation",
3325                   Arg1);
3326             end if;
3327
3328             --  Set the convention
3329
3330             Set_Convention (E, C);
3331             Set_Has_Convention_Pragma (E);
3332
3333             if Is_Incomplete_Or_Private_Type (E)
3334               and then Present (Underlying_Type (E))
3335             then
3336                Set_Convention            (Underlying_Type (E), C);
3337                Set_Has_Convention_Pragma (Underlying_Type (E), True);
3338             end if;
3339
3340             --  A class-wide type should inherit the convention of the specific
3341             --  root type (although this isn't specified clearly by the RM).
3342
3343             if Is_Type (E) and then Present (Class_Wide_Type (E)) then
3344                Set_Convention (Class_Wide_Type (E), C);
3345             end if;
3346
3347             --  If the entity is a record type, then check for special case of
3348             --  C_Pass_By_Copy, which is treated the same as C except that the
3349             --  special record flag is set. This convention is only permitted
3350             --  on record types (see AI95-00131).
3351
3352             if Cname = Name_C_Pass_By_Copy then
3353                if Is_Record_Type (E) then
3354                   Set_C_Pass_By_Copy (Base_Type (E));
3355                elsif Is_Incomplete_Or_Private_Type (E)
3356                  and then Is_Record_Type (Underlying_Type (E))
3357                then
3358                   Set_C_Pass_By_Copy (Base_Type (Underlying_Type (E)));
3359                else
3360                   Error_Pragma_Arg
3361                     ("C_Pass_By_Copy convention allowed only for record type",
3362                      Arg2);
3363                end if;
3364             end if;
3365
3366             --  If the entity is a derived boolean type, check for the special
3367             --  case of convention C, C++, or Fortran, where we consider any
3368             --  nonzero value to represent true.
3369
3370             if Is_Discrete_Type (E)
3371               and then Root_Type (Etype (E)) = Standard_Boolean
3372               and then
3373                 (C = Convention_C
3374                    or else
3375                  C = Convention_CPP
3376                    or else
3377                  C = Convention_Fortran)
3378             then
3379                Set_Nonzero_Is_True (Base_Type (E));
3380             end if;
3381          end Set_Convention_From_Pragma;
3382
3383       --  Start of processing for Process_Convention
3384
3385       begin
3386          Check_At_Least_N_Arguments (2);
3387          Check_Optional_Identifier (Arg1, Name_Convention);
3388          Check_Arg_Is_Identifier (Arg1);
3389          Cname := Chars (Get_Pragma_Arg (Arg1));
3390
3391          --  C_Pass_By_Copy is treated as a synonym for convention C (this is
3392          --  tested again below to set the critical flag).
3393
3394          if Cname = Name_C_Pass_By_Copy then
3395             C := Convention_C;
3396
3397          --  Otherwise we must have something in the standard convention list
3398
3399          elsif Is_Convention_Name (Cname) then
3400             C := Get_Convention_Id (Chars (Get_Pragma_Arg (Arg1)));
3401
3402          --  In DEC VMS, it seems that there is an undocumented feature that
3403          --  any unrecognized convention is treated as the default, which for
3404          --  us is convention C. It does not seem so terrible to do this
3405          --  unconditionally, silently in the VMS case, and with a warning
3406          --  in the non-VMS case.
3407
3408          else
3409             if Warn_On_Export_Import and not OpenVMS_On_Target then
3410                Error_Msg_N
3411                  ("?unrecognized convention name, C assumed",
3412                   Get_Pragma_Arg (Arg1));
3413             end if;
3414
3415             C := Convention_C;
3416          end if;
3417
3418          Check_Optional_Identifier (Arg2, Name_Entity);
3419          Check_Arg_Is_Local_Name (Arg2);
3420
3421          Id := Get_Pragma_Arg (Arg2);
3422          Analyze (Id);
3423
3424          if not Is_Entity_Name (Id) then
3425             Error_Pragma_Arg ("entity name required", Arg2);
3426          end if;
3427
3428          E := Entity (Id);
3429
3430          --  Set entity to return
3431
3432          Ent := E;
3433
3434          --  Ada_Pass_By_Copy special checking
3435
3436          if C = Convention_Ada_Pass_By_Copy then
3437             if not Is_First_Subtype (E) then
3438                Error_Pragma_Arg
3439                  ("convention `Ada_Pass_By_Copy` only "
3440                   & "allowed for types", Arg2);
3441             end if;
3442
3443             if Is_By_Reference_Type (E) then
3444                Error_Pragma_Arg
3445                  ("convention `Ada_Pass_By_Copy` not allowed for "
3446                   & "by-reference type", Arg1);
3447             end if;
3448          end if;
3449
3450          --  Ada_Pass_By_Reference special checking
3451
3452          if C = Convention_Ada_Pass_By_Reference then
3453             if not Is_First_Subtype (E) then
3454                Error_Pragma_Arg
3455                  ("convention `Ada_Pass_By_Reference` only "
3456                   & "allowed for types", Arg2);
3457             end if;
3458
3459             if Is_By_Copy_Type (E) then
3460                Error_Pragma_Arg
3461                  ("convention `Ada_Pass_By_Reference` not allowed for "
3462                   & "by-copy type", Arg1);
3463             end if;
3464          end if;
3465
3466          --  Go to renamed subprogram if present, since convention applies to
3467          --  the actual renamed entity, not to the renaming entity. If the
3468          --  subprogram is inherited, go to parent subprogram.
3469
3470          if Is_Subprogram (E)
3471            and then Present (Alias (E))
3472          then
3473             if Nkind (Parent (Declaration_Node (E))) =
3474                                        N_Subprogram_Renaming_Declaration
3475             then
3476                if Scope (E) /= Scope (Alias (E)) then
3477                   Error_Pragma_Ref
3478                     ("cannot apply pragma% to non-local entity&#", E);
3479                end if;
3480
3481                E := Alias (E);
3482
3483             elsif Nkind_In (Parent (E), N_Full_Type_Declaration,
3484                                         N_Private_Extension_Declaration)
3485               and then Scope (E) = Scope (Alias (E))
3486             then
3487                E := Alias (E);
3488
3489                --  Return the parent subprogram the entity was inherited from
3490
3491                Ent := E;
3492             end if;
3493          end if;
3494
3495          --  Check that we are not applying this to a specless body
3496
3497          if Is_Subprogram (E)
3498            and then Nkind (Parent (Declaration_Node (E))) = N_Subprogram_Body
3499          then
3500             Error_Pragma
3501               ("pragma% requires separate spec and must come before body");
3502          end if;
3503
3504          --  Check that we are not applying this to a named constant
3505
3506          if Ekind_In (E, E_Named_Integer, E_Named_Real) then
3507             Error_Msg_Name_1 := Pname;
3508             Error_Msg_N
3509               ("cannot apply pragma% to named constant!",
3510                Get_Pragma_Arg (Arg2));
3511             Error_Pragma_Arg
3512               ("\supply appropriate type for&!", Arg2);
3513          end if;
3514
3515          if Ekind (E) = E_Enumeration_Literal then
3516             Error_Pragma ("enumeration literal not allowed for pragma%");
3517          end if;
3518
3519          --  Check for rep item appearing too early or too late
3520
3521          if Etype (E) = Any_Type
3522            or else Rep_Item_Too_Early (E, N)
3523          then
3524             raise Pragma_Exit;
3525
3526          elsif Present (Underlying_Type (E)) then
3527             E := Underlying_Type (E);
3528          end if;
3529
3530          if Rep_Item_Too_Late (E, N) then
3531             raise Pragma_Exit;
3532          end if;
3533
3534          if Has_Convention_Pragma (E) then
3535             Diagnose_Multiple_Pragmas (E);
3536
3537          elsif Convention (E) = Convention_Protected
3538            or else Ekind (Scope (E)) = E_Protected_Type
3539          then
3540             Error_Pragma_Arg
3541               ("a protected operation cannot be given a different convention",
3542                 Arg2);
3543          end if;
3544
3545          --  For Intrinsic, a subprogram is required
3546
3547          if C = Convention_Intrinsic
3548            and then not Is_Subprogram (E)
3549            and then not Is_Generic_Subprogram (E)
3550          then
3551             Error_Pragma_Arg
3552               ("second argument of pragma% must be a subprogram", Arg2);
3553          end if;
3554
3555          --  Stdcall case
3556
3557          if C = Convention_Stdcall then
3558
3559             --  A dispatching call is not allowed. A dispatching subprogram
3560             --  cannot be used to interface to the Win32 API, so in fact this
3561             --  check does not impose any effective restriction.
3562
3563             if Is_Dispatching_Operation (E) then
3564
3565                Error_Pragma
3566                  ("dispatching subprograms cannot use Stdcall convention");
3567
3568             --  Subprogram is allowed, but not a generic subprogram, and not a
3569             --  dispatching operation.
3570
3571             elsif not Is_Subprogram (E)
3572               and then not Is_Generic_Subprogram (E)
3573
3574               --  A variable is OK
3575
3576               and then Ekind (E) /= E_Variable
3577
3578               --  An access to subprogram is also allowed
3579
3580               and then not
3581                 (Is_Access_Type (E)
3582                   and then Ekind (Designated_Type (E)) = E_Subprogram_Type)
3583             then
3584                Error_Pragma_Arg
3585                  ("second argument of pragma% must be subprogram (type)",
3586                   Arg2);
3587             end if;
3588          end if;
3589
3590          if not Is_Subprogram (E)
3591            and then not Is_Generic_Subprogram (E)
3592          then
3593             Set_Convention_From_Pragma (E);
3594
3595             if Is_Type (E) then
3596                Check_First_Subtype (Arg2);
3597                Set_Convention_From_Pragma (Base_Type (E));
3598
3599                --  For subprograms, we must set the convention on the
3600                --  internally generated directly designated type as well.
3601
3602                if Ekind (E) = E_Access_Subprogram_Type then
3603                   Set_Convention_From_Pragma (Directly_Designated_Type (E));
3604                end if;
3605             end if;
3606
3607          --  For the subprogram case, set proper convention for all homonyms
3608          --  in same scope and the same declarative part, i.e. the same
3609          --  compilation unit.
3610
3611          else
3612             Comp_Unit := Get_Source_Unit (E);
3613             Set_Convention_From_Pragma (E);
3614
3615             --  Treat a pragma Import as an implicit body, for GPS use
3616
3617             if Prag_Id = Pragma_Import then
3618                Generate_Reference (E, Id, 'b');
3619             end if;
3620
3621             --  Loop through the homonyms of the pragma argument's entity
3622
3623             E1 := Ent;
3624             loop
3625                E1 := Homonym (E1);
3626                exit when No (E1) or else Scope (E1) /= Current_Scope;
3627
3628                --  Do not set the pragma on inherited operations or on formal
3629                --  subprograms.
3630
3631                if Comes_From_Source (E1)
3632                  and then Comp_Unit = Get_Source_Unit (E1)
3633                  and then not Is_Formal_Subprogram (E1)
3634                  and then Nkind (Original_Node (Parent (E1))) /=
3635                                                     N_Full_Type_Declaration
3636                then
3637                   if Present (Alias (E1))
3638                     and then Scope (E1) /= Scope (Alias (E1))
3639                   then
3640                      Error_Pragma_Ref
3641                        ("cannot apply pragma% to non-local entity& declared#",
3642                         E1);
3643                   end if;
3644
3645                   Set_Convention_From_Pragma (E1);
3646
3647                   if Prag_Id = Pragma_Import then
3648                      Generate_Reference (E1, Id, 'b');
3649                   end if;
3650                end if;
3651
3652                --  For aspect case, do NOT apply to homonyms
3653
3654                exit when From_Aspect_Specification (N);
3655             end loop;
3656          end if;
3657       end Process_Convention;
3658
3659       ----------------------------------------
3660       -- Process_Disable_Enable_Atomic_Sync --
3661       ----------------------------------------
3662
3663       procedure Process_Disable_Enable_Atomic_Sync (Nam : Name_Id) is
3664       begin
3665          GNAT_Pragma;
3666          Check_No_Identifiers;
3667          Check_At_Most_N_Arguments (1);
3668
3669          --  Modeled internally as
3670          --    pragma Unsuppress (Atomic_Synchronization [,Entity])
3671
3672          Rewrite (N,
3673            Make_Pragma (Loc,
3674              Pragma_Identifier            =>
3675                Make_Identifier (Loc, Nam),
3676              Pragma_Argument_Associations => New_List (
3677                Make_Pragma_Argument_Association (Loc,
3678                  Expression =>
3679                    Make_Identifier (Loc, Name_Atomic_Synchronization)))));
3680
3681          if Present (Arg1) then
3682             Append_To (Pragma_Argument_Associations (N), New_Copy (Arg1));
3683          end if;
3684
3685          Analyze (N);
3686       end Process_Disable_Enable_Atomic_Sync;
3687
3688       -----------------------------------------------------
3689       -- Process_Extended_Import_Export_Exception_Pragma --
3690       -----------------------------------------------------
3691
3692       procedure Process_Extended_Import_Export_Exception_Pragma
3693         (Arg_Internal : Node_Id;
3694          Arg_External : Node_Id;
3695          Arg_Form     : Node_Id;
3696          Arg_Code     : Node_Id)
3697       is
3698          Def_Id   : Entity_Id;
3699          Code_Val : Uint;
3700
3701       begin
3702          if not OpenVMS_On_Target then
3703             Error_Pragma
3704               ("?pragma% ignored (applies only to Open'V'M'S)");
3705          end if;
3706
3707          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3708          Def_Id := Entity (Arg_Internal);
3709
3710          if Ekind (Def_Id) /= E_Exception then
3711             Error_Pragma_Arg
3712               ("pragma% must refer to declared exception", Arg_Internal);
3713          end if;
3714
3715          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3716
3717          if Present (Arg_Form) then
3718             Check_Arg_Is_One_Of (Arg_Form, Name_Ada, Name_VMS);
3719          end if;
3720
3721          if Present (Arg_Form)
3722            and then Chars (Arg_Form) = Name_Ada
3723          then
3724             null;
3725          else
3726             Set_Is_VMS_Exception (Def_Id);
3727             Set_Exception_Code (Def_Id, No_Uint);
3728          end if;
3729
3730          if Present (Arg_Code) then
3731             if not Is_VMS_Exception (Def_Id) then
3732                Error_Pragma_Arg
3733                  ("Code option for pragma% not allowed for Ada case",
3734                   Arg_Code);
3735             end if;
3736
3737             Check_Arg_Is_Static_Expression (Arg_Code, Any_Integer);
3738             Code_Val := Expr_Value (Arg_Code);
3739
3740             if not UI_Is_In_Int_Range (Code_Val) then
3741                Error_Pragma_Arg
3742                  ("Code option for pragma% must be in 32-bit range",
3743                   Arg_Code);
3744
3745             else
3746                Set_Exception_Code (Def_Id, Code_Val);
3747             end if;
3748          end if;
3749       end Process_Extended_Import_Export_Exception_Pragma;
3750
3751       -------------------------------------------------
3752       -- Process_Extended_Import_Export_Internal_Arg --
3753       -------------------------------------------------
3754
3755       procedure Process_Extended_Import_Export_Internal_Arg
3756         (Arg_Internal : Node_Id := Empty)
3757       is
3758       begin
3759          if No (Arg_Internal) then
3760             Error_Pragma ("Internal parameter required for pragma%");
3761          end if;
3762
3763          if Nkind (Arg_Internal) = N_Identifier then
3764             null;
3765
3766          elsif Nkind (Arg_Internal) = N_Operator_Symbol
3767            and then (Prag_Id = Pragma_Import_Function
3768                        or else
3769                      Prag_Id = Pragma_Export_Function)
3770          then
3771             null;
3772
3773          else
3774             Error_Pragma_Arg
3775               ("wrong form for Internal parameter for pragma%", Arg_Internal);
3776          end if;
3777
3778          Check_Arg_Is_Local_Name (Arg_Internal);
3779       end Process_Extended_Import_Export_Internal_Arg;
3780
3781       --------------------------------------------------
3782       -- Process_Extended_Import_Export_Object_Pragma --
3783       --------------------------------------------------
3784
3785       procedure Process_Extended_Import_Export_Object_Pragma
3786         (Arg_Internal : Node_Id;
3787          Arg_External : Node_Id;
3788          Arg_Size     : Node_Id)
3789       is
3790          Def_Id : Entity_Id;
3791
3792       begin
3793          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3794          Def_Id := Entity (Arg_Internal);
3795
3796          if not Ekind_In (Def_Id, E_Constant, E_Variable) then
3797             Error_Pragma_Arg
3798               ("pragma% must designate an object", Arg_Internal);
3799          end if;
3800
3801          if Has_Rep_Pragma (Def_Id, Name_Common_Object)
3802               or else
3803             Has_Rep_Pragma (Def_Id, Name_Psect_Object)
3804          then
3805             Error_Pragma_Arg
3806               ("previous Common/Psect_Object applies, pragma % not permitted",
3807                Arg_Internal);
3808          end if;
3809
3810          if Rep_Item_Too_Late (Def_Id, N) then
3811             raise Pragma_Exit;
3812          end if;
3813
3814          Set_Extended_Import_Export_External_Name (Def_Id, Arg_External);
3815
3816          if Present (Arg_Size) then
3817             Check_Arg_Is_External_Name (Arg_Size);
3818          end if;
3819
3820          --  Export_Object case
3821
3822          if Prag_Id = Pragma_Export_Object then
3823             if not Is_Library_Level_Entity (Def_Id) then
3824                Error_Pragma_Arg
3825                  ("argument for pragma% must be library level entity",
3826                   Arg_Internal);
3827             end if;
3828
3829             if Ekind (Current_Scope) = E_Generic_Package then
3830                Error_Pragma ("pragma& cannot appear in a generic unit");
3831             end if;
3832
3833             if not Size_Known_At_Compile_Time (Etype (Def_Id)) then
3834                Error_Pragma_Arg
3835                  ("exported object must have compile time known size",
3836                   Arg_Internal);
3837             end if;
3838
3839             if Warn_On_Export_Import and then Is_Exported (Def_Id) then
3840                Error_Msg_N ("?duplicate Export_Object pragma", N);
3841             else
3842                Set_Exported (Def_Id, Arg_Internal);
3843             end if;
3844
3845          --  Import_Object case
3846
3847          else
3848             if Is_Concurrent_Type (Etype (Def_Id)) then
3849                Error_Pragma_Arg
3850                  ("cannot use pragma% for task/protected object",
3851                   Arg_Internal);
3852             end if;
3853
3854             if Ekind (Def_Id) = E_Constant then
3855                Error_Pragma_Arg
3856                  ("cannot import a constant", Arg_Internal);
3857             end if;
3858
3859             if Warn_On_Export_Import
3860               and then Has_Discriminants (Etype (Def_Id))
3861             then
3862                Error_Msg_N
3863                  ("imported value must be initialized?", Arg_Internal);
3864             end if;
3865
3866             if Warn_On_Export_Import
3867               and then Is_Access_Type (Etype (Def_Id))
3868             then
3869                Error_Pragma_Arg
3870                  ("cannot import object of an access type?", Arg_Internal);
3871             end if;
3872
3873             if Warn_On_Export_Import
3874               and then Is_Imported (Def_Id)
3875             then
3876                Error_Msg_N
3877                  ("?duplicate Import_Object pragma", N);
3878
3879             --  Check for explicit initialization present. Note that an
3880             --  initialization generated by the code generator, e.g. for an
3881             --  access type, does not count here.
3882
3883             elsif Present (Expression (Parent (Def_Id)))
3884                and then
3885                  Comes_From_Source
3886                    (Original_Node (Expression (Parent (Def_Id))))
3887             then
3888                Error_Msg_Sloc := Sloc (Def_Id);
3889                Error_Pragma_Arg
3890                  ("imported entities cannot be initialized (RM B.1(24))",
3891                   "\no initialization allowed for & declared#", Arg1);
3892             else
3893                Set_Imported (Def_Id);
3894                Note_Possible_Modification (Arg_Internal, Sure => False);
3895             end if;
3896          end if;
3897       end Process_Extended_Import_Export_Object_Pragma;
3898
3899       ------------------------------------------------------
3900       -- Process_Extended_Import_Export_Subprogram_Pragma --
3901       ------------------------------------------------------
3902
3903       procedure Process_Extended_Import_Export_Subprogram_Pragma
3904         (Arg_Internal                 : Node_Id;
3905          Arg_External                 : Node_Id;
3906          Arg_Parameter_Types          : Node_Id;
3907          Arg_Result_Type              : Node_Id := Empty;
3908          Arg_Mechanism                : Node_Id;
3909          Arg_Result_Mechanism         : Node_Id := Empty;
3910          Arg_First_Optional_Parameter : Node_Id := Empty)
3911       is
3912          Ent       : Entity_Id;
3913          Def_Id    : Entity_Id;
3914          Hom_Id    : Entity_Id;
3915          Formal    : Entity_Id;
3916          Ambiguous : Boolean;
3917          Match     : Boolean;
3918          Dval      : Node_Id;
3919
3920          function Same_Base_Type
3921           (Ptype  : Node_Id;
3922            Formal : Entity_Id) return Boolean;
3923          --  Determines if Ptype references the type of Formal. Note that only
3924          --  the base types need to match according to the spec. Ptype here is
3925          --  the argument from the pragma, which is either a type name, or an
3926          --  access attribute.
3927
3928          --------------------
3929          -- Same_Base_Type --
3930          --------------------
3931
3932          function Same_Base_Type
3933            (Ptype  : Node_Id;
3934             Formal : Entity_Id) return Boolean
3935          is
3936             Ftyp : constant Entity_Id := Base_Type (Etype (Formal));
3937             Pref : Node_Id;
3938
3939          begin
3940             --  Case where pragma argument is typ'Access
3941
3942             if Nkind (Ptype) = N_Attribute_Reference
3943               and then Attribute_Name (Ptype) = Name_Access
3944             then
3945                Pref := Prefix (Ptype);
3946                Find_Type (Pref);
3947
3948                if not Is_Entity_Name (Pref)
3949                  or else Entity (Pref) = Any_Type
3950                then
3951                   raise Pragma_Exit;
3952                end if;
3953
3954                --  We have a match if the corresponding argument is of an
3955                --  anonymous access type, and its designated type matches the
3956                --  type of the prefix of the access attribute
3957
3958                return Ekind (Ftyp) = E_Anonymous_Access_Type
3959                  and then Base_Type (Entity (Pref)) =
3960                             Base_Type (Etype (Designated_Type (Ftyp)));
3961
3962             --  Case where pragma argument is a type name
3963
3964             else
3965                Find_Type (Ptype);
3966
3967                if not Is_Entity_Name (Ptype)
3968                  or else Entity (Ptype) = Any_Type
3969                then
3970                   raise Pragma_Exit;
3971                end if;
3972
3973                --  We have a match if the corresponding argument is of the type
3974                --  given in the pragma (comparing base types)
3975
3976                return Base_Type (Entity (Ptype)) = Ftyp;
3977             end if;
3978          end Same_Base_Type;
3979
3980       --  Start of processing for
3981       --  Process_Extended_Import_Export_Subprogram_Pragma
3982
3983       begin
3984          Process_Extended_Import_Export_Internal_Arg (Arg_Internal);
3985          Ent := Empty;
3986          Ambiguous := False;
3987
3988          --  Loop through homonyms (overloadings) of the entity
3989
3990          Hom_Id := Entity (Arg_Internal);
3991          while Present (Hom_Id) loop
3992             Def_Id := Get_Base_Subprogram (Hom_Id);
3993
3994             --  We need a subprogram in the current scope
3995
3996             if not Is_Subprogram (Def_Id)
3997               or else Scope (Def_Id) /= Current_Scope
3998             then
3999                null;
4000
4001             else
4002                Match := True;
4003
4004                --  Pragma cannot apply to subprogram body
4005
4006                if Is_Subprogram (Def_Id)
4007                  and then Nkind (Parent (Declaration_Node (Def_Id))) =
4008                                                              N_Subprogram_Body
4009                then
4010                   Error_Pragma
4011                     ("pragma% requires separate spec"
4012                       & " and must come before body");
4013                end if;
4014
4015                --  Test result type if given, note that the result type
4016                --  parameter can only be present for the function cases.
4017
4018                if Present (Arg_Result_Type)
4019                  and then not Same_Base_Type (Arg_Result_Type, Def_Id)
4020                then
4021                   Match := False;
4022
4023                elsif Etype (Def_Id) /= Standard_Void_Type
4024                  and then
4025                    (Pname = Name_Export_Procedure
4026                       or else
4027                     Pname = Name_Import_Procedure)
4028                then
4029                   Match := False;
4030
4031                --  Test parameter types if given. Note that this parameter
4032                --  has not been analyzed (and must not be, since it is
4033                --  semantic nonsense), so we get it as the parser left it.
4034
4035                elsif Present (Arg_Parameter_Types) then
4036                   Check_Matching_Types : declare
4037                      Formal : Entity_Id;
4038                      Ptype  : Node_Id;
4039
4040                   begin
4041                      Formal := First_Formal (Def_Id);
4042
4043                      if Nkind (Arg_Parameter_Types) = N_Null then
4044                         if Present (Formal) then
4045                            Match := False;
4046                         end if;
4047
4048                      --  A list of one type, e.g. (List) is parsed as
4049                      --  a parenthesized expression.
4050
4051                      elsif Nkind (Arg_Parameter_Types) /= N_Aggregate
4052                        and then Paren_Count (Arg_Parameter_Types) = 1
4053                      then
4054                         if No (Formal)
4055                           or else Present (Next_Formal (Formal))
4056                         then
4057                            Match := False;
4058                         else
4059                            Match :=
4060                              Same_Base_Type (Arg_Parameter_Types, Formal);
4061                         end if;
4062
4063                      --  A list of more than one type is parsed as a aggregate
4064
4065                      elsif Nkind (Arg_Parameter_Types) = N_Aggregate
4066                        and then Paren_Count (Arg_Parameter_Types) = 0
4067                      then
4068                         Ptype := First (Expressions (Arg_Parameter_Types));
4069                         while Present (Ptype) or else Present (Formal) loop
4070                            if No (Ptype)
4071                              or else No (Formal)
4072                              or else not Same_Base_Type (Ptype, Formal)
4073                            then
4074                               Match := False;
4075                               exit;
4076                            else
4077                               Next_Formal (Formal);
4078                               Next (Ptype);
4079                            end if;
4080                         end loop;
4081
4082                      --  Anything else is of the wrong form
4083
4084                      else
4085                         Error_Pragma_Arg
4086                           ("wrong form for Parameter_Types parameter",
4087                            Arg_Parameter_Types);
4088                      end if;
4089                   end Check_Matching_Types;
4090                end if;
4091
4092                --  Match is now False if the entry we found did not match
4093                --  either a supplied Parameter_Types or Result_Types argument
4094
4095                if Match then
4096                   if No (Ent) then
4097                      Ent := Def_Id;
4098
4099                   --  Ambiguous case, the flag Ambiguous shows if we already
4100                   --  detected this and output the initial messages.
4101
4102                   else
4103                      if not Ambiguous then
4104                         Ambiguous := True;
4105                         Error_Msg_Name_1 := Pname;
4106                         Error_Msg_N
4107                           ("pragma% does not uniquely identify subprogram!",
4108                            N);
4109                         Error_Msg_Sloc := Sloc (Ent);
4110                         Error_Msg_N ("matching subprogram #!", N);
4111                         Ent := Empty;
4112                      end if;
4113
4114                      Error_Msg_Sloc := Sloc (Def_Id);
4115                      Error_Msg_N ("matching subprogram #!", N);
4116                   end if;
4117                end if;
4118             end if;
4119
4120             Hom_Id := Homonym (Hom_Id);
4121          end loop;
4122
4123          --  See if we found an entry
4124
4125          if No (Ent) then
4126             if not Ambiguous then
4127                if Is_Generic_Subprogram (Entity (Arg_Internal)) then
4128                   Error_Pragma
4129                     ("pragma% cannot be given for generic subprogram");
4130                else
4131                   Error_Pragma
4132                     ("pragma% does not identify local subprogram");
4133                end if;
4134             end if;
4135
4136             return;
4137          end if;
4138
4139          --  Import pragmas must be for imported entities
4140
4141          if Prag_Id = Pragma_Import_Function
4142               or else
4143             Prag_Id = Pragma_Import_Procedure
4144               or else
4145             Prag_Id = Pragma_Import_Valued_Procedure
4146          then
4147             if not Is_Imported (Ent) then
4148                Error_Pragma
4149                  ("pragma Import or Interface must precede pragma%");
4150             end if;
4151
4152          --  Here we have the Export case which can set the entity as exported
4153
4154          --  But does not do so if the specified external name is null, since
4155          --  that is taken as a signal in DEC Ada 83 (with which we want to be
4156          --  compatible) to request no external name.
4157
4158          elsif Nkind (Arg_External) = N_String_Literal
4159            and then String_Length (Strval (Arg_External)) = 0
4160          then
4161             null;
4162
4163          --  In all other cases, set entity as exported
4164
4165          else
4166             Set_Exported (Ent, Arg_Internal);
4167          end if;
4168
4169          --  Special processing for Valued_Procedure cases
4170
4171          if Prag_Id = Pragma_Import_Valued_Procedure
4172            or else
4173             Prag_Id = Pragma_Export_Valued_Procedure
4174          then
4175             Formal := First_Formal (Ent);
4176
4177             if No (Formal) then
4178                Error_Pragma ("at least one parameter required for pragma%");
4179
4180             elsif Ekind (Formal) /= E_Out_Parameter then
4181                Error_Pragma ("first parameter must have mode out for pragma%");
4182
4183             else
4184                Set_Is_Valued_Procedure (Ent);
4185             end if;
4186          end if;
4187
4188          Set_Extended_Import_Export_External_Name (Ent, Arg_External);
4189
4190          --  Process Result_Mechanism argument if present. We have already
4191          --  checked that this is only allowed for the function case.
4192
4193          if Present (Arg_Result_Mechanism) then
4194             Set_Mechanism_Value (Ent, Arg_Result_Mechanism);
4195          end if;
4196
4197          --  Process Mechanism parameter if present. Note that this parameter
4198          --  is not analyzed, and must not be analyzed since it is semantic
4199          --  nonsense, so we get it in exactly as the parser left it.
4200
4201          if Present (Arg_Mechanism) then
4202             declare
4203                Formal : Entity_Id;
4204                Massoc : Node_Id;
4205                Mname  : Node_Id;
4206                Choice : Node_Id;
4207
4208             begin
4209                --  A single mechanism association without a formal parameter
4210                --  name is parsed as a parenthesized expression. All other
4211                --  cases are parsed as aggregates, so we rewrite the single
4212                --  parameter case as an aggregate for consistency.
4213
4214                if Nkind (Arg_Mechanism) /= N_Aggregate
4215                  and then Paren_Count (Arg_Mechanism) = 1
4216                then
4217                   Rewrite (Arg_Mechanism,
4218                     Make_Aggregate (Sloc (Arg_Mechanism),
4219                       Expressions => New_List (
4220                         Relocate_Node (Arg_Mechanism))));
4221                end if;
4222
4223                --  Case of only mechanism name given, applies to all formals
4224
4225                if Nkind (Arg_Mechanism) /= N_Aggregate then
4226                   Formal := First_Formal (Ent);
4227                   while Present (Formal) loop
4228                      Set_Mechanism_Value (Formal, Arg_Mechanism);
4229                      Next_Formal (Formal);
4230                   end loop;
4231
4232                --  Case of list of mechanism associations given
4233
4234                else
4235                   if Null_Record_Present (Arg_Mechanism) then
4236                      Error_Pragma_Arg
4237                        ("inappropriate form for Mechanism parameter",
4238                         Arg_Mechanism);
4239                   end if;
4240
4241                   --  Deal with positional ones first
4242
4243                   Formal := First_Formal (Ent);
4244
4245                   if Present (Expressions (Arg_Mechanism)) then
4246                      Mname := First (Expressions (Arg_Mechanism));
4247                      while Present (Mname) loop
4248                         if No (Formal) then
4249                            Error_Pragma_Arg
4250                              ("too many mechanism associations", Mname);
4251                         end if;
4252
4253                         Set_Mechanism_Value (Formal, Mname);
4254                         Next_Formal (Formal);
4255                         Next (Mname);
4256                      end loop;
4257                   end if;
4258
4259                   --  Deal with named entries
4260
4261                   if Present (Component_Associations (Arg_Mechanism)) then
4262                      Massoc := First (Component_Associations (Arg_Mechanism));
4263                      while Present (Massoc) loop
4264                         Choice := First (Choices (Massoc));
4265
4266                         if Nkind (Choice) /= N_Identifier
4267                           or else Present (Next (Choice))
4268                         then
4269                            Error_Pragma_Arg
4270                              ("incorrect form for mechanism association",
4271                               Massoc);
4272                         end if;
4273
4274                         Formal := First_Formal (Ent);
4275                         loop
4276                            if No (Formal) then
4277                               Error_Pragma_Arg
4278                                 ("parameter name & not present", Choice);
4279                            end if;
4280
4281                            if Chars (Choice) = Chars (Formal) then
4282                               Set_Mechanism_Value
4283                                 (Formal, Expression (Massoc));
4284
4285                               --  Set entity on identifier (needed by ASIS)
4286
4287                               Set_Entity (Choice, Formal);
4288
4289                               exit;
4290                            end if;
4291
4292                            Next_Formal (Formal);
4293                         end loop;
4294
4295                         Next (Massoc);
4296                      end loop;
4297                   end if;
4298                end if;
4299             end;
4300          end if;
4301
4302          --  Process First_Optional_Parameter argument if present. We have
4303          --  already checked that this is only allowed for the Import case.
4304
4305          if Present (Arg_First_Optional_Parameter) then
4306             if Nkind (Arg_First_Optional_Parameter) /= N_Identifier then
4307                Error_Pragma_Arg
4308                  ("first optional parameter must be formal parameter name",
4309                   Arg_First_Optional_Parameter);
4310             end if;
4311
4312             Formal := First_Formal (Ent);
4313             loop
4314                if No (Formal) then
4315                   Error_Pragma_Arg
4316                     ("specified formal parameter& not found",
4317                      Arg_First_Optional_Parameter);
4318                end if;
4319
4320                exit when Chars (Formal) =
4321                          Chars (Arg_First_Optional_Parameter);
4322
4323                Next_Formal (Formal);
4324             end loop;
4325
4326             Set_First_Optional_Parameter (Ent, Formal);
4327
4328             --  Check specified and all remaining formals have right form
4329
4330             while Present (Formal) loop
4331                if Ekind (Formal) /= E_In_Parameter then
4332                   Error_Msg_NE
4333                     ("optional formal& is not of mode in!",
4334                      Arg_First_Optional_Parameter, Formal);
4335
4336                else
4337                   Dval := Default_Value (Formal);
4338
4339                   if No (Dval) then
4340                      Error_Msg_NE
4341                        ("optional formal& does not have default value!",
4342                         Arg_First_Optional_Parameter, Formal);
4343
4344                   elsif Compile_Time_Known_Value_Or_Aggr (Dval) then
4345                      null;
4346
4347                   else
4348                      Error_Msg_FE
4349                        ("default value for optional formal& is non-static!",
4350                         Arg_First_Optional_Parameter, Formal);
4351                   end if;
4352                end if;
4353
4354                Set_Is_Optional_Parameter (Formal);
4355                Next_Formal (Formal);
4356             end loop;
4357          end if;
4358       end Process_Extended_Import_Export_Subprogram_Pragma;
4359
4360       --------------------------
4361       -- Process_Generic_List --
4362       --------------------------
4363
4364       procedure Process_Generic_List is
4365          Arg : Node_Id;
4366          Exp : Node_Id;
4367
4368       begin
4369          Check_No_Identifiers;
4370          Check_At_Least_N_Arguments (1);
4371
4372          Arg := Arg1;
4373          while Present (Arg) loop
4374             Exp := Get_Pragma_Arg (Arg);
4375             Analyze (Exp);
4376
4377             if not Is_Entity_Name (Exp)
4378               or else
4379                 (not Is_Generic_Instance (Entity (Exp))
4380                   and then
4381                  not Is_Generic_Unit (Entity (Exp)))
4382             then
4383                Error_Pragma_Arg
4384                  ("pragma% argument must be name of generic unit/instance",
4385                   Arg);
4386             end if;
4387
4388             Next (Arg);
4389          end loop;
4390       end Process_Generic_List;
4391
4392       ------------------------------------
4393       -- Process_Import_Predefined_Type --
4394       ------------------------------------
4395
4396       procedure Process_Import_Predefined_Type is
4397          Loc  : constant Source_Ptr := Sloc (N);
4398          Elmt : Elmt_Id;
4399          Ftyp : Node_Id := Empty;
4400          Decl : Node_Id;
4401          Def  : Node_Id;
4402          Nam  : Name_Id;
4403
4404       begin
4405          String_To_Name_Buffer (Strval (Expression (Arg3)));
4406          Nam := Name_Find;
4407
4408          Elmt := First_Elmt (Predefined_Float_Types);
4409          while Present (Elmt) and then Chars (Node (Elmt)) /= Nam loop
4410             Next_Elmt (Elmt);
4411          end loop;
4412
4413          Ftyp := Node (Elmt);
4414
4415          if Present (Ftyp) then
4416
4417             --  Don't build a derived type declaration, because predefined C
4418             --  types have no declaration anywhere, so cannot really be named.
4419             --  Instead build a full type declaration, starting with an
4420             --  appropriate type definition is built
4421
4422             if Is_Floating_Point_Type (Ftyp) then
4423                Def := Make_Floating_Point_Definition (Loc,
4424                  Make_Integer_Literal (Loc, Digits_Value (Ftyp)),
4425                  Make_Real_Range_Specification (Loc,
4426                    Make_Real_Literal (Loc, Realval (Type_Low_Bound (Ftyp))),
4427                    Make_Real_Literal (Loc, Realval (Type_High_Bound (Ftyp)))));
4428
4429             --  Should never have a predefined type we cannot handle
4430
4431             else
4432                raise Program_Error;
4433             end if;
4434
4435             --  Build and insert a Full_Type_Declaration, which will be
4436             --  analyzed as soon as this list entry has been analyzed.
4437
4438             Decl := Make_Full_Type_Declaration (Loc,
4439               Make_Defining_Identifier (Loc, Chars (Expression (Arg2))),
4440               Type_Definition => Def);
4441
4442             Insert_After (N, Decl);
4443             Mark_Rewrite_Insertion (Decl);
4444
4445          else
4446             Error_Pragma_Arg ("no matching type found for pragma%",
4447             Arg2);
4448          end if;
4449       end Process_Import_Predefined_Type;
4450
4451       ---------------------------------
4452       -- Process_Import_Or_Interface --
4453       ---------------------------------
4454
4455       procedure Process_Import_Or_Interface is
4456          C      : Convention_Id;
4457          Def_Id : Entity_Id;
4458          Hom_Id : Entity_Id;
4459
4460       begin
4461          Process_Convention (C, Def_Id);
4462          Kill_Size_Check_Code (Def_Id);
4463          Note_Possible_Modification (Get_Pragma_Arg (Arg2), Sure => False);
4464
4465          if Ekind_In (Def_Id, E_Variable, E_Constant) then
4466
4467             --  We do not permit Import to apply to a renaming declaration
4468
4469             if Present (Renamed_Object (Def_Id)) then
4470                Error_Pragma_Arg
4471                  ("pragma% not allowed for object renaming", Arg2);
4472
4473             --  User initialization is not allowed for imported object, but
4474             --  the object declaration may contain a default initialization,
4475             --  that will be discarded. Note that an explicit initialization
4476             --  only counts if it comes from source, otherwise it is simply
4477             --  the code generator making an implicit initialization explicit.
4478
4479             elsif Present (Expression (Parent (Def_Id)))
4480               and then Comes_From_Source (Expression (Parent (Def_Id)))
4481             then
4482                Error_Msg_Sloc := Sloc (Def_Id);
4483                Error_Pragma_Arg
4484                  ("no initialization allowed for declaration of& #",
4485                   "\imported entities cannot be initialized (RM B.1(24))",
4486                   Arg2);
4487
4488             else
4489                Set_Imported (Def_Id);
4490                Process_Interface_Name (Def_Id, Arg3, Arg4);
4491
4492                --  Note that we do not set Is_Public here. That's because we
4493                --  only want to set it if there is no address clause, and we
4494                --  don't know that yet, so we delay that processing till
4495                --  freeze time.
4496
4497                --  pragma Import completes deferred constants
4498
4499                if Ekind (Def_Id) = E_Constant then
4500                   Set_Has_Completion (Def_Id);
4501                end if;
4502
4503                --  It is not possible to import a constant of an unconstrained
4504                --  array type (e.g. string) because there is no simple way to
4505                --  write a meaningful subtype for it.
4506
4507                if Is_Array_Type (Etype (Def_Id))
4508                  and then not Is_Constrained (Etype (Def_Id))
4509                then
4510                   Error_Msg_NE
4511                     ("imported constant& must have a constrained subtype",
4512                       N, Def_Id);
4513                end if;
4514             end if;
4515
4516          elsif Is_Subprogram (Def_Id)
4517            or else Is_Generic_Subprogram (Def_Id)
4518          then
4519             --  If the name is overloaded, pragma applies to all of the denoted
4520             --  entities in the same declarative part.
4521
4522             Hom_Id := Def_Id;
4523             while Present (Hom_Id) loop
4524                Def_Id := Get_Base_Subprogram (Hom_Id);
4525
4526                --  Ignore inherited subprograms because the pragma will apply
4527                --  to the parent operation, which is the one called.
4528
4529                if Is_Overloadable (Def_Id)
4530                  and then Present (Alias (Def_Id))
4531                then
4532                   null;
4533
4534                --  If it is not a subprogram, it must be in an outer scope and
4535                --  pragma does not apply.
4536
4537                elsif not Is_Subprogram (Def_Id)
4538                  and then not Is_Generic_Subprogram (Def_Id)
4539                then
4540                   null;
4541
4542                --  The pragma does not apply to primitives of interfaces
4543
4544                elsif Is_Dispatching_Operation (Def_Id)
4545                  and then Present (Find_Dispatching_Type (Def_Id))
4546                  and then Is_Interface (Find_Dispatching_Type (Def_Id))
4547                then
4548                   null;
4549
4550                --  Verify that the homonym is in the same declarative part (not
4551                --  just the same scope).
4552
4553                elsif Parent (Unit_Declaration_Node (Def_Id)) /= Parent (N)
4554                  and then Nkind (Parent (N)) /= N_Compilation_Unit_Aux
4555                then
4556                   exit;
4557
4558                else
4559                   Set_Imported (Def_Id);
4560
4561                   --  Reject an Import applied to an abstract subprogram
4562
4563                   if Is_Subprogram (Def_Id)
4564                     and then Is_Abstract_Subprogram (Def_Id)
4565                   then
4566                      Error_Msg_Sloc := Sloc (Def_Id);
4567                      Error_Msg_NE
4568                        ("cannot import abstract subprogram& declared#",
4569                         Arg2, Def_Id);
4570                   end if;
4571
4572                   --  Special processing for Convention_Intrinsic
4573
4574                   if C = Convention_Intrinsic then
4575
4576                      --  Link_Name argument not allowed for intrinsic
4577
4578                      Check_No_Link_Name;
4579
4580                      Set_Is_Intrinsic_Subprogram (Def_Id);
4581
4582                      --  If no external name is present, then check that this
4583                      --  is a valid intrinsic subprogram. If an external name
4584                      --  is present, then this is handled by the back end.
4585
4586                      if No (Arg3) then
4587                         Check_Intrinsic_Subprogram
4588                           (Def_Id, Get_Pragma_Arg (Arg2));
4589                      end if;
4590                   end if;
4591
4592                   --  All interfaced procedures need an external symbol created
4593                   --  for them since they are always referenced from another
4594                   --  object file.
4595
4596                   Set_Is_Public (Def_Id);
4597
4598                   --  Verify that the subprogram does not have a completion
4599                   --  through a renaming declaration. For other completions the
4600                   --  pragma appears as a too late representation.
4601
4602                   declare
4603                      Decl : constant Node_Id := Unit_Declaration_Node (Def_Id);
4604
4605                   begin
4606                      if Present (Decl)
4607                        and then Nkind (Decl) = N_Subprogram_Declaration
4608                        and then Present (Corresponding_Body (Decl))
4609                        and then Nkind (Unit_Declaration_Node
4610                                         (Corresponding_Body (Decl))) =
4611                                              N_Subprogram_Renaming_Declaration
4612                      then
4613                         Error_Msg_Sloc := Sloc (Def_Id);
4614                         Error_Msg_NE
4615                           ("cannot import&, renaming already provided for " &
4616                            "declaration #", N, Def_Id);
4617                      end if;
4618                   end;
4619
4620                   Set_Has_Completion (Def_Id);
4621                   Process_Interface_Name (Def_Id, Arg3, Arg4);
4622                end if;
4623
4624                if Is_Compilation_Unit (Hom_Id) then
4625
4626                   --  Its possible homonyms are not affected by the pragma.
4627                   --  Such homonyms might be present in the context of other
4628                   --  units being compiled.
4629
4630                   exit;
4631
4632                else
4633                   Hom_Id := Homonym (Hom_Id);
4634                end if;
4635             end loop;
4636
4637          --  When the convention is Java or CIL, we also allow Import to be
4638          --  given for packages, generic packages, exceptions, record
4639          --  components, and access to subprograms.
4640
4641          elsif (C = Convention_Java or else C = Convention_CIL)
4642            and then
4643              (Is_Package_Or_Generic_Package (Def_Id)
4644                or else Ekind (Def_Id) = E_Exception
4645                or else Ekind (Def_Id) = E_Access_Subprogram_Type
4646                or else Nkind (Parent (Def_Id)) = N_Component_Declaration)
4647          then
4648             Set_Imported (Def_Id);
4649             Set_Is_Public (Def_Id);
4650             Process_Interface_Name (Def_Id, Arg3, Arg4);
4651
4652          --  Import a CPP class
4653
4654          elsif C = Convention_CPP
4655            and then (Is_Record_Type (Def_Id)
4656                       or else Ekind (Def_Id) = E_Incomplete_Type)
4657          then
4658             if Ekind (Def_Id) = E_Incomplete_Type then
4659                if Present (Full_View (Def_Id)) then
4660                   Def_Id := Full_View (Def_Id);
4661
4662                else
4663                   Error_Msg_N
4664                     ("cannot import 'C'P'P type before full declaration seen",
4665                      Get_Pragma_Arg (Arg2));
4666
4667                   --  Although we have reported the error we decorate it as
4668                   --  CPP_Class to avoid reporting spurious errors
4669
4670                   Set_Is_CPP_Class (Def_Id);
4671                   return;
4672                end if;
4673             end if;
4674
4675             --  Types treated as CPP classes must be declared limited (note:
4676             --  this used to be a warning but there is no real benefit to it
4677             --  since we did effectively intend to treat the type as limited
4678             --  anyway).
4679
4680             if not Is_Limited_Type (Def_Id) then
4681                Error_Msg_N
4682                  ("imported 'C'P'P type must be limited",
4683                   Get_Pragma_Arg (Arg2));
4684             end if;
4685
4686             Set_Is_CPP_Class (Def_Id);
4687
4688             --  Imported CPP types must not have discriminants (because C++
4689             --  classes do not have discriminants).
4690
4691             if Has_Discriminants (Def_Id) then
4692                Error_Msg_N
4693                  ("imported 'C'P'P type cannot have discriminants",
4694                   First (Discriminant_Specifications
4695                           (Declaration_Node (Def_Id))));
4696             end if;
4697
4698             --  Check that components of imported CPP types do not have default
4699             --  expressions. For private types this check is performed when the
4700             --  full view is analyzed (see Process_Full_View).
4701
4702             if not Is_Private_Type (Def_Id) then
4703                Check_CPP_Type_Has_No_Defaults (Def_Id);
4704             end if;
4705
4706          elsif Nkind (Parent (Def_Id)) = N_Incomplete_Type_Declaration then
4707             Check_No_Link_Name;
4708             Check_Arg_Count (3);
4709             Check_Arg_Is_Static_Expression (Arg3, Standard_String);
4710
4711             Process_Import_Predefined_Type;
4712
4713          else
4714             Error_Pragma_Arg
4715               ("second argument of pragma% must be object, subprogram "
4716                & "or incomplete type",
4717                Arg2);
4718          end if;
4719
4720          --  If this pragma applies to a compilation unit, then the unit, which
4721          --  is a subprogram, does not require (or allow) a body. We also do
4722          --  not need to elaborate imported procedures.
4723
4724          if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
4725             declare
4726                Cunit : constant Node_Id := Parent (Parent (N));
4727             begin
4728                Set_Body_Required (Cunit, False);
4729             end;
4730          end if;
4731       end Process_Import_Or_Interface;
4732
4733       --------------------
4734       -- Process_Inline --
4735       --------------------
4736
4737       procedure Process_Inline (Active : Boolean) is
4738          Assoc     : Node_Id;
4739          Decl      : Node_Id;
4740          Subp_Id   : Node_Id;
4741          Subp      : Entity_Id;
4742          Applies   : Boolean;
4743
4744          Effective : Boolean := False;
4745          --  Set True if inline has some effect, i.e. if there is at least one
4746          --  subprogram set as inlined as a result of the use of the pragma.
4747
4748          procedure Make_Inline (Subp : Entity_Id);
4749          --  Subp is the defining unit name of the subprogram declaration. Set
4750          --  the flag, as well as the flag in the corresponding body, if there
4751          --  is one present.
4752
4753          procedure Set_Inline_Flags (Subp : Entity_Id);
4754          --  Sets Is_Inlined and Has_Pragma_Inline flags for Subp and also
4755          --  Has_Pragma_Inline_Always for the Inline_Always case.
4756
4757          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean;
4758          --  Returns True if it can be determined at this stage that inlining
4759          --  is not possible, for example if the body is available and contains
4760          --  exception handlers, we prevent inlining, since otherwise we can
4761          --  get undefined symbols at link time. This function also emits a
4762          --  warning if front-end inlining is enabled and the pragma appears
4763          --  too late.
4764          --
4765          --  ??? is business with link symbols still valid, or does it relate
4766          --  to front end ZCX which is being phased out ???
4767
4768          ---------------------------
4769          -- Inlining_Not_Possible --
4770          ---------------------------
4771
4772          function Inlining_Not_Possible (Subp : Entity_Id) return Boolean is
4773             Decl  : constant Node_Id := Unit_Declaration_Node (Subp);
4774             Stats : Node_Id;
4775
4776          begin
4777             if Nkind (Decl) = N_Subprogram_Body then
4778                Stats := Handled_Statement_Sequence (Decl);
4779                return Present (Exception_Handlers (Stats))
4780                  or else Present (At_End_Proc (Stats));
4781
4782             elsif Nkind (Decl) = N_Subprogram_Declaration
4783               and then Present (Corresponding_Body (Decl))
4784             then
4785                if Front_End_Inlining
4786                  and then Analyzed (Corresponding_Body (Decl))
4787                then
4788                   Error_Msg_N ("pragma appears too late, ignored?", N);
4789                   return True;
4790
4791                --  If the subprogram is a renaming as body, the body is just a
4792                --  call to the renamed subprogram, and inlining is trivially
4793                --  possible.
4794
4795                elsif
4796                  Nkind (Unit_Declaration_Node (Corresponding_Body (Decl))) =
4797                                              N_Subprogram_Renaming_Declaration
4798                then
4799                   return False;
4800
4801                else
4802                   Stats :=
4803                     Handled_Statement_Sequence
4804                         (Unit_Declaration_Node (Corresponding_Body (Decl)));
4805
4806                   return
4807                     Present (Exception_Handlers (Stats))
4808                       or else Present (At_End_Proc (Stats));
4809                end if;
4810
4811             else
4812                --  If body is not available, assume the best, the check is
4813                --  performed again when compiling enclosing package bodies.
4814
4815                return False;
4816             end if;
4817          end Inlining_Not_Possible;
4818
4819          -----------------
4820          -- Make_Inline --
4821          -----------------
4822
4823          procedure Make_Inline (Subp : Entity_Id) is
4824             Kind       : constant Entity_Kind := Ekind (Subp);
4825             Inner_Subp : Entity_Id   := Subp;
4826
4827          begin
4828             --  Ignore if bad type, avoid cascaded error
4829
4830             if Etype (Subp) = Any_Type then
4831                Applies := True;
4832                return;
4833
4834             --  Ignore if all inlining is suppressed
4835
4836             elsif Suppress_All_Inlining then
4837                Applies := True;
4838                return;
4839
4840             --  If inlining is not possible, for now do not treat as an error
4841
4842             elsif Inlining_Not_Possible (Subp) then
4843                Applies := True;
4844                return;
4845
4846             --  Here we have a candidate for inlining, but we must exclude
4847             --  derived operations. Otherwise we would end up trying to inline
4848             --  a phantom declaration, and the result would be to drag in a
4849             --  body which has no direct inlining associated with it. That
4850             --  would not only be inefficient but would also result in the
4851             --  backend doing cross-unit inlining in cases where it was
4852             --  definitely inappropriate to do so.
4853
4854             --  However, a simple Comes_From_Source test is insufficient, since
4855             --  we do want to allow inlining of generic instances which also do
4856             --  not come from source. We also need to recognize specs generated
4857             --  by the front-end for bodies that carry the pragma. Finally,
4858             --  predefined operators do not come from source but are not
4859             --  inlineable either.
4860
4861             elsif Is_Generic_Instance (Subp)
4862               or else Nkind (Parent (Parent (Subp))) = N_Subprogram_Declaration
4863             then
4864                null;
4865
4866             elsif not Comes_From_Source (Subp)
4867               and then Scope (Subp) /= Standard_Standard
4868             then
4869                Applies := True;
4870                return;
4871             end if;
4872
4873             --  The referenced entity must either be the enclosing entity, or
4874             --  an entity declared within the current open scope.
4875
4876             if Present (Scope (Subp))
4877               and then Scope (Subp) /= Current_Scope
4878               and then Subp /= Current_Scope
4879             then
4880                Error_Pragma_Arg
4881                  ("argument of% must be entity in current scope", Assoc);
4882                return;
4883             end if;
4884
4885             --  Processing for procedure, operator or function. If subprogram
4886             --  is aliased (as for an instance) indicate that the renamed
4887             --  entity (if declared in the same unit) is inlined.
4888
4889             if Is_Subprogram (Subp) then
4890                Inner_Subp := Ultimate_Alias (Inner_Subp);
4891
4892                if In_Same_Source_Unit (Subp, Inner_Subp) then
4893                   Set_Inline_Flags (Inner_Subp);
4894
4895                   Decl := Parent (Parent (Inner_Subp));
4896
4897                   if Nkind (Decl) = N_Subprogram_Declaration
4898                     and then Present (Corresponding_Body (Decl))
4899                   then
4900                      Set_Inline_Flags (Corresponding_Body (Decl));
4901
4902                   elsif Is_Generic_Instance (Subp) then
4903
4904                      --  Indicate that the body needs to be created for
4905                      --  inlining subsequent calls. The instantiation node
4906                      --  follows the declaration of the wrapper package
4907                      --  created for it.
4908
4909                      if Scope (Subp) /= Standard_Standard
4910                        and then
4911                          Need_Subprogram_Instance_Body
4912                           (Next (Unit_Declaration_Node (Scope (Alias (Subp)))),
4913                               Subp)
4914                      then
4915                         null;
4916                      end if;
4917
4918                   --  Inline is a program unit pragma (RM 10.1.5) and cannot
4919                   --  appear in a formal part to apply to a formal subprogram.
4920                   --  Do not apply check within an instance or a formal package
4921                   --  the test will have been applied to the original generic.
4922
4923                   elsif Nkind (Decl) in N_Formal_Subprogram_Declaration
4924                     and then List_Containing (Decl) = List_Containing (N)
4925                     and then not In_Instance
4926                   then
4927                      Error_Msg_N
4928                        ("Inline cannot apply to a formal subprogram", N);
4929                   end if;
4930                end if;
4931
4932                Applies := True;
4933
4934             --  For a generic subprogram set flag as well, for use at the point
4935             --  of instantiation, to determine whether the body should be
4936             --  generated.
4937
4938             elsif Is_Generic_Subprogram (Subp) then
4939                Set_Inline_Flags (Subp);
4940                Applies := True;
4941
4942             --  Literals are by definition inlined
4943
4944             elsif Kind = E_Enumeration_Literal then
4945                null;
4946
4947             --  Anything else is an error
4948
4949             else
4950                Error_Pragma_Arg
4951                  ("expect subprogram name for pragma%", Assoc);
4952             end if;
4953          end Make_Inline;
4954
4955          ----------------------
4956          -- Set_Inline_Flags --
4957          ----------------------
4958
4959          procedure Set_Inline_Flags (Subp : Entity_Id) is
4960          begin
4961             if Active then
4962                Set_Is_Inlined (Subp);
4963             end if;
4964
4965             if not Has_Pragma_Inline (Subp) then
4966                Set_Has_Pragma_Inline (Subp);
4967                Effective := True;
4968             end if;
4969
4970             if Prag_Id = Pragma_Inline_Always then
4971                Set_Has_Pragma_Inline_Always (Subp);
4972             end if;
4973          end Set_Inline_Flags;
4974
4975       --  Start of processing for Process_Inline
4976
4977       begin
4978          Check_No_Identifiers;
4979          Check_At_Least_N_Arguments (1);
4980
4981          if Active then
4982             Inline_Processing_Required := True;
4983          end if;
4984
4985          Assoc := Arg1;
4986          while Present (Assoc) loop
4987             Subp_Id := Get_Pragma_Arg (Assoc);
4988             Analyze (Subp_Id);
4989             Applies := False;
4990
4991             if Is_Entity_Name (Subp_Id) then
4992                Subp := Entity (Subp_Id);
4993
4994                if Subp = Any_Id then
4995
4996                   --  If previous error, avoid cascaded errors
4997
4998                   Applies := True;
4999                   Effective := True;
5000
5001                else
5002                   Make_Inline (Subp);
5003
5004                   --  For the pragma case, climb homonym chain. This is
5005                   --  what implements allowing the pragma in the renaming
5006                   --  case, with the result applying to the ancestors, and
5007                   --  also allows Inline to apply to all previous homonyms.
5008
5009                   if not From_Aspect_Specification (N) then
5010                      while Present (Homonym (Subp))
5011                        and then Scope (Homonym (Subp)) = Current_Scope
5012                      loop
5013                         Make_Inline (Homonym (Subp));
5014                         Subp := Homonym (Subp);
5015                      end loop;
5016                   end if;
5017                end if;
5018             end if;
5019
5020             if not Applies then
5021                Error_Pragma_Arg
5022                  ("inappropriate argument for pragma%", Assoc);
5023
5024             elsif not Effective
5025               and then Warn_On_Redundant_Constructs
5026               and then not Suppress_All_Inlining
5027             then
5028                if Inlining_Not_Possible (Subp) then
5029                   Error_Msg_NE
5030                     ("pragma Inline for& is ignored?", N, Entity (Subp_Id));
5031                else
5032                   Error_Msg_NE
5033                     ("pragma Inline for& is redundant?", N, Entity (Subp_Id));
5034                end if;
5035             end if;
5036
5037             Next (Assoc);
5038          end loop;
5039       end Process_Inline;
5040
5041       ----------------------------
5042       -- Process_Interface_Name --
5043       ----------------------------
5044
5045       procedure Process_Interface_Name
5046         (Subprogram_Def : Entity_Id;
5047          Ext_Arg        : Node_Id;
5048          Link_Arg       : Node_Id)
5049       is
5050          Ext_Nam    : Node_Id;
5051          Link_Nam   : Node_Id;
5052          String_Val : String_Id;
5053
5054          procedure Check_Form_Of_Interface_Name
5055            (SN            : Node_Id;
5056             Ext_Name_Case : Boolean);
5057          --  SN is a string literal node for an interface name. This routine
5058          --  performs some minimal checks that the name is reasonable. In
5059          --  particular that no spaces or other obviously incorrect characters
5060          --  appear. This is only a warning, since any characters are allowed.
5061          --  Ext_Name_Case is True for an External_Name, False for a Link_Name.
5062
5063          ----------------------------------
5064          -- Check_Form_Of_Interface_Name --
5065          ----------------------------------
5066
5067          procedure Check_Form_Of_Interface_Name
5068            (SN            : Node_Id;
5069             Ext_Name_Case : Boolean)
5070          is
5071             S  : constant String_Id := Strval (Expr_Value_S (SN));
5072             SL : constant Nat       := String_Length (S);
5073             C  : Char_Code;
5074
5075          begin
5076             if SL = 0 then
5077                Error_Msg_N ("interface name cannot be null string", SN);
5078             end if;
5079
5080             for J in 1 .. SL loop
5081                C := Get_String_Char (S, J);
5082
5083                --  Look for dubious character and issue unconditional warning.
5084                --  Definitely dubious if not in character range.
5085
5086                if not In_Character_Range (C)
5087
5088                   --  For all cases except CLI target,
5089                   --  commas, spaces and slashes are dubious (in CLI, we use
5090                   --  commas and backslashes in external names to specify
5091                   --  assembly version and public key, while slashes and spaces
5092                   --  can be used in names to mark nested classes and
5093                   --  valuetypes).
5094
5095                   or else ((not Ext_Name_Case or else VM_Target /= CLI_Target)
5096                              and then (Get_Character (C) = ','
5097                                          or else
5098                                        Get_Character (C) = '\'))
5099                  or else (VM_Target /= CLI_Target
5100                             and then (Get_Character (C) = ' '
5101                                         or else
5102                                       Get_Character (C) = '/'))
5103                then
5104                   Error_Msg
5105                     ("?interface name contains illegal character",
5106                      Sloc (SN) + Source_Ptr (J));
5107                end if;
5108             end loop;
5109          end Check_Form_Of_Interface_Name;
5110
5111       --  Start of processing for Process_Interface_Name
5112
5113       begin
5114          if No (Link_Arg) then
5115             if No (Ext_Arg) then
5116                if VM_Target = CLI_Target
5117                  and then Ekind (Subprogram_Def) = E_Package
5118                  and then Nkind (Parent (Subprogram_Def)) =
5119                                                  N_Package_Specification
5120                  and then Present (Generic_Parent (Parent (Subprogram_Def)))
5121                then
5122                   Set_Interface_Name
5123                      (Subprogram_Def,
5124                       Interface_Name
5125                         (Generic_Parent (Parent (Subprogram_Def))));
5126                end if;
5127
5128                return;
5129
5130             elsif Chars (Ext_Arg) = Name_Link_Name then
5131                Ext_Nam  := Empty;
5132                Link_Nam := Expression (Ext_Arg);
5133
5134             else
5135                Check_Optional_Identifier (Ext_Arg, Name_External_Name);
5136                Ext_Nam  := Expression (Ext_Arg);
5137                Link_Nam := Empty;
5138             end if;
5139
5140          else
5141             Check_Optional_Identifier (Ext_Arg,  Name_External_Name);
5142             Check_Optional_Identifier (Link_Arg, Name_Link_Name);
5143             Ext_Nam  := Expression (Ext_Arg);
5144             Link_Nam := Expression (Link_Arg);
5145          end if;
5146
5147          --  Check expressions for external name and link name are static
5148
5149          if Present (Ext_Nam) then
5150             Check_Arg_Is_Static_Expression (Ext_Nam, Standard_String);
5151             Check_Form_Of_Interface_Name (Ext_Nam, Ext_Name_Case => True);
5152
5153             --  Verify that external name is not the name of a local entity,
5154             --  which would hide the imported one and could lead to run-time
5155             --  surprises. The problem can only arise for entities declared in
5156             --  a package body (otherwise the external name is fully qualified
5157             --  and will not conflict).
5158
5159             declare
5160                Nam : Name_Id;
5161                E   : Entity_Id;
5162                Par : Node_Id;
5163
5164             begin
5165                if Prag_Id = Pragma_Import then
5166                   String_To_Name_Buffer (Strval (Expr_Value_S (Ext_Nam)));
5167                   Nam := Name_Find;
5168                   E   := Entity_Id (Get_Name_Table_Info (Nam));
5169
5170                   if Nam /= Chars (Subprogram_Def)
5171                     and then Present (E)
5172                     and then not Is_Overloadable (E)
5173                     and then Is_Immediately_Visible (E)
5174                     and then not Is_Imported (E)
5175                     and then Ekind (Scope (E)) = E_Package
5176                   then
5177                      Par := Parent (E);
5178                      while Present (Par) loop
5179                         if Nkind (Par) = N_Package_Body then
5180                            Error_Msg_Sloc := Sloc (E);
5181                            Error_Msg_NE
5182                              ("imported entity is hidden by & declared#",
5183                               Ext_Arg, E);
5184                            exit;
5185                         end if;
5186
5187                         Par := Parent (Par);
5188                      end loop;
5189                   end if;
5190                end if;
5191             end;
5192          end if;
5193
5194          if Present (Link_Nam) then
5195             Check_Arg_Is_Static_Expression (Link_Nam, Standard_String);
5196             Check_Form_Of_Interface_Name (Link_Nam, Ext_Name_Case => False);
5197          end if;
5198
5199          --  If there is no link name, just set the external name
5200
5201          if No (Link_Nam) then
5202             Link_Nam := Adjust_External_Name_Case (Expr_Value_S (Ext_Nam));
5203
5204          --  For the Link_Name case, the given literal is preceded by an
5205          --  asterisk, which indicates to GCC that the given name should be
5206          --  taken literally, and in particular that no prepending of
5207          --  underlines should occur, even in systems where this is the
5208          --  normal default.
5209
5210          else
5211             Start_String;
5212
5213             if VM_Target = No_VM then
5214                Store_String_Char (Get_Char_Code ('*'));
5215             end if;
5216
5217             String_Val := Strval (Expr_Value_S (Link_Nam));
5218             Store_String_Chars (String_Val);
5219             Link_Nam :=
5220               Make_String_Literal (Sloc (Link_Nam),
5221                 Strval => End_String);
5222          end if;
5223
5224          --  Set the interface name. If the entity is a generic instance, use
5225          --  its alias, which is the callable entity.
5226
5227          if Is_Generic_Instance (Subprogram_Def) then
5228             Set_Encoded_Interface_Name
5229               (Alias (Get_Base_Subprogram (Subprogram_Def)), Link_Nam);
5230          else
5231             Set_Encoded_Interface_Name
5232               (Get_Base_Subprogram (Subprogram_Def), Link_Nam);
5233          end if;
5234
5235          --  We allow duplicated export names in CIL/Java, as they are always
5236          --  enclosed in a namespace that differentiates them, and overloaded
5237          --  entities are supported by the VM.
5238
5239          if Convention (Subprogram_Def) /= Convention_CIL
5240               and then
5241             Convention (Subprogram_Def) /= Convention_Java
5242          then
5243             Check_Duplicated_Export_Name (Link_Nam);
5244          end if;
5245       end Process_Interface_Name;
5246
5247       -----------------------------------------
5248       -- Process_Interrupt_Or_Attach_Handler --
5249       -----------------------------------------
5250
5251       procedure Process_Interrupt_Or_Attach_Handler is
5252          Arg1_X       : constant Node_Id   := Get_Pragma_Arg (Arg1);
5253          Handler_Proc : constant Entity_Id := Entity (Arg1_X);
5254          Proc_Scope   : constant Entity_Id := Scope (Handler_Proc);
5255
5256       begin
5257          Set_Is_Interrupt_Handler (Handler_Proc);
5258
5259          --  If the pragma is not associated with a handler procedure within a
5260          --  protected type, then it must be for a nonprotected procedure for
5261          --  the AAMP target, in which case we don't associate a representation
5262          --  item with the procedure's scope.
5263
5264          if Ekind (Proc_Scope) = E_Protected_Type then
5265             if Prag_Id = Pragma_Interrupt_Handler
5266                  or else
5267                Prag_Id = Pragma_Attach_Handler
5268             then
5269                Record_Rep_Item (Proc_Scope, N);
5270             end if;
5271          end if;
5272       end Process_Interrupt_Or_Attach_Handler;
5273
5274       --------------------------------------------------
5275       -- Process_Restrictions_Or_Restriction_Warnings --
5276       --------------------------------------------------
5277
5278       --  Note: some of the simple identifier cases were handled in par-prag,
5279       --  but it is harmless (and more straightforward) to simply handle all
5280       --  cases here, even if it means we repeat a bit of work in some cases.
5281
5282       procedure Process_Restrictions_Or_Restriction_Warnings
5283         (Warn : Boolean)
5284       is
5285          Arg   : Node_Id;
5286          R_Id  : Restriction_Id;
5287          Id    : Name_Id;
5288          Expr  : Node_Id;
5289          Val   : Uint;
5290
5291          procedure Check_Unit_Name (N : Node_Id);
5292          --  Checks unit name parameter for No_Dependence. Returns if it has
5293          --  an appropriate form, otherwise raises pragma argument error.
5294
5295          ---------------------
5296          -- Check_Unit_Name --
5297          ---------------------
5298
5299          procedure Check_Unit_Name (N : Node_Id) is
5300          begin
5301             if Nkind (N) = N_Selected_Component then
5302                Check_Unit_Name (Prefix (N));
5303                Check_Unit_Name (Selector_Name (N));
5304
5305             elsif Nkind (N) = N_Identifier then
5306                return;
5307
5308             else
5309                Error_Pragma_Arg
5310                  ("wrong form for unit name for No_Dependence", N);
5311             end if;
5312          end Check_Unit_Name;
5313
5314       --  Start of processing for Process_Restrictions_Or_Restriction_Warnings
5315
5316       begin
5317          --  Ignore all Restrictions pragma in CodePeer mode
5318
5319          if CodePeer_Mode then
5320             return;
5321          end if;
5322
5323          Check_Ada_83_Warning;
5324          Check_At_Least_N_Arguments (1);
5325          Check_Valid_Configuration_Pragma;
5326
5327          Arg := Arg1;
5328          while Present (Arg) loop
5329             Id := Chars (Arg);
5330             Expr := Get_Pragma_Arg (Arg);
5331
5332             --  Case of no restriction identifier present
5333
5334             if Id = No_Name then
5335                if Nkind (Expr) /= N_Identifier then
5336                   Error_Pragma_Arg
5337                     ("invalid form for restriction", Arg);
5338                end if;
5339
5340                R_Id :=
5341                  Get_Restriction_Id
5342                    (Process_Restriction_Synonyms (Expr));
5343
5344                if R_Id not in All_Boolean_Restrictions then
5345                   Error_Msg_Name_1 := Pname;
5346                   Error_Msg_N
5347                     ("invalid restriction identifier&", Get_Pragma_Arg (Arg));
5348
5349                   --  Check for possible misspelling
5350
5351                   for J in Restriction_Id loop
5352                      declare
5353                         Rnm : constant String := Restriction_Id'Image (J);
5354
5355                      begin
5356                         Name_Buffer (1 .. Rnm'Length) := Rnm;
5357                         Name_Len := Rnm'Length;
5358                         Set_Casing (All_Lower_Case);
5359
5360                         if Is_Bad_Spelling_Of (Chars (Expr), Name_Enter) then
5361                            Set_Casing
5362                              (Identifier_Casing (Current_Source_File));
5363                            Error_Msg_String (1 .. Rnm'Length) :=
5364                              Name_Buffer (1 .. Name_Len);
5365                            Error_Msg_Strlen := Rnm'Length;
5366                            Error_Msg_N -- CODEFIX
5367                              ("\possible misspelling of ""~""",
5368                               Get_Pragma_Arg (Arg));
5369                            exit;
5370                         end if;
5371                      end;
5372                   end loop;
5373
5374                   raise Pragma_Exit;
5375                end if;
5376
5377                if Implementation_Restriction (R_Id) then
5378                   Check_Restriction (No_Implementation_Restrictions, Arg);
5379                end if;
5380
5381                --  Special processing for No_Elaboration_Code restriction
5382
5383                if R_Id = No_Elaboration_Code then
5384
5385                   --  Restriction is only recognized within a configuration
5386                   --  pragma file, or within a unit of the main extended
5387                   --  program. Note: the test for Main_Unit is needed to
5388                   --  properly include the case of configuration pragma files.
5389
5390                   if not (Current_Sem_Unit = Main_Unit
5391                            or else In_Extended_Main_Source_Unit (N))
5392                   then
5393                      return;
5394
5395                   --  Don't allow in a subunit unless already specified in
5396                   --  body or spec.
5397
5398                   elsif Nkind (Parent (N)) = N_Compilation_Unit
5399                     and then Nkind (Unit (Parent (N))) = N_Subunit
5400                     and then not Restriction_Active (No_Elaboration_Code)
5401                   then
5402                      Error_Msg_N
5403                        ("invalid specification of ""No_Elaboration_Code""",
5404                         N);
5405                      Error_Msg_N
5406                        ("\restriction cannot be specified in a subunit", N);
5407                      Error_Msg_N
5408                        ("\unless also specified in body or spec", N);
5409                      return;
5410
5411                   --  If we have a No_Elaboration_Code pragma that we
5412                   --  accept, then it needs to be added to the configuration
5413                   --  restrcition set so that we get proper application to
5414                   --  other units in the main extended source as required.
5415
5416                   else
5417                      Add_To_Config_Boolean_Restrictions (No_Elaboration_Code);
5418                   end if;
5419                end if;
5420
5421                --  If this is a warning, then set the warning unless we already
5422                --  have a real restriction active (we never want a warning to
5423                --  override a real restriction).
5424
5425                if Warn then
5426                   if not Restriction_Active (R_Id) then
5427                      Set_Restriction (R_Id, N);
5428                      Restriction_Warnings (R_Id) := True;
5429                   end if;
5430
5431                --  If real restriction case, then set it and make sure that the
5432                --  restriction warning flag is off, since a real restriction
5433                --  always overrides a warning.
5434
5435                else
5436                   Set_Restriction (R_Id, N);
5437                   Restriction_Warnings (R_Id) := False;
5438                end if;
5439
5440                --  Check for obsolescent restrictions in Ada 2005 mode
5441
5442                if not Warn
5443                  and then Ada_Version >= Ada_2005
5444                  and then (R_Id = No_Asynchronous_Control
5445                             or else
5446                            R_Id = No_Unchecked_Deallocation
5447                             or else
5448                            R_Id = No_Unchecked_Conversion)
5449                then
5450                   Check_Restriction (No_Obsolescent_Features, N);
5451                end if;
5452
5453                --  A very special case that must be processed here: pragma
5454                --  Restrictions (No_Exceptions) turns off all run-time
5455                --  checking. This is a bit dubious in terms of the formal
5456                --  language definition, but it is what is intended by RM
5457                --  H.4(12). Restriction_Warnings never affects generated code
5458                --  so this is done only in the real restriction case.
5459
5460                --  Atomic_Synchronization is not a real check, so it is not
5461                --  affected by this processing).
5462
5463                if R_Id = No_Exceptions and then not Warn then
5464                   for J in Scope_Suppress'Range loop
5465                      if J /= Atomic_Synchronization then
5466                         Scope_Suppress (J) := True;
5467                      end if;
5468                   end loop;
5469                end if;
5470
5471             --  Case of No_Dependence => unit-name. Note that the parser
5472             --  already made the necessary entry in the No_Dependence table.
5473
5474             elsif Id = Name_No_Dependence then
5475                Check_Unit_Name (Expr);
5476
5477             --  Case of No_Specification_Of_Aspect => Identifier.
5478
5479             elsif Id = Name_No_Specification_Of_Aspect then
5480                declare
5481                   A_Id : Aspect_Id;
5482
5483                begin
5484                   if Nkind (Expr) /= N_Identifier then
5485                      A_Id := No_Aspect;
5486                   else
5487                      A_Id := Get_Aspect_Id (Chars (Expr));
5488                   end if;
5489
5490                   if A_Id = No_Aspect then
5491                      Error_Pragma_Arg ("invalid restriction name", Arg);
5492                   else
5493                      Set_Restriction_No_Specification_Of_Aspect (Expr, Warn);
5494                   end if;
5495                end;
5496
5497             --  All other cases of restriction identifier present
5498
5499             else
5500                R_Id := Get_Restriction_Id (Process_Restriction_Synonyms (Arg));
5501                Analyze_And_Resolve (Expr, Any_Integer);
5502
5503                if R_Id not in All_Parameter_Restrictions then
5504                   Error_Pragma_Arg
5505                     ("invalid restriction parameter identifier", Arg);
5506
5507                elsif not Is_OK_Static_Expression (Expr) then
5508                   Flag_Non_Static_Expr
5509                     ("value must be static expression!", Expr);
5510                   raise Pragma_Exit;
5511
5512                elsif not Is_Integer_Type (Etype (Expr))
5513                  or else Expr_Value (Expr) < 0
5514                then
5515                   Error_Pragma_Arg
5516                     ("value must be non-negative integer", Arg);
5517                end if;
5518
5519                --  Restriction pragma is active
5520
5521                Val := Expr_Value (Expr);
5522
5523                if not UI_Is_In_Int_Range (Val) then
5524                   Error_Pragma_Arg
5525                     ("pragma ignored, value too large?", Arg);
5526                end if;
5527
5528                --  Warning case. If the real restriction is active, then we
5529                --  ignore the request, since warning never overrides a real
5530                --  restriction. Otherwise we set the proper warning. Note that
5531                --  this circuit sets the warning again if it is already set,
5532                --  which is what we want, since the constant may have changed.
5533
5534                if Warn then
5535                   if not Restriction_Active (R_Id) then
5536                      Set_Restriction
5537                        (R_Id, N, Integer (UI_To_Int (Val)));
5538                      Restriction_Warnings (R_Id) := True;
5539                   end if;
5540
5541                --  Real restriction case, set restriction and make sure warning
5542                --  flag is off since real restriction always overrides warning.
5543
5544                else
5545                   Set_Restriction (R_Id, N, Integer (UI_To_Int (Val)));
5546                   Restriction_Warnings (R_Id) := False;
5547                end if;
5548             end if;
5549
5550             Next (Arg);
5551          end loop;
5552       end Process_Restrictions_Or_Restriction_Warnings;
5553
5554       ---------------------------------
5555       -- Process_Suppress_Unsuppress --
5556       ---------------------------------
5557
5558       --  Note: this procedure makes entries in the check suppress data
5559       --  structures managed by Sem. See spec of package Sem for full
5560       --  details on how we handle recording of check suppression.
5561
5562       procedure Process_Suppress_Unsuppress (Suppress_Case : Boolean) is
5563          C    : Check_Id;
5564          E_Id : Node_Id;
5565          E    : Entity_Id;
5566
5567          In_Package_Spec : constant Boolean :=
5568                              Is_Package_Or_Generic_Package (Current_Scope)
5569                                and then not In_Package_Body (Current_Scope);
5570
5571          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id);
5572          --  Used to suppress a single check on the given entity
5573
5574          --------------------------------
5575          -- Suppress_Unsuppress_Echeck --
5576          --------------------------------
5577
5578          procedure Suppress_Unsuppress_Echeck (E : Entity_Id; C : Check_Id) is
5579          begin
5580             --  Check for error of trying to set atomic synchronization for
5581             --  a non-atomic variable.
5582
5583             if C = Atomic_Synchronization
5584               and then not (Is_Atomic (E) or else Has_Atomic_Components (E))
5585             then
5586                Error_Msg_N
5587                  ("pragma & requires atomic type or variable",
5588                   Pragma_Identifier (Original_Node (N)));
5589             end if;
5590
5591             Set_Checks_May_Be_Suppressed (E);
5592
5593             if In_Package_Spec then
5594                Push_Global_Suppress_Stack_Entry
5595                  (Entity   => E,
5596                   Check    => C,
5597                   Suppress => Suppress_Case);
5598             else
5599                Push_Local_Suppress_Stack_Entry
5600                  (Entity   => E,
5601                   Check    => C,
5602                   Suppress => Suppress_Case);
5603             end if;
5604
5605             --  If this is a first subtype, and the base type is distinct,
5606             --  then also set the suppress flags on the base type.
5607
5608             if Is_First_Subtype (E)
5609               and then Etype (E) /= E
5610             then
5611                Suppress_Unsuppress_Echeck (Etype (E), C);
5612             end if;
5613          end Suppress_Unsuppress_Echeck;
5614
5615       --  Start of processing for Process_Suppress_Unsuppress
5616
5617       begin
5618          --  Ignore pragma Suppress/Unsuppress in CodePeer and Alfa modes on
5619          --  user code: we want to generate checks for analysis purposes, as
5620          --  set respectively by -gnatC and -gnatd.F
5621
5622          if (CodePeer_Mode or Alfa_Mode)
5623            and then Comes_From_Source (N)
5624          then
5625             return;
5626          end if;
5627
5628          --  Suppress/Unsuppress can appear as a configuration pragma, or in a
5629          --  declarative part or a package spec (RM 11.5(5)).
5630
5631          if not Is_Configuration_Pragma then
5632             Check_Is_In_Decl_Part_Or_Package_Spec;
5633          end if;
5634
5635          Check_At_Least_N_Arguments (1);
5636          Check_At_Most_N_Arguments (2);
5637          Check_No_Identifier (Arg1);
5638          Check_Arg_Is_Identifier (Arg1);
5639
5640          C := Get_Check_Id (Chars (Get_Pragma_Arg (Arg1)));
5641
5642          if C = No_Check_Id then
5643             Error_Pragma_Arg
5644               ("argument of pragma% is not valid check name", Arg1);
5645          end if;
5646
5647          if not Suppress_Case
5648            and then (C = All_Checks or else C = Overflow_Check)
5649          then
5650             Opt.Overflow_Checks_Unsuppressed := True;
5651          end if;
5652
5653          if Arg_Count = 1 then
5654
5655             --  Make an entry in the local scope suppress table. This is the
5656             --  table that directly shows the current value of the scope
5657             --  suppress check for any check id value.
5658
5659             if C = All_Checks then
5660
5661                --  For All_Checks, we set all specific predefined checks with
5662                --  the exception of Elaboration_Check, which is handled
5663                --  specially because of not wanting All_Checks to have the
5664                --  effect of deactivating static elaboration order processing.
5665                --  Atomic_Synchronization is also not affected, since this is
5666                --  not a real check.
5667
5668                for J in Scope_Suppress'Range loop
5669                   if J /= Elaboration_Check
5670                     and then J /= Atomic_Synchronization
5671                   then
5672                      Scope_Suppress (J) := Suppress_Case;
5673                   end if;
5674                end loop;
5675
5676             --  If not All_Checks, and predefined check, then set appropriate
5677             --  scope entry. Note that we will set Elaboration_Check if this
5678             --  is explicitly specified. Atomic_Synchronization is allowed
5679             --  only if internally generated and entity is atomic.
5680
5681             elsif C in Predefined_Check_Id
5682               and then (not Comes_From_Source (N)
5683                          or else C /= Atomic_Synchronization)
5684             then
5685                Scope_Suppress (C) := Suppress_Case;
5686             end if;
5687
5688             --  Also make an entry in the Local_Entity_Suppress table
5689
5690             Push_Local_Suppress_Stack_Entry
5691               (Entity   => Empty,
5692                Check    => C,
5693                Suppress => Suppress_Case);
5694
5695          --  Case of two arguments present, where the check is suppressed for
5696          --  a specified entity (given as the second argument of the pragma)
5697
5698          else
5699             --  This is obsolescent in Ada 2005 mode
5700
5701             if Ada_Version >= Ada_2005 then
5702                Check_Restriction (No_Obsolescent_Features, Arg2);
5703             end if;
5704
5705             Check_Optional_Identifier (Arg2, Name_On);
5706             E_Id := Get_Pragma_Arg (Arg2);
5707             Analyze (E_Id);
5708
5709             if not Is_Entity_Name (E_Id) then
5710                Error_Pragma_Arg
5711                  ("second argument of pragma% must be entity name", Arg2);
5712             end if;
5713
5714             E := Entity (E_Id);
5715
5716             if E = Any_Id then
5717                return;
5718             end if;
5719
5720             --  Enforce RM 11.5(7) which requires that for a pragma that
5721             --  appears within a package spec, the named entity must be
5722             --  within the package spec. We allow the package name itself
5723             --  to be mentioned since that makes sense, although it is not
5724             --  strictly allowed by 11.5(7).
5725
5726             if In_Package_Spec
5727               and then E /= Current_Scope
5728               and then Scope (E) /= Current_Scope
5729             then
5730                Error_Pragma_Arg
5731                  ("entity in pragma% is not in package spec (RM 11.5(7))",
5732                   Arg2);
5733             end if;
5734
5735             --  Loop through homonyms. As noted below, in the case of a package
5736             --  spec, only homonyms within the package spec are considered.
5737
5738             loop
5739                Suppress_Unsuppress_Echeck (E, C);
5740
5741                if Is_Generic_Instance (E)
5742                  and then Is_Subprogram (E)
5743                  and then Present (Alias (E))
5744                then
5745                   Suppress_Unsuppress_Echeck (Alias (E), C);
5746                end if;
5747
5748                --  Move to next homonym if not aspect spec case
5749
5750                exit when From_Aspect_Specification (N);
5751                E := Homonym (E);
5752                exit when No (E);
5753
5754                --  If we are within a package specification, the pragma only
5755                --  applies to homonyms in the same scope.
5756
5757                exit when In_Package_Spec
5758                  and then Scope (E) /= Current_Scope;
5759             end loop;
5760          end if;
5761       end Process_Suppress_Unsuppress;
5762
5763       ------------------
5764       -- Set_Exported --
5765       ------------------
5766
5767       procedure Set_Exported (E : Entity_Id; Arg : Node_Id) is
5768       begin
5769          if Is_Imported (E) then
5770             Error_Pragma_Arg
5771               ("cannot export entity& that was previously imported", Arg);
5772
5773          elsif Present (Address_Clause (E)) and then not CodePeer_Mode then
5774             Error_Pragma_Arg
5775               ("cannot export entity& that has an address clause", Arg);
5776          end if;
5777
5778          Set_Is_Exported (E);
5779
5780          --  Generate a reference for entity explicitly, because the
5781          --  identifier may be overloaded and name resolution will not
5782          --  generate one.
5783
5784          Generate_Reference (E, Arg);
5785
5786          --  Deal with exporting non-library level entity
5787
5788          if not Is_Library_Level_Entity (E) then
5789
5790             --  Not allowed at all for subprograms
5791
5792             if Is_Subprogram (E) then
5793                Error_Pragma_Arg ("local subprogram& cannot be exported", Arg);
5794
5795             --  Otherwise set public and statically allocated
5796
5797             else
5798                Set_Is_Public (E);
5799                Set_Is_Statically_Allocated (E);
5800
5801                --  Warn if the corresponding W flag is set and the pragma comes
5802                --  from source. The latter may not be true e.g. on VMS where we
5803                --  expand export pragmas for exception codes associated with
5804                --  imported or exported exceptions. We do not want to generate
5805                --  a warning for something that the user did not write.
5806
5807                if Warn_On_Export_Import
5808                  and then Comes_From_Source (Arg)
5809                then
5810                   Error_Msg_NE
5811                     ("?& has been made static as a result of Export", Arg, E);
5812                   Error_Msg_N
5813                     ("\this usage is non-standard and non-portable", Arg);
5814                end if;
5815             end if;
5816          end if;
5817
5818          if Warn_On_Export_Import and then Is_Type (E) then
5819             Error_Msg_NE ("exporting a type has no effect?", Arg, E);
5820          end if;
5821
5822          if Warn_On_Export_Import and Inside_A_Generic then
5823             Error_Msg_NE
5824               ("all instances of& will have the same external name?", Arg, E);
5825          end if;
5826       end Set_Exported;
5827
5828       ----------------------------------------------
5829       -- Set_Extended_Import_Export_External_Name --
5830       ----------------------------------------------
5831
5832       procedure Set_Extended_Import_Export_External_Name
5833         (Internal_Ent : Entity_Id;
5834          Arg_External : Node_Id)
5835       is
5836          Old_Name : constant Node_Id := Interface_Name (Internal_Ent);
5837          New_Name : Node_Id;
5838
5839       begin
5840          if No (Arg_External) then
5841             return;
5842          end if;
5843
5844          Check_Arg_Is_External_Name (Arg_External);
5845
5846          if Nkind (Arg_External) = N_String_Literal then
5847             if String_Length (Strval (Arg_External)) = 0 then
5848                return;
5849             else
5850                New_Name := Adjust_External_Name_Case (Arg_External);
5851             end if;
5852
5853          elsif Nkind (Arg_External) = N_Identifier then
5854             New_Name := Get_Default_External_Name (Arg_External);
5855
5856          --  Check_Arg_Is_External_Name should let through only identifiers and
5857          --  string literals or static string expressions (which are folded to
5858          --  string literals).
5859
5860          else
5861             raise Program_Error;
5862          end if;
5863
5864          --  If we already have an external name set (by a prior normal Import
5865          --  or Export pragma), then the external names must match
5866
5867          if Present (Interface_Name (Internal_Ent)) then
5868             Check_Matching_Internal_Names : declare
5869                S1 : constant String_Id := Strval (Old_Name);
5870                S2 : constant String_Id := Strval (New_Name);
5871
5872                procedure Mismatch;
5873                --  Called if names do not match
5874
5875                --------------
5876                -- Mismatch --
5877                --------------
5878
5879                procedure Mismatch is
5880                begin
5881                   Error_Msg_Sloc := Sloc (Old_Name);
5882                   Error_Pragma_Arg
5883                     ("external name does not match that given #",
5884                      Arg_External);
5885                end Mismatch;
5886
5887             --  Start of processing for Check_Matching_Internal_Names
5888
5889             begin
5890                if String_Length (S1) /= String_Length (S2) then
5891                   Mismatch;
5892
5893                else
5894                   for J in 1 .. String_Length (S1) loop
5895                      if Get_String_Char (S1, J) /= Get_String_Char (S2, J) then
5896                         Mismatch;
5897                      end if;
5898                   end loop;
5899                end if;
5900             end Check_Matching_Internal_Names;
5901
5902          --  Otherwise set the given name
5903
5904          else
5905             Set_Encoded_Interface_Name (Internal_Ent, New_Name);
5906             Check_Duplicated_Export_Name (New_Name);
5907          end if;
5908       end Set_Extended_Import_Export_External_Name;
5909
5910       ------------------
5911       -- Set_Imported --
5912       ------------------
5913
5914       procedure Set_Imported (E : Entity_Id) is
5915       begin
5916          --  Error message if already imported or exported
5917
5918          if Is_Exported (E) or else Is_Imported (E) then
5919
5920             --  Error if being set Exported twice
5921
5922             if Is_Exported (E) then
5923                Error_Msg_NE ("entity& was previously exported", N, E);
5924
5925             --  OK if Import/Interface case
5926
5927             elsif Import_Interface_Present (N) then
5928                goto OK;
5929
5930             --  Error if being set Imported twice
5931
5932             else
5933                Error_Msg_NE ("entity& was previously imported", N, E);
5934             end if;
5935
5936             Error_Msg_Name_1 := Pname;
5937             Error_Msg_N
5938               ("\(pragma% applies to all previous entities)", N);
5939
5940             Error_Msg_Sloc  := Sloc (E);
5941             Error_Msg_NE ("\import not allowed for& declared#", N, E);
5942
5943          --  Here if not previously imported or exported, OK to import
5944
5945          else
5946             Set_Is_Imported (E);
5947
5948             --  If the entity is an object that is not at the library level,
5949             --  then it is statically allocated. We do not worry about objects
5950             --  with address clauses in this context since they are not really
5951             --  imported in the linker sense.
5952
5953             if Is_Object (E)
5954               and then not Is_Library_Level_Entity (E)
5955               and then No (Address_Clause (E))
5956             then
5957                Set_Is_Statically_Allocated (E);
5958             end if;
5959          end if;
5960
5961          <<OK>> null;
5962       end Set_Imported;
5963
5964       -------------------------
5965       -- Set_Mechanism_Value --
5966       -------------------------
5967
5968       --  Note: the mechanism name has not been analyzed (and cannot indeed be
5969       --  analyzed, since it is semantic nonsense), so we get it in the exact
5970       --  form created by the parser.
5971
5972       procedure Set_Mechanism_Value (Ent : Entity_Id; Mech_Name : Node_Id) is
5973          Class        : Node_Id;
5974          Param        : Node_Id;
5975          Mech_Name_Id : Name_Id;
5976
5977          procedure Bad_Class;
5978          --  Signal bad descriptor class name
5979
5980          procedure Bad_Mechanism;
5981          --  Signal bad mechanism name
5982
5983          ---------------
5984          -- Bad_Class --
5985          ---------------
5986
5987          procedure Bad_Class is
5988          begin
5989             Error_Pragma_Arg ("unrecognized descriptor class name", Class);
5990          end Bad_Class;
5991
5992          -------------------------
5993          -- Bad_Mechanism_Value --
5994          -------------------------
5995
5996          procedure Bad_Mechanism is
5997          begin
5998             Error_Pragma_Arg ("unrecognized mechanism name", Mech_Name);
5999          end Bad_Mechanism;
6000
6001       --  Start of processing for Set_Mechanism_Value
6002
6003       begin
6004          if Mechanism (Ent) /= Default_Mechanism then
6005             Error_Msg_NE
6006               ("mechanism for & has already been set", Mech_Name, Ent);
6007          end if;
6008
6009          --  MECHANISM_NAME ::= value | reference | descriptor |
6010          --                     short_descriptor
6011
6012          if Nkind (Mech_Name) = N_Identifier then
6013             if Chars (Mech_Name) = Name_Value then
6014                Set_Mechanism (Ent, By_Copy);
6015                return;
6016
6017             elsif Chars (Mech_Name) = Name_Reference then
6018                Set_Mechanism (Ent, By_Reference);
6019                return;
6020
6021             elsif Chars (Mech_Name) = Name_Descriptor then
6022                Check_VMS (Mech_Name);
6023
6024                --  Descriptor => Short_Descriptor if pragma was given
6025
6026                if Short_Descriptors then
6027                   Set_Mechanism (Ent, By_Short_Descriptor);
6028                else
6029                   Set_Mechanism (Ent, By_Descriptor);
6030                end if;
6031
6032                return;
6033
6034             elsif Chars (Mech_Name) = Name_Short_Descriptor then
6035                Check_VMS (Mech_Name);
6036                Set_Mechanism (Ent, By_Short_Descriptor);
6037                return;
6038
6039             elsif Chars (Mech_Name) = Name_Copy then
6040                Error_Pragma_Arg
6041                  ("bad mechanism name, Value assumed", Mech_Name);
6042
6043             else
6044                Bad_Mechanism;
6045             end if;
6046
6047          --  MECHANISM_NAME ::= descriptor (CLASS_NAME) |
6048          --                     short_descriptor (CLASS_NAME)
6049          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
6050
6051          --  Note: this form is parsed as an indexed component
6052
6053          elsif Nkind (Mech_Name) = N_Indexed_Component then
6054             Class := First (Expressions (Mech_Name));
6055
6056             if Nkind (Prefix (Mech_Name)) /= N_Identifier
6057              or else not (Chars (Prefix (Mech_Name)) = Name_Descriptor or else
6058                           Chars (Prefix (Mech_Name)) = Name_Short_Descriptor)
6059              or else Present (Next (Class))
6060             then
6061                Bad_Mechanism;
6062             else
6063                Mech_Name_Id := Chars (Prefix (Mech_Name));
6064
6065                --  Change Descriptor => Short_Descriptor if pragma was given
6066
6067                if Mech_Name_Id = Name_Descriptor
6068                  and then Short_Descriptors
6069                then
6070                   Mech_Name_Id := Name_Short_Descriptor;
6071                end if;
6072             end if;
6073
6074          --  MECHANISM_NAME ::= descriptor (Class => CLASS_NAME) |
6075          --                     short_descriptor (Class => CLASS_NAME)
6076          --  CLASS_NAME     ::= ubs | ubsb | uba | s | sb | a | nca
6077
6078          --  Note: this form is parsed as a function call
6079
6080          elsif Nkind (Mech_Name) = N_Function_Call then
6081             Param := First (Parameter_Associations (Mech_Name));
6082
6083             if Nkind (Name (Mech_Name)) /= N_Identifier
6084               or else not (Chars (Name (Mech_Name)) = Name_Descriptor or else
6085                            Chars (Name (Mech_Name)) = Name_Short_Descriptor)
6086               or else Present (Next (Param))
6087               or else No (Selector_Name (Param))
6088               or else Chars (Selector_Name (Param)) /= Name_Class
6089             then
6090                Bad_Mechanism;
6091             else
6092                Class := Explicit_Actual_Parameter (Param);
6093                Mech_Name_Id := Chars (Name (Mech_Name));
6094             end if;
6095
6096          else
6097             Bad_Mechanism;
6098          end if;
6099
6100          --  Fall through here with Class set to descriptor class name
6101
6102          Check_VMS (Mech_Name);
6103
6104          if Nkind (Class) /= N_Identifier then
6105             Bad_Class;
6106
6107          elsif Mech_Name_Id = Name_Descriptor
6108            and then Chars (Class) = Name_UBS
6109          then
6110             Set_Mechanism (Ent, By_Descriptor_UBS);
6111
6112          elsif Mech_Name_Id = Name_Descriptor
6113            and then Chars (Class) = Name_UBSB
6114          then
6115             Set_Mechanism (Ent, By_Descriptor_UBSB);
6116
6117          elsif Mech_Name_Id = Name_Descriptor
6118            and then Chars (Class) = Name_UBA
6119          then
6120             Set_Mechanism (Ent, By_Descriptor_UBA);
6121
6122          elsif Mech_Name_Id = Name_Descriptor
6123            and then Chars (Class) = Name_S
6124          then
6125             Set_Mechanism (Ent, By_Descriptor_S);
6126
6127          elsif Mech_Name_Id = Name_Descriptor
6128            and then Chars (Class) = Name_SB
6129          then
6130             Set_Mechanism (Ent, By_Descriptor_SB);
6131
6132          elsif Mech_Name_Id = Name_Descriptor
6133            and then Chars (Class) = Name_A
6134          then
6135             Set_Mechanism (Ent, By_Descriptor_A);
6136
6137          elsif Mech_Name_Id = Name_Descriptor
6138            and then Chars (Class) = Name_NCA
6139          then
6140             Set_Mechanism (Ent, By_Descriptor_NCA);
6141
6142          elsif Mech_Name_Id = Name_Short_Descriptor
6143            and then Chars (Class) = Name_UBS
6144          then
6145             Set_Mechanism (Ent, By_Short_Descriptor_UBS);
6146
6147          elsif Mech_Name_Id = Name_Short_Descriptor
6148            and then Chars (Class) = Name_UBSB
6149          then
6150             Set_Mechanism (Ent, By_Short_Descriptor_UBSB);
6151
6152          elsif Mech_Name_Id = Name_Short_Descriptor
6153            and then Chars (Class) = Name_UBA
6154          then
6155             Set_Mechanism (Ent, By_Short_Descriptor_UBA);
6156
6157          elsif Mech_Name_Id = Name_Short_Descriptor
6158            and then Chars (Class) = Name_S
6159          then
6160             Set_Mechanism (Ent, By_Short_Descriptor_S);
6161
6162          elsif Mech_Name_Id = Name_Short_Descriptor
6163            and then Chars (Class) = Name_SB
6164          then
6165             Set_Mechanism (Ent, By_Short_Descriptor_SB);
6166
6167          elsif Mech_Name_Id = Name_Short_Descriptor
6168            and then Chars (Class) = Name_A
6169          then
6170             Set_Mechanism (Ent, By_Short_Descriptor_A);
6171
6172          elsif Mech_Name_Id = Name_Short_Descriptor
6173            and then Chars (Class) = Name_NCA
6174          then
6175             Set_Mechanism (Ent, By_Short_Descriptor_NCA);
6176
6177          else
6178             Bad_Class;
6179          end if;
6180       end Set_Mechanism_Value;
6181
6182       ---------------------------
6183       -- Set_Ravenscar_Profile --
6184       ---------------------------
6185
6186       --  The tasks to be done here are
6187
6188       --    Set required policies
6189
6190       --      pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6191       --      pragma Locking_Policy (Ceiling_Locking)
6192
6193       --    Set Detect_Blocking mode
6194
6195       --    Set required restrictions (see System.Rident for detailed list)
6196
6197       --    Set the No_Dependence rules
6198       --      No_Dependence => Ada.Asynchronous_Task_Control
6199       --      No_Dependence => Ada.Calendar
6200       --      No_Dependence => Ada.Execution_Time.Group_Budget
6201       --      No_Dependence => Ada.Execution_Time.Timers
6202       --      No_Dependence => Ada.Task_Attributes
6203       --      No_Dependence => System.Multiprocessors.Dispatching_Domains
6204
6205       procedure Set_Ravenscar_Profile (N : Node_Id) is
6206          Prefix_Entity   : Entity_Id;
6207          Selector_Entity : Entity_Id;
6208          Prefix_Node     : Node_Id;
6209          Node            : Node_Id;
6210
6211       begin
6212          --  pragma Task_Dispatching_Policy (FIFO_Within_Priorities)
6213
6214          if Task_Dispatching_Policy /= ' '
6215            and then Task_Dispatching_Policy /= 'F'
6216          then
6217             Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
6218             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6219
6220          --  Set the FIFO_Within_Priorities policy, but always preserve
6221          --  System_Location since we like the error message with the run time
6222          --  name.
6223
6224          else
6225             Task_Dispatching_Policy := 'F';
6226
6227             if Task_Dispatching_Policy_Sloc /= System_Location then
6228                Task_Dispatching_Policy_Sloc := Loc;
6229             end if;
6230          end if;
6231
6232          --  pragma Locking_Policy (Ceiling_Locking)
6233
6234          if Locking_Policy /= ' '
6235            and then Locking_Policy /= 'C'
6236          then
6237             Error_Msg_Sloc := Locking_Policy_Sloc;
6238             Error_Pragma ("Profile (Ravenscar) incompatible with policy#");
6239
6240          --  Set the Ceiling_Locking policy, but preserve System_Location since
6241          --  we like the error message with the run time name.
6242
6243          else
6244             Locking_Policy := 'C';
6245
6246             if Locking_Policy_Sloc /= System_Location then
6247                Locking_Policy_Sloc := Loc;
6248             end if;
6249          end if;
6250
6251          --  pragma Detect_Blocking
6252
6253          Detect_Blocking := True;
6254
6255          --  Set the corresponding restrictions
6256
6257          Set_Profile_Restrictions
6258            (Ravenscar, N, Warn => Treat_Restrictions_As_Warnings);
6259
6260          --  Set the No_Dependence restrictions
6261
6262          --  The following No_Dependence restrictions:
6263          --    No_Dependence => Ada.Asynchronous_Task_Control
6264          --    No_Dependence => Ada.Calendar
6265          --    No_Dependence => Ada.Task_Attributes
6266          --  are already set by previous call to Set_Profile_Restrictions.
6267
6268          --  Set the following restrictions which were added to Ada 2005:
6269          --    No_Dependence => Ada.Execution_Time.Group_Budget
6270          --    No_Dependence => Ada.Execution_Time.Timers
6271
6272          if Ada_Version >= Ada_2005 then
6273             Name_Buffer (1 .. 3) := "ada";
6274             Name_Len := 3;
6275
6276             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6277
6278             Name_Buffer (1 .. 14) := "execution_time";
6279             Name_Len := 14;
6280
6281             Selector_Entity := Make_Identifier (Loc, Name_Find);
6282
6283             Prefix_Node :=
6284               Make_Selected_Component
6285                 (Sloc          => Loc,
6286                  Prefix        => Prefix_Entity,
6287                  Selector_Name => Selector_Entity);
6288
6289             Name_Buffer (1 .. 13) := "group_budgets";
6290             Name_Len := 13;
6291
6292             Selector_Entity := Make_Identifier (Loc, Name_Find);
6293
6294             Node :=
6295               Make_Selected_Component
6296                 (Sloc          => Loc,
6297                  Prefix        => Prefix_Node,
6298                  Selector_Name => Selector_Entity);
6299
6300             Set_Restriction_No_Dependence
6301               (Unit    => Node,
6302                Warn    => Treat_Restrictions_As_Warnings,
6303                Profile => Ravenscar);
6304
6305             Name_Buffer (1 .. 6) := "timers";
6306             Name_Len := 6;
6307
6308             Selector_Entity := Make_Identifier (Loc, Name_Find);
6309
6310             Node :=
6311               Make_Selected_Component
6312                 (Sloc          => Loc,
6313                  Prefix        => Prefix_Node,
6314                  Selector_Name => Selector_Entity);
6315
6316             Set_Restriction_No_Dependence
6317               (Unit    => Node,
6318                Warn    => Treat_Restrictions_As_Warnings,
6319                Profile => Ravenscar);
6320          end if;
6321
6322          --  Set the following restrictions which was added to Ada 2012 (see
6323          --  AI-0171):
6324          --    No_Dependence => System.Multiprocessors.Dispatching_Domains
6325
6326          if Ada_Version >= Ada_2012 then
6327             Name_Buffer (1 .. 6) := "system";
6328             Name_Len := 6;
6329
6330             Prefix_Entity := Make_Identifier (Loc, Name_Find);
6331
6332             Name_Buffer (1 .. 15) := "multiprocessors";
6333             Name_Len := 15;
6334
6335             Selector_Entity := Make_Identifier (Loc, Name_Find);
6336
6337             Prefix_Node :=
6338               Make_Selected_Component
6339                 (Sloc          => Loc,
6340                  Prefix        => Prefix_Entity,
6341                  Selector_Name => Selector_Entity);
6342
6343             Name_Buffer (1 .. 19) := "dispatching_domains";
6344             Name_Len := 19;
6345
6346             Selector_Entity := Make_Identifier (Loc, Name_Find);
6347
6348             Node :=
6349               Make_Selected_Component
6350                 (Sloc          => Loc,
6351                  Prefix        => Prefix_Node,
6352                  Selector_Name => Selector_Entity);
6353
6354             Set_Restriction_No_Dependence
6355               (Unit    => Node,
6356                Warn    => Treat_Restrictions_As_Warnings,
6357                Profile => Ravenscar);
6358          end if;
6359       end Set_Ravenscar_Profile;
6360
6361    --  Start of processing for Analyze_Pragma
6362
6363    begin
6364       --  The following code is a defense against recursion. Not clear that
6365       --  this can happen legitimately, but perhaps some error situations
6366       --  can cause it, and we did see this recursion during testing.
6367
6368       if Analyzed (N) then
6369          return;
6370       else
6371          Set_Analyzed (N, True);
6372       end if;
6373
6374       --  Deal with unrecognized pragma
6375
6376       Pname := Pragma_Name (N);
6377
6378       if not Is_Pragma_Name (Pname) then
6379          if Warn_On_Unrecognized_Pragma then
6380             Error_Msg_Name_1 := Pname;
6381             Error_Msg_N ("?unrecognized pragma%!", Pragma_Identifier (N));
6382
6383             for PN in First_Pragma_Name .. Last_Pragma_Name loop
6384                if Is_Bad_Spelling_Of (Pname, PN) then
6385                   Error_Msg_Name_1 := PN;
6386                   Error_Msg_N -- CODEFIX
6387                     ("\?possible misspelling of %!", Pragma_Identifier (N));
6388                   exit;
6389                end if;
6390             end loop;
6391          end if;
6392
6393          return;
6394       end if;
6395
6396       --  Here to start processing for recognized pragma
6397
6398       Prag_Id := Get_Pragma_Id (Pname);
6399
6400       if Present (Corresponding_Aspect (N)) then
6401          Pname := Chars (Identifier (Corresponding_Aspect (N)));
6402       end if;
6403
6404       --  Preset arguments
6405
6406       Arg_Count := 0;
6407       Arg1      := Empty;
6408       Arg2      := Empty;
6409       Arg3      := Empty;
6410       Arg4      := Empty;
6411
6412       if Present (Pragma_Argument_Associations (N)) then
6413          Arg_Count := List_Length (Pragma_Argument_Associations (N));
6414          Arg1 := First (Pragma_Argument_Associations (N));
6415
6416          if Present (Arg1) then
6417             Arg2 := Next (Arg1);
6418
6419             if Present (Arg2) then
6420                Arg3 := Next (Arg2);
6421
6422                if Present (Arg3) then
6423                   Arg4 := Next (Arg3);
6424                end if;
6425             end if;
6426          end if;
6427       end if;
6428
6429       --  An enumeration type defines the pragmas that are supported by the
6430       --  implementation. Get_Pragma_Id (in package Prag) transforms a name
6431       --  into the corresponding enumeration value for the following case.
6432
6433       case Prag_Id is
6434
6435          -----------------
6436          -- Abort_Defer --
6437          -----------------
6438
6439          --  pragma Abort_Defer;
6440
6441          when Pragma_Abort_Defer =>
6442             GNAT_Pragma;
6443             Check_Arg_Count (0);
6444
6445             --  The only required semantic processing is to check the
6446             --  placement. This pragma must appear at the start of the
6447             --  statement sequence of a handled sequence of statements.
6448
6449             if Nkind (Parent (N)) /= N_Handled_Sequence_Of_Statements
6450               or else N /= First (Statements (Parent (N)))
6451             then
6452                Pragma_Misplaced;
6453             end if;
6454
6455          ------------
6456          -- Ada_83 --
6457          ------------
6458
6459          --  pragma Ada_83;
6460
6461          --  Note: this pragma also has some specific processing in Par.Prag
6462          --  because we want to set the Ada version mode during parsing.
6463
6464          when Pragma_Ada_83 =>
6465             GNAT_Pragma;
6466             Check_Arg_Count (0);
6467
6468             --  We really should check unconditionally for proper configuration
6469             --  pragma placement, since we really don't want mixed Ada modes
6470             --  within a single unit, and the GNAT reference manual has always
6471             --  said this was a configuration pragma, but we did not check and
6472             --  are hesitant to add the check now.
6473
6474             --  However, we really cannot tolerate mixing Ada 2005 or Ada 2012
6475             --  with Ada 83 or Ada 95, so we must check if we are in Ada 2005
6476             --  or Ada 2012 mode.
6477
6478             if Ada_Version >= Ada_2005 then
6479                Check_Valid_Configuration_Pragma;
6480             end if;
6481
6482             --  Now set Ada 83 mode
6483
6484             Ada_Version := Ada_83;
6485             Ada_Version_Explicit := Ada_Version;
6486
6487          ------------
6488          -- Ada_95 --
6489          ------------
6490
6491          --  pragma Ada_95;
6492
6493          --  Note: this pragma also has some specific processing in Par.Prag
6494          --  because we want to set the Ada 83 version mode during parsing.
6495
6496          when Pragma_Ada_95 =>
6497             GNAT_Pragma;
6498             Check_Arg_Count (0);
6499
6500             --  We really should check unconditionally for proper configuration
6501             --  pragma placement, since we really don't want mixed Ada modes
6502             --  within a single unit, and the GNAT reference manual has always
6503             --  said this was a configuration pragma, but we did not check and
6504             --  are hesitant to add the check now.
6505
6506             --  However, we really cannot tolerate mixing Ada 2005 with Ada 83
6507             --  or Ada 95, so we must check if we are in Ada 2005 mode.
6508
6509             if Ada_Version >= Ada_2005 then
6510                Check_Valid_Configuration_Pragma;
6511             end if;
6512
6513             --  Now set Ada 95 mode
6514
6515             Ada_Version := Ada_95;
6516             Ada_Version_Explicit := Ada_Version;
6517
6518          ---------------------
6519          -- Ada_05/Ada_2005 --
6520          ---------------------
6521
6522          --  pragma Ada_05;
6523          --  pragma Ada_05 (LOCAL_NAME);
6524
6525          --  pragma Ada_2005;
6526          --  pragma Ada_2005 (LOCAL_NAME):
6527
6528          --  Note: these pragmas also have some specific processing in Par.Prag
6529          --  because we want to set the Ada 2005 version mode during parsing.
6530
6531          when Pragma_Ada_05 | Pragma_Ada_2005 => declare
6532             E_Id : Node_Id;
6533
6534          begin
6535             GNAT_Pragma;
6536
6537             if Arg_Count = 1 then
6538                Check_Arg_Is_Local_Name (Arg1);
6539                E_Id := Get_Pragma_Arg (Arg1);
6540
6541                if Etype (E_Id) = Any_Type then
6542                   return;
6543                end if;
6544
6545                Set_Is_Ada_2005_Only (Entity (E_Id));
6546
6547             else
6548                Check_Arg_Count (0);
6549
6550                --  For Ada_2005 we unconditionally enforce the documented
6551                --  configuration pragma placement, since we do not want to
6552                --  tolerate mixed modes in a unit involving Ada 2005. That
6553                --  would cause real difficulties for those cases where there
6554                --  are incompatibilities between Ada 95 and Ada 2005.
6555
6556                Check_Valid_Configuration_Pragma;
6557
6558                --  Now set appropriate Ada mode
6559
6560                Ada_Version          := Ada_2005;
6561                Ada_Version_Explicit := Ada_2005;
6562             end if;
6563          end;
6564
6565          ---------------------
6566          -- Ada_12/Ada_2012 --
6567          ---------------------
6568
6569          --  pragma Ada_12;
6570          --  pragma Ada_12 (LOCAL_NAME);
6571
6572          --  pragma Ada_2012;
6573          --  pragma Ada_2012 (LOCAL_NAME):
6574
6575          --  Note: these pragmas also have some specific processing in Par.Prag
6576          --  because we want to set the Ada 2012 version mode during parsing.
6577
6578          when Pragma_Ada_12 | Pragma_Ada_2012 => declare
6579             E_Id : Node_Id;
6580
6581          begin
6582             GNAT_Pragma;
6583
6584             if Arg_Count = 1 then
6585                Check_Arg_Is_Local_Name (Arg1);
6586                E_Id := Get_Pragma_Arg (Arg1);
6587
6588                if Etype (E_Id) = Any_Type then
6589                   return;
6590                end if;
6591
6592                Set_Is_Ada_2012_Only (Entity (E_Id));
6593
6594             else
6595                Check_Arg_Count (0);
6596
6597                --  For Ada_2012 we unconditionally enforce the documented
6598                --  configuration pragma placement, since we do not want to
6599                --  tolerate mixed modes in a unit involving Ada 2012. That
6600                --  would cause real difficulties for those cases where there
6601                --  are incompatibilities between Ada 95 and Ada 2012. We could
6602                --  allow mixing of Ada 2005 and Ada 2012 but it's not worth it.
6603
6604                Check_Valid_Configuration_Pragma;
6605
6606                --  Now set appropriate Ada mode
6607
6608                Ada_Version          := Ada_2012;
6609                Ada_Version_Explicit := Ada_2012;
6610             end if;
6611          end;
6612
6613          ----------------------
6614          -- All_Calls_Remote --
6615          ----------------------
6616
6617          --  pragma All_Calls_Remote [(library_package_NAME)];
6618
6619          when Pragma_All_Calls_Remote => All_Calls_Remote : declare
6620             Lib_Entity : Entity_Id;
6621
6622          begin
6623             Check_Ada_83_Warning;
6624             Check_Valid_Library_Unit_Pragma;
6625
6626             if Nkind (N) = N_Null_Statement then
6627                return;
6628             end if;
6629
6630             Lib_Entity := Find_Lib_Unit_Name;
6631
6632             --  This pragma should only apply to a RCI unit (RM E.2.3(23))
6633
6634             if Present (Lib_Entity)
6635               and then not Debug_Flag_U
6636             then
6637                if not Is_Remote_Call_Interface (Lib_Entity) then
6638                   Error_Pragma ("pragma% only apply to rci unit");
6639
6640                --  Set flag for entity of the library unit
6641
6642                else
6643                   Set_Has_All_Calls_Remote (Lib_Entity);
6644                end if;
6645
6646             end if;
6647          end All_Calls_Remote;
6648
6649          --------------
6650          -- Annotate --
6651          --------------
6652
6653          --  pragma Annotate (IDENTIFIER [, IDENTIFIER {, ARG}]);
6654          --  ARG ::= NAME | EXPRESSION
6655
6656          --  The first two arguments are by convention intended to refer to an
6657          --  external tool and a tool-specific function. These arguments are
6658          --  not analyzed.
6659
6660          when Pragma_Annotate => Annotate : declare
6661             Arg : Node_Id;
6662             Exp : Node_Id;
6663
6664          begin
6665             GNAT_Pragma;
6666             Check_At_Least_N_Arguments (1);
6667             Check_Arg_Is_Identifier (Arg1);
6668             Check_No_Identifiers;
6669             Store_Note (N);
6670
6671             --  Second parameter is optional, it is never analyzed
6672
6673             if No (Arg2) then
6674                null;
6675
6676             --  Here if we have a second parameter
6677
6678             else
6679                --  Second parameter must be identifier
6680
6681                Check_Arg_Is_Identifier (Arg2);
6682
6683                --  Process remaining parameters if any
6684
6685                Arg := Next (Arg2);
6686                while Present (Arg) loop
6687                   Exp := Get_Pragma_Arg (Arg);
6688                   Analyze (Exp);
6689
6690                   if Is_Entity_Name (Exp) then
6691                      null;
6692
6693                   --  For string literals, we assume Standard_String as the
6694                   --  type, unless the string contains wide or wide_wide
6695                   --  characters.
6696
6697                   elsif Nkind (Exp) = N_String_Literal then
6698                      if Has_Wide_Wide_Character (Exp) then
6699                         Resolve (Exp, Standard_Wide_Wide_String);
6700                      elsif Has_Wide_Character (Exp) then
6701                         Resolve (Exp, Standard_Wide_String);
6702                      else
6703                         Resolve (Exp, Standard_String);
6704                      end if;
6705
6706                   elsif Is_Overloaded (Exp) then
6707                         Error_Pragma_Arg
6708                           ("ambiguous argument for pragma%", Exp);
6709
6710                   else
6711                      Resolve (Exp);
6712                   end if;
6713
6714                   Next (Arg);
6715                end loop;
6716             end if;
6717          end Annotate;
6718
6719          ------------
6720          -- Assert --
6721          ------------
6722
6723          --  pragma Assert ([Check =>] Boolean_EXPRESSION
6724          --                 [, [Message =>] Static_String_EXPRESSION]);
6725
6726          when Pragma_Assert => Assert : declare
6727             Expr : Node_Id;
6728             Newa : List_Id;
6729
6730          begin
6731             Ada_2005_Pragma;
6732             Check_At_Least_N_Arguments (1);
6733             Check_At_Most_N_Arguments (2);
6734             Check_Arg_Order ((Name_Check, Name_Message));
6735             Check_Optional_Identifier (Arg1, Name_Check);
6736
6737             --  We treat pragma Assert as equivalent to:
6738
6739             --    pragma Check (Assertion, condition [, msg]);
6740
6741             --  So rewrite pragma in this manner, and analyze the result
6742
6743             Expr := Get_Pragma_Arg (Arg1);
6744             Newa := New_List (
6745               Make_Pragma_Argument_Association (Loc,
6746                 Expression => Make_Identifier (Loc, Name_Assertion)),
6747
6748               Make_Pragma_Argument_Association (Sloc (Expr),
6749                 Expression => Expr));
6750
6751             if Arg_Count > 1 then
6752                Check_Optional_Identifier (Arg2, Name_Message);
6753                Analyze_And_Resolve (Get_Pragma_Arg (Arg2), Standard_String);
6754                Append_To (Newa, Relocate_Node (Arg2));
6755             end if;
6756
6757             Rewrite (N,
6758               Make_Pragma (Loc,
6759                 Chars                        => Name_Check,
6760                 Pragma_Argument_Associations => Newa));
6761             Analyze (N);
6762          end Assert;
6763
6764          ----------------------
6765          -- Assertion_Policy --
6766          ----------------------
6767
6768          --  pragma Assertion_Policy (Check | Disable |Ignore)
6769
6770          when Pragma_Assertion_Policy => Assertion_Policy : declare
6771             Policy : Node_Id;
6772
6773          begin
6774             Ada_2005_Pragma;
6775             Check_Valid_Configuration_Pragma;
6776             Check_Arg_Count (1);
6777             Check_No_Identifiers;
6778             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
6779
6780             --  We treat pragma Assertion_Policy as equivalent to:
6781
6782             --    pragma Check_Policy (Assertion, policy)
6783
6784             --  So rewrite the pragma in that manner and link on to the chain
6785             --  of Check_Policy pragmas, marking the pragma as analyzed.
6786
6787             Policy := Get_Pragma_Arg (Arg1);
6788
6789             Rewrite (N,
6790               Make_Pragma (Loc,
6791                 Chars => Name_Check_Policy,
6792
6793                 Pragma_Argument_Associations => New_List (
6794                   Make_Pragma_Argument_Association (Loc,
6795                     Expression => Make_Identifier (Loc, Name_Assertion)),
6796
6797                   Make_Pragma_Argument_Association (Loc,
6798                     Expression =>
6799                       Make_Identifier (Sloc (Policy), Chars (Policy))))));
6800
6801             Set_Analyzed (N);
6802             Set_Next_Pragma (N, Opt.Check_Policy_List);
6803             Opt.Check_Policy_List := N;
6804          end Assertion_Policy;
6805
6806          ------------------------------
6807          -- Assume_No_Invalid_Values --
6808          ------------------------------
6809
6810          --  pragma Assume_No_Invalid_Values (On | Off);
6811
6812          when Pragma_Assume_No_Invalid_Values =>
6813             GNAT_Pragma;
6814             Check_Valid_Configuration_Pragma;
6815             Check_Arg_Count (1);
6816             Check_No_Identifiers;
6817             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
6818
6819             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
6820                Assume_No_Invalid_Values := True;
6821             else
6822                Assume_No_Invalid_Values := False;
6823             end if;
6824
6825          ---------------
6826          -- AST_Entry --
6827          ---------------
6828
6829          --  pragma AST_Entry (entry_IDENTIFIER);
6830
6831          when Pragma_AST_Entry => AST_Entry : declare
6832             Ent : Node_Id;
6833
6834          begin
6835             GNAT_Pragma;
6836             Check_VMS (N);
6837             Check_Arg_Count (1);
6838             Check_No_Identifiers;
6839             Check_Arg_Is_Local_Name (Arg1);
6840             Ent := Entity (Get_Pragma_Arg (Arg1));
6841
6842             --  Note: the implementation of the AST_Entry pragma could handle
6843             --  the entry family case fine, but for now we are consistent with
6844             --  the DEC rules, and do not allow the pragma, which of course
6845             --  has the effect of also forbidding the attribute.
6846
6847             if Ekind (Ent) /= E_Entry then
6848                Error_Pragma_Arg
6849                  ("pragma% argument must be simple entry name", Arg1);
6850
6851             elsif Is_AST_Entry (Ent) then
6852                Error_Pragma_Arg
6853                  ("duplicate % pragma for entry", Arg1);
6854
6855             elsif Has_Homonym (Ent) then
6856                Error_Pragma_Arg
6857                  ("pragma% argument cannot specify overloaded entry", Arg1);
6858
6859             else
6860                declare
6861                   FF : constant Entity_Id := First_Formal (Ent);
6862
6863                begin
6864                   if Present (FF) then
6865                      if Present (Next_Formal (FF)) then
6866                         Error_Pragma_Arg
6867                           ("entry for pragma% can have only one argument",
6868                            Arg1);
6869
6870                      elsif Parameter_Mode (FF) /= E_In_Parameter then
6871                         Error_Pragma_Arg
6872                           ("entry parameter for pragma% must have mode IN",
6873                            Arg1);
6874                      end if;
6875                   end if;
6876                end;
6877
6878                Set_Is_AST_Entry (Ent);
6879             end if;
6880          end AST_Entry;
6881
6882          ------------------
6883          -- Asynchronous --
6884          ------------------
6885
6886          --  pragma Asynchronous (LOCAL_NAME);
6887
6888          when Pragma_Asynchronous => Asynchronous : declare
6889             Nm     : Entity_Id;
6890             C_Ent  : Entity_Id;
6891             L      : List_Id;
6892             S      : Node_Id;
6893             N      : Node_Id;
6894             Formal : Entity_Id;
6895
6896             procedure Process_Async_Pragma;
6897             --  Common processing for procedure and access-to-procedure case
6898
6899             --------------------------
6900             -- Process_Async_Pragma --
6901             --------------------------
6902
6903             procedure Process_Async_Pragma is
6904             begin
6905                if No (L) then
6906                   Set_Is_Asynchronous (Nm);
6907                   return;
6908                end if;
6909
6910                --  The formals should be of mode IN (RM E.4.1(6))
6911
6912                S := First (L);
6913                while Present (S) loop
6914                   Formal := Defining_Identifier (S);
6915
6916                   if Nkind (Formal) = N_Defining_Identifier
6917                     and then Ekind (Formal) /= E_In_Parameter
6918                   then
6919                      Error_Pragma_Arg
6920                        ("pragma% procedure can only have IN parameter",
6921                         Arg1);
6922                   end if;
6923
6924                   Next (S);
6925                end loop;
6926
6927                Set_Is_Asynchronous (Nm);
6928             end Process_Async_Pragma;
6929
6930          --  Start of processing for pragma Asynchronous
6931
6932          begin
6933             Check_Ada_83_Warning;
6934             Check_No_Identifiers;
6935             Check_Arg_Count (1);
6936             Check_Arg_Is_Local_Name (Arg1);
6937
6938             if Debug_Flag_U then
6939                return;
6940             end if;
6941
6942             C_Ent := Cunit_Entity (Current_Sem_Unit);
6943             Analyze (Get_Pragma_Arg (Arg1));
6944             Nm := Entity (Get_Pragma_Arg (Arg1));
6945
6946             if not Is_Remote_Call_Interface (C_Ent)
6947               and then not Is_Remote_Types (C_Ent)
6948             then
6949                --  This pragma should only appear in an RCI or Remote Types
6950                --  unit (RM E.4.1(4)).
6951
6952                Error_Pragma
6953                  ("pragma% not in Remote_Call_Interface or " &
6954                   "Remote_Types unit");
6955             end if;
6956
6957             if Ekind (Nm) = E_Procedure
6958               and then Nkind (Parent (Nm)) = N_Procedure_Specification
6959             then
6960                if not Is_Remote_Call_Interface (Nm) then
6961                   Error_Pragma_Arg
6962                     ("pragma% cannot be applied on non-remote procedure",
6963                      Arg1);
6964                end if;
6965
6966                L := Parameter_Specifications (Parent (Nm));
6967                Process_Async_Pragma;
6968                return;
6969
6970             elsif Ekind (Nm) = E_Function then
6971                Error_Pragma_Arg
6972                  ("pragma% cannot be applied to function", Arg1);
6973
6974             elsif Is_Remote_Access_To_Subprogram_Type (Nm) then
6975                   if Is_Record_Type (Nm) then
6976
6977                   --  A record type that is the Equivalent_Type for a remote
6978                   --  access-to-subprogram type.
6979
6980                      N := Declaration_Node (Corresponding_Remote_Type (Nm));
6981
6982                   else
6983                      --  A non-expanded RAS type (distribution is not enabled)
6984
6985                      N := Declaration_Node (Nm);
6986                   end if;
6987
6988                if Nkind (N) = N_Full_Type_Declaration
6989                  and then Nkind (Type_Definition (N)) =
6990                                      N_Access_Procedure_Definition
6991                then
6992                   L := Parameter_Specifications (Type_Definition (N));
6993                   Process_Async_Pragma;
6994
6995                   if Is_Asynchronous (Nm)
6996                     and then Expander_Active
6997                     and then Get_PCS_Name /= Name_No_DSA
6998                   then
6999                      RACW_Type_Is_Asynchronous (Underlying_RACW_Type (Nm));
7000                   end if;
7001
7002                else
7003                   Error_Pragma_Arg
7004                     ("pragma% cannot reference access-to-function type",
7005                     Arg1);
7006                end if;
7007
7008             --  Only other possibility is Access-to-class-wide type
7009
7010             elsif Is_Access_Type (Nm)
7011               and then Is_Class_Wide_Type (Designated_Type (Nm))
7012             then
7013                Check_First_Subtype (Arg1);
7014                Set_Is_Asynchronous (Nm);
7015                if Expander_Active then
7016                   RACW_Type_Is_Asynchronous (Nm);
7017                end if;
7018
7019             else
7020                Error_Pragma_Arg ("inappropriate argument for pragma%", Arg1);
7021             end if;
7022          end Asynchronous;
7023
7024          ------------
7025          -- Atomic --
7026          ------------
7027
7028          --  pragma Atomic (LOCAL_NAME);
7029
7030          when Pragma_Atomic =>
7031             Process_Atomic_Shared_Volatile;
7032
7033          -----------------------
7034          -- Atomic_Components --
7035          -----------------------
7036
7037          --  pragma Atomic_Components (array_LOCAL_NAME);
7038
7039          --  This processing is shared by Volatile_Components
7040
7041          when Pragma_Atomic_Components   |
7042               Pragma_Volatile_Components =>
7043
7044          Atomic_Components : declare
7045             E_Id : Node_Id;
7046             E    : Entity_Id;
7047             D    : Node_Id;
7048             K    : Node_Kind;
7049
7050          begin
7051             Check_Ada_83_Warning;
7052             Check_No_Identifiers;
7053             Check_Arg_Count (1);
7054             Check_Arg_Is_Local_Name (Arg1);
7055             E_Id := Get_Pragma_Arg (Arg1);
7056
7057             if Etype (E_Id) = Any_Type then
7058                return;
7059             end if;
7060
7061             E := Entity (E_Id);
7062
7063             Check_Duplicate_Pragma (E);
7064
7065             if Rep_Item_Too_Early (E, N)
7066                  or else
7067                Rep_Item_Too_Late (E, N)
7068             then
7069                return;
7070             end if;
7071
7072             D := Declaration_Node (E);
7073             K := Nkind (D);
7074
7075             if (K = N_Full_Type_Declaration and then Is_Array_Type (E))
7076               or else
7077                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
7078                    and then Nkind (D) = N_Object_Declaration
7079                    and then Nkind (Object_Definition (D)) =
7080                                        N_Constrained_Array_Definition)
7081             then
7082                --  The flag is set on the object, or on the base type
7083
7084                if Nkind (D) /= N_Object_Declaration then
7085                   E := Base_Type (E);
7086                end if;
7087
7088                Set_Has_Volatile_Components (E);
7089
7090                if Prag_Id = Pragma_Atomic_Components then
7091                   Set_Has_Atomic_Components (E);
7092                end if;
7093
7094             else
7095                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
7096             end if;
7097          end Atomic_Components;
7098          --------------------
7099          -- Attach_Handler --
7100          --------------------
7101
7102          --  pragma Attach_Handler (handler_NAME, EXPRESSION);
7103
7104          when Pragma_Attach_Handler =>
7105             Check_Ada_83_Warning;
7106             Check_No_Identifiers;
7107             Check_Arg_Count (2);
7108
7109             if No_Run_Time_Mode then
7110                Error_Msg_CRT ("Attach_Handler pragma", N);
7111             else
7112                Check_Interrupt_Or_Attach_Handler;
7113
7114                --  The expression that designates the attribute may depend on a
7115                --  discriminant, and is therefore a per-object expression, to
7116                --  be expanded in the init proc. If expansion is enabled, then
7117                --  perform semantic checks on a copy only.
7118
7119                if Expander_Active then
7120                   declare
7121                      Temp : constant Node_Id :=
7122                               New_Copy_Tree (Get_Pragma_Arg (Arg2));
7123                   begin
7124                      Set_Parent (Temp, N);
7125                      Preanalyze_And_Resolve (Temp, RTE (RE_Interrupt_ID));
7126                   end;
7127
7128                else
7129                   Analyze (Get_Pragma_Arg (Arg2));
7130                   Resolve (Get_Pragma_Arg (Arg2), RTE (RE_Interrupt_ID));
7131                end if;
7132
7133                Process_Interrupt_Or_Attach_Handler;
7134             end if;
7135
7136          --------------------
7137          -- C_Pass_By_Copy --
7138          --------------------
7139
7140          --  pragma C_Pass_By_Copy ([Max_Size =>] static_integer_EXPRESSION);
7141
7142          when Pragma_C_Pass_By_Copy => C_Pass_By_Copy : declare
7143             Arg : Node_Id;
7144             Val : Uint;
7145
7146          begin
7147             GNAT_Pragma;
7148             Check_Valid_Configuration_Pragma;
7149             Check_Arg_Count (1);
7150             Check_Optional_Identifier (Arg1, "max_size");
7151
7152             Arg := Get_Pragma_Arg (Arg1);
7153             Check_Arg_Is_Static_Expression (Arg, Any_Integer);
7154
7155             Val := Expr_Value (Arg);
7156
7157             if Val <= 0 then
7158                Error_Pragma_Arg
7159                  ("maximum size for pragma% must be positive", Arg1);
7160
7161             elsif UI_Is_In_Int_Range (Val) then
7162                Default_C_Record_Mechanism := UI_To_Int (Val);
7163
7164             --  If a giant value is given, Int'Last will do well enough.
7165             --  If sometime someone complains that a record larger than
7166             --  two gigabytes is not copied, we will worry about it then!
7167
7168             else
7169                Default_C_Record_Mechanism := Mechanism_Type'Last;
7170             end if;
7171          end C_Pass_By_Copy;
7172
7173          -----------
7174          -- Check --
7175          -----------
7176
7177          --  pragma Check ([Name    =>] IDENTIFIER,
7178          --                [Check   =>] Boolean_EXPRESSION
7179          --              [,[Message =>] String_EXPRESSION]);
7180
7181          when Pragma_Check => Check : declare
7182             Expr : Node_Id;
7183             Eloc : Source_Ptr;
7184
7185             Check_On : Boolean;
7186             --  Set True if category of assertions referenced by Name enabled
7187
7188          begin
7189             GNAT_Pragma;
7190             Check_At_Least_N_Arguments (2);
7191             Check_At_Most_N_Arguments (3);
7192             Check_Optional_Identifier (Arg1, Name_Name);
7193             Check_Optional_Identifier (Arg2, Name_Check);
7194
7195             if Arg_Count = 3 then
7196                Check_Optional_Identifier (Arg3, Name_Message);
7197                Analyze_And_Resolve (Get_Pragma_Arg (Arg3), Standard_String);
7198             end if;
7199
7200             Check_Arg_Is_Identifier (Arg1);
7201
7202             --  Completely ignore if disabled
7203
7204             if Check_Disabled (Chars (Get_Pragma_Arg (Arg1))) then
7205                Rewrite (N, Make_Null_Statement (Loc));
7206                Analyze (N);
7207                return;
7208             end if;
7209
7210             --  Indicate if pragma is enabled. The Original_Node reference here
7211             --  is to deal with pragma Assert rewritten as a Check pragma.
7212
7213             Check_On := Check_Enabled (Chars (Get_Pragma_Arg (Arg1)));
7214
7215             if Check_On then
7216                Set_SCO_Pragma_Enabled (Loc);
7217             end if;
7218
7219             --  If expansion is active and the check is not enabled then we
7220             --  rewrite the Check as:
7221
7222             --    if False and then condition then
7223             --       null;
7224             --    end if;
7225
7226             --  The reason we do this rewriting during semantic analysis rather
7227             --  than as part of normal expansion is that we cannot analyze and
7228             --  expand the code for the boolean expression directly, or it may
7229             --  cause insertion of actions that would escape the attempt to
7230             --  suppress the check code.
7231
7232             --  Note that the Sloc for the if statement corresponds to the
7233             --  argument condition, not the pragma itself. The reason for this
7234             --  is that we may generate a warning if the condition is False at
7235             --  compile time, and we do not want to delete this warning when we
7236             --  delete the if statement.
7237
7238             Expr := Get_Pragma_Arg (Arg2);
7239
7240             if Expander_Active and then not Check_On then
7241                Eloc := Sloc (Expr);
7242
7243                Rewrite (N,
7244                  Make_If_Statement (Eloc,
7245                    Condition =>
7246                      Make_And_Then (Eloc,
7247                        Left_Opnd  => New_Occurrence_Of (Standard_False, Eloc),
7248                        Right_Opnd => Expr),
7249                    Then_Statements => New_List (
7250                      Make_Null_Statement (Eloc))));
7251
7252                Analyze (N);
7253
7254             --  Check is active
7255
7256             else
7257                Analyze_And_Resolve (Expr, Any_Boolean);
7258             end if;
7259          end Check;
7260
7261          ----------------
7262          -- Check_Name --
7263          ----------------
7264
7265          --  pragma Check_Name (check_IDENTIFIER);
7266
7267          when Pragma_Check_Name =>
7268             Check_No_Identifiers;
7269             GNAT_Pragma;
7270             Check_Valid_Configuration_Pragma;
7271             Check_Arg_Count (1);
7272             Check_Arg_Is_Identifier (Arg1);
7273
7274             declare
7275                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
7276
7277             begin
7278                for J in Check_Names.First .. Check_Names.Last loop
7279                   if Check_Names.Table (J) = Nam then
7280                      return;
7281                   end if;
7282                end loop;
7283
7284                Check_Names.Append (Nam);
7285             end;
7286
7287          ------------------
7288          -- Check_Policy --
7289          ------------------
7290
7291          --  pragma Check_Policy (
7292          --    [Name   =>] IDENTIFIER,
7293          --    [Policy =>] POLICY_IDENTIFIER);
7294
7295          --  POLICY_IDENTIFIER ::= ON | OFF | CHECK | DISABLE | IGNORE
7296
7297          --  Note: this is a configuration pragma, but it is allowed to appear
7298          --  anywhere else.
7299
7300          when Pragma_Check_Policy =>
7301             GNAT_Pragma;
7302             Check_Arg_Count (2);
7303             Check_Optional_Identifier (Arg1, Name_Name);
7304             Check_Optional_Identifier (Arg2, Name_Policy);
7305             Check_Arg_Is_One_Of
7306               (Arg2, Name_On, Name_Off, Name_Check, Name_Disable, Name_Ignore);
7307
7308             --  A Check_Policy pragma can appear either as a configuration
7309             --  pragma, or in a declarative part or a package spec (see RM
7310             --  11.5(5) for rules for Suppress/Unsuppress which are also
7311             --  followed for Check_Policy).
7312
7313             if not Is_Configuration_Pragma then
7314                Check_Is_In_Decl_Part_Or_Package_Spec;
7315             end if;
7316
7317             Set_Next_Pragma (N, Opt.Check_Policy_List);
7318             Opt.Check_Policy_List := N;
7319
7320          ---------------------
7321          -- CIL_Constructor --
7322          ---------------------
7323
7324          --  pragma CIL_Constructor ([Entity =>] LOCAL_NAME);
7325
7326          --  Processing for this pragma is shared with Java_Constructor
7327
7328          -------------
7329          -- Comment --
7330          -------------
7331
7332          --  pragma Comment (static_string_EXPRESSION)
7333
7334          --  Processing for pragma Comment shares the circuitry for pragma
7335          --  Ident. The only differences are that Ident enforces a limit of 31
7336          --  characters on its argument, and also enforces limitations on
7337          --  placement for DEC compatibility. Pragma Comment shares neither of
7338          --  these restrictions.
7339
7340          -------------------
7341          -- Common_Object --
7342          -------------------
7343
7344          --  pragma Common_Object (
7345          --        [Internal =>] LOCAL_NAME
7346          --     [, [External =>] EXTERNAL_SYMBOL]
7347          --     [, [Size     =>] EXTERNAL_SYMBOL]);
7348
7349          --  Processing for this pragma is shared with Psect_Object
7350
7351          ------------------------
7352          -- Compile_Time_Error --
7353          ------------------------
7354
7355          --  pragma Compile_Time_Error
7356          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7357
7358          when Pragma_Compile_Time_Error =>
7359             GNAT_Pragma;
7360             Process_Compile_Time_Warning_Or_Error;
7361
7362          --------------------------
7363          -- Compile_Time_Warning --
7364          --------------------------
7365
7366          --  pragma Compile_Time_Warning
7367          --    (boolean_EXPRESSION, static_string_EXPRESSION);
7368
7369          when Pragma_Compile_Time_Warning =>
7370             GNAT_Pragma;
7371             Process_Compile_Time_Warning_Or_Error;
7372
7373          -------------------
7374          -- Compiler_Unit --
7375          -------------------
7376
7377          when Pragma_Compiler_Unit =>
7378             GNAT_Pragma;
7379             Check_Arg_Count (0);
7380             Set_Is_Compiler_Unit (Get_Source_Unit (N));
7381
7382          -----------------------------
7383          -- Complete_Representation --
7384          -----------------------------
7385
7386          --  pragma Complete_Representation;
7387
7388          when Pragma_Complete_Representation =>
7389             GNAT_Pragma;
7390             Check_Arg_Count (0);
7391
7392             if Nkind (Parent (N)) /= N_Record_Representation_Clause then
7393                Error_Pragma
7394                  ("pragma & must appear within record representation clause");
7395             end if;
7396
7397          ----------------------------
7398          -- Complex_Representation --
7399          ----------------------------
7400
7401          --  pragma Complex_Representation ([Entity =>] LOCAL_NAME);
7402
7403          when Pragma_Complex_Representation => Complex_Representation : declare
7404             E_Id : Entity_Id;
7405             E    : Entity_Id;
7406             Ent  : Entity_Id;
7407
7408          begin
7409             GNAT_Pragma;
7410             Check_Arg_Count (1);
7411             Check_Optional_Identifier (Arg1, Name_Entity);
7412             Check_Arg_Is_Local_Name (Arg1);
7413             E_Id := Get_Pragma_Arg (Arg1);
7414
7415             if Etype (E_Id) = Any_Type then
7416                return;
7417             end if;
7418
7419             E := Entity (E_Id);
7420
7421             if not Is_Record_Type (E) then
7422                Error_Pragma_Arg
7423                  ("argument for pragma% must be record type", Arg1);
7424             end if;
7425
7426             Ent := First_Entity (E);
7427
7428             if No (Ent)
7429               or else No (Next_Entity (Ent))
7430               or else Present (Next_Entity (Next_Entity (Ent)))
7431               or else not Is_Floating_Point_Type (Etype (Ent))
7432               or else Etype (Ent) /= Etype (Next_Entity (Ent))
7433             then
7434                Error_Pragma_Arg
7435                  ("record for pragma% must have two fields of the same "
7436                   & "floating-point type", Arg1);
7437
7438             else
7439                Set_Has_Complex_Representation (Base_Type (E));
7440
7441                --  We need to treat the type has having a non-standard
7442                --  representation, for back-end purposes, even though in
7443                --  general a complex will have the default representation
7444                --  of a record with two real components.
7445
7446                Set_Has_Non_Standard_Rep (Base_Type (E));
7447             end if;
7448          end Complex_Representation;
7449
7450          -------------------------
7451          -- Component_Alignment --
7452          -------------------------
7453
7454          --  pragma Component_Alignment (
7455          --        [Form =>] ALIGNMENT_CHOICE
7456          --     [, [Name =>] type_LOCAL_NAME]);
7457          --
7458          --   ALIGNMENT_CHOICE ::=
7459          --     Component_Size
7460          --   | Component_Size_4
7461          --   | Storage_Unit
7462          --   | Default
7463
7464          when Pragma_Component_Alignment => Component_AlignmentP : declare
7465             Args  : Args_List (1 .. 2);
7466             Names : constant Name_List (1 .. 2) := (
7467                       Name_Form,
7468                       Name_Name);
7469
7470             Form  : Node_Id renames Args (1);
7471             Name  : Node_Id renames Args (2);
7472
7473             Atype : Component_Alignment_Kind;
7474             Typ   : Entity_Id;
7475
7476          begin
7477             GNAT_Pragma;
7478             Gather_Associations (Names, Args);
7479
7480             if No (Form) then
7481                Error_Pragma ("missing Form argument for pragma%");
7482             end if;
7483
7484             Check_Arg_Is_Identifier (Form);
7485
7486             --  Get proper alignment, note that Default = Component_Size on all
7487             --  machines we have so far, and we want to set this value rather
7488             --  than the default value to indicate that it has been explicitly
7489             --  set (and thus will not get overridden by the default component
7490             --  alignment for the current scope)
7491
7492             if Chars (Form) = Name_Component_Size then
7493                Atype := Calign_Component_Size;
7494
7495             elsif Chars (Form) = Name_Component_Size_4 then
7496                Atype := Calign_Component_Size_4;
7497
7498             elsif Chars (Form) = Name_Default then
7499                Atype := Calign_Component_Size;
7500
7501             elsif Chars (Form) = Name_Storage_Unit then
7502                Atype := Calign_Storage_Unit;
7503
7504             else
7505                Error_Pragma_Arg
7506                  ("invalid Form parameter for pragma%", Form);
7507             end if;
7508
7509             --  Case with no name, supplied, affects scope table entry
7510
7511             if No (Name) then
7512                Scope_Stack.Table
7513                  (Scope_Stack.Last).Component_Alignment_Default := Atype;
7514
7515             --  Case of name supplied
7516
7517             else
7518                Check_Arg_Is_Local_Name (Name);
7519                Find_Type (Name);
7520                Typ := Entity (Name);
7521
7522                if Typ = Any_Type
7523                  or else Rep_Item_Too_Early (Typ, N)
7524                then
7525                   return;
7526                else
7527                   Typ := Underlying_Type (Typ);
7528                end if;
7529
7530                if not Is_Record_Type (Typ)
7531                  and then not Is_Array_Type (Typ)
7532                then
7533                   Error_Pragma_Arg
7534                     ("Name parameter of pragma% must identify record or " &
7535                      "array type", Name);
7536                end if;
7537
7538                --  An explicit Component_Alignment pragma overrides an
7539                --  implicit pragma Pack, but not an explicit one.
7540
7541                if not Has_Pragma_Pack (Base_Type (Typ)) then
7542                   Set_Is_Packed (Base_Type (Typ), False);
7543                   Set_Component_Alignment (Base_Type (Typ), Atype);
7544                end if;
7545             end if;
7546          end Component_AlignmentP;
7547
7548          ----------------
7549          -- Controlled --
7550          ----------------
7551
7552          --  pragma Controlled (first_subtype_LOCAL_NAME);
7553
7554          when Pragma_Controlled => Controlled : declare
7555             Arg : Node_Id;
7556
7557          begin
7558             Check_No_Identifiers;
7559             Check_Arg_Count (1);
7560             Check_Arg_Is_Local_Name (Arg1);
7561             Arg := Get_Pragma_Arg (Arg1);
7562
7563             if not Is_Entity_Name (Arg)
7564               or else not Is_Access_Type (Entity (Arg))
7565             then
7566                Error_Pragma_Arg ("pragma% requires access type", Arg1);
7567             else
7568                Set_Has_Pragma_Controlled (Base_Type (Entity (Arg)));
7569             end if;
7570          end Controlled;
7571
7572          ----------------
7573          -- Convention --
7574          ----------------
7575
7576          --  pragma Convention ([Convention =>] convention_IDENTIFIER,
7577          --    [Entity =>] LOCAL_NAME);
7578
7579          when Pragma_Convention => Convention : declare
7580             C : Convention_Id;
7581             E : Entity_Id;
7582             pragma Warnings (Off, C);
7583             pragma Warnings (Off, E);
7584          begin
7585             Check_Arg_Order ((Name_Convention, Name_Entity));
7586             Check_Ada_83_Warning;
7587             Check_Arg_Count (2);
7588             Process_Convention (C, E);
7589          end Convention;
7590
7591          ---------------------------
7592          -- Convention_Identifier --
7593          ---------------------------
7594
7595          --  pragma Convention_Identifier ([Name =>] IDENTIFIER,
7596          --    [Convention =>] convention_IDENTIFIER);
7597
7598          when Pragma_Convention_Identifier => Convention_Identifier : declare
7599             Idnam : Name_Id;
7600             Cname : Name_Id;
7601
7602          begin
7603             GNAT_Pragma;
7604             Check_Arg_Order ((Name_Name, Name_Convention));
7605             Check_Arg_Count (2);
7606             Check_Optional_Identifier (Arg1, Name_Name);
7607             Check_Optional_Identifier (Arg2, Name_Convention);
7608             Check_Arg_Is_Identifier (Arg1);
7609             Check_Arg_Is_Identifier (Arg2);
7610             Idnam := Chars (Get_Pragma_Arg (Arg1));
7611             Cname := Chars (Get_Pragma_Arg (Arg2));
7612
7613             if Is_Convention_Name (Cname) then
7614                Record_Convention_Identifier
7615                  (Idnam, Get_Convention_Id (Cname));
7616             else
7617                Error_Pragma_Arg
7618                  ("second arg for % pragma must be convention", Arg2);
7619             end if;
7620          end Convention_Identifier;
7621
7622          ---------------
7623          -- CPP_Class --
7624          ---------------
7625
7626          --  pragma CPP_Class ([Entity =>] local_NAME)
7627
7628          when Pragma_CPP_Class => CPP_Class : declare
7629             Arg : Node_Id;
7630             Typ : Entity_Id;
7631
7632          begin
7633             if Warn_On_Obsolescent_Feature then
7634                Error_Msg_N
7635                  ("'G'N'A'T pragma cpp'_class is now obsolete; replace it" &
7636                   " by pragma import?", N);
7637             end if;
7638
7639             GNAT_Pragma;
7640             Check_Arg_Count (1);
7641             Check_Optional_Identifier (Arg1, Name_Entity);
7642             Check_Arg_Is_Local_Name (Arg1);
7643
7644             Arg := Get_Pragma_Arg (Arg1);
7645             Analyze (Arg);
7646
7647             if Etype (Arg) = Any_Type then
7648                return;
7649             end if;
7650
7651             if not Is_Entity_Name (Arg)
7652               or else not Is_Type (Entity (Arg))
7653             then
7654                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
7655             end if;
7656
7657             Typ := Entity (Arg);
7658
7659             if not Is_Tagged_Type (Typ) then
7660                Error_Pragma_Arg ("pragma% applicable to tagged types ", Arg1);
7661             end if;
7662
7663             --  Types treated as CPP classes must be declared limited (note:
7664             --  this used to be a warning but there is no real benefit to it
7665             --  since we did effectively intend to treat the type as limited
7666             --  anyway).
7667
7668             if not Is_Limited_Type (Typ) then
7669                Error_Msg_N
7670                  ("imported 'C'P'P type must be limited",
7671                   Get_Pragma_Arg (Arg1));
7672             end if;
7673
7674             Set_Is_CPP_Class (Typ);
7675             Set_Convention (Typ, Convention_CPP);
7676
7677             --  Imported CPP types must not have discriminants (because C++
7678             --  classes do not have discriminants).
7679
7680             if Has_Discriminants (Typ) then
7681                Error_Msg_N
7682                  ("imported 'C'P'P type cannot have discriminants",
7683                   First (Discriminant_Specifications
7684                           (Declaration_Node (Typ))));
7685             end if;
7686
7687             --  Components of imported CPP types must not have default
7688             --  expressions because the constructor (if any) is in the
7689             --  C++ side.
7690
7691             if Is_Incomplete_Or_Private_Type (Typ)
7692               and then No (Underlying_Type (Typ))
7693             then
7694                --  It should be an error to apply pragma CPP to a private
7695                --  type if the underlying type is not visible (as it is
7696                --  for any representation item). For now, for backward
7697                --  compatibility we do nothing but we cannot check components
7698                --  because they are not available at this stage. All this code
7699                --  will be removed when we cleanup this obsolete GNAT pragma???
7700
7701                null;
7702
7703             else
7704                declare
7705                   Tdef  : constant Node_Id :=
7706                             Type_Definition (Declaration_Node (Typ));
7707                   Clist : Node_Id;
7708                   Comp  : Node_Id;
7709
7710                begin
7711                   if Nkind (Tdef) = N_Record_Definition then
7712                      Clist := Component_List (Tdef);
7713                   else
7714                      pragma Assert (Nkind (Tdef) = N_Derived_Type_Definition);
7715                      Clist := Component_List (Record_Extension_Part (Tdef));
7716                   end if;
7717
7718                   if Present (Clist) then
7719                      Comp := First (Component_Items (Clist));
7720                      while Present (Comp) loop
7721                         if Present (Expression (Comp)) then
7722                            Error_Msg_N
7723                              ("component of imported 'C'P'P type cannot have" &
7724                               " default expression", Expression (Comp));
7725                         end if;
7726
7727                         Next (Comp);
7728                      end loop;
7729                   end if;
7730                end;
7731             end if;
7732          end CPP_Class;
7733
7734          ---------------------
7735          -- CPP_Constructor --
7736          ---------------------
7737
7738          --  pragma CPP_Constructor ([Entity =>] LOCAL_NAME
7739          --    [, [External_Name =>] static_string_EXPRESSION ]
7740          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
7741
7742          when Pragma_CPP_Constructor => CPP_Constructor : declare
7743             Elmt    : Elmt_Id;
7744             Id      : Entity_Id;
7745             Def_Id  : Entity_Id;
7746             Tag_Typ : Entity_Id;
7747
7748          begin
7749             GNAT_Pragma;
7750             Check_At_Least_N_Arguments (1);
7751             Check_At_Most_N_Arguments (3);
7752             Check_Optional_Identifier (Arg1, Name_Entity);
7753             Check_Arg_Is_Local_Name (Arg1);
7754
7755             Id := Get_Pragma_Arg (Arg1);
7756             Find_Program_Unit_Name (Id);
7757
7758             --  If we did not find the name, we are done
7759
7760             if Etype (Id) = Any_Type then
7761                return;
7762             end if;
7763
7764             Def_Id := Entity (Id);
7765
7766             --  Check if already defined as constructor
7767
7768             if Is_Constructor (Def_Id) then
7769                Error_Msg_N
7770                  ("?duplicate argument for pragma 'C'P'P_Constructor", Arg1);
7771                return;
7772             end if;
7773
7774             if Ekind (Def_Id) = E_Function
7775               and then (Is_CPP_Class (Etype (Def_Id))
7776                          or else (Is_Class_Wide_Type (Etype (Def_Id))
7777                                    and then
7778                                   Is_CPP_Class (Root_Type (Etype (Def_Id)))))
7779             then
7780                if Arg_Count >= 2 then
7781                   Set_Imported (Def_Id);
7782                   Set_Is_Public (Def_Id);
7783                   Process_Interface_Name (Def_Id, Arg2, Arg3);
7784                end if;
7785
7786                Set_Has_Completion (Def_Id);
7787                Set_Is_Constructor (Def_Id);
7788                Set_Convention (Def_Id, Convention_CPP);
7789
7790                --  Imported C++ constructors are not dispatching primitives
7791                --  because in C++ they don't have a dispatch table slot.
7792                --  However, in Ada the constructor has the profile of a
7793                --  function that returns a tagged type and therefore it has
7794                --  been treated as a primitive operation during semantic
7795                --  analysis. We now remove it from the list of primitive
7796                --  operations of the type.
7797
7798                if Is_Tagged_Type (Etype (Def_Id))
7799                  and then not Is_Class_Wide_Type (Etype (Def_Id))
7800                then
7801                   pragma Assert (Is_Dispatching_Operation (Def_Id));
7802                   Tag_Typ := Etype (Def_Id);
7803
7804                   Elmt := First_Elmt (Primitive_Operations (Tag_Typ));
7805                   while Present (Elmt) and then Node (Elmt) /= Def_Id loop
7806                      Next_Elmt (Elmt);
7807                   end loop;
7808
7809                   Remove_Elmt (Primitive_Operations (Tag_Typ), Elmt);
7810                   Set_Is_Dispatching_Operation (Def_Id, False);
7811                end if;
7812
7813                --  For backward compatibility, if the constructor returns a
7814                --  class wide type, and we internally change the return type to
7815                --  the corresponding root type.
7816
7817                if Is_Class_Wide_Type (Etype (Def_Id)) then
7818                   Set_Etype (Def_Id, Root_Type (Etype (Def_Id)));
7819                end if;
7820             else
7821                Error_Pragma_Arg
7822                  ("pragma% requires function returning a 'C'P'P_Class type",
7823                    Arg1);
7824             end if;
7825          end CPP_Constructor;
7826
7827          -----------------
7828          -- CPP_Virtual --
7829          -----------------
7830
7831          when Pragma_CPP_Virtual => CPP_Virtual : declare
7832          begin
7833             GNAT_Pragma;
7834
7835             if Warn_On_Obsolescent_Feature then
7836                Error_Msg_N
7837                  ("'G'N'A'T pragma cpp'_virtual is now obsolete and has " &
7838                   "no effect?", N);
7839             end if;
7840          end CPP_Virtual;
7841
7842          ----------------
7843          -- CPP_Vtable --
7844          ----------------
7845
7846          when Pragma_CPP_Vtable => CPP_Vtable : declare
7847          begin
7848             GNAT_Pragma;
7849
7850             if Warn_On_Obsolescent_Feature then
7851                Error_Msg_N
7852                  ("'G'N'A'T pragma cpp'_vtable is now obsolete and has " &
7853                   "no effect?", N);
7854             end if;
7855          end CPP_Vtable;
7856
7857          ---------
7858          -- CPU --
7859          ---------
7860
7861          --  pragma CPU (EXPRESSION);
7862
7863          when Pragma_CPU => CPU : declare
7864             P   : constant Node_Id := Parent (N);
7865             Arg : Node_Id;
7866
7867          begin
7868             Ada_2012_Pragma;
7869             Check_No_Identifiers;
7870             Check_Arg_Count (1);
7871
7872             --  Subprogram case
7873
7874             if Nkind (P) = N_Subprogram_Body then
7875                Check_In_Main_Program;
7876
7877                Arg := Get_Pragma_Arg (Arg1);
7878                Analyze_And_Resolve (Arg, Any_Integer);
7879
7880                --  Must be static
7881
7882                if not Is_Static_Expression (Arg) then
7883                   Flag_Non_Static_Expr
7884                     ("main subprogram affinity is not static!", Arg);
7885                   raise Pragma_Exit;
7886
7887                --  If constraint error, then we already signalled an error
7888
7889                elsif Raises_Constraint_Error (Arg) then
7890                   null;
7891
7892                --  Otherwise check in range
7893
7894                else
7895                   declare
7896                      CPU_Id : constant Entity_Id := RTE (RE_CPU_Range);
7897                      --  This is the entity System.Multiprocessors.CPU_Range;
7898
7899                      Val : constant Uint := Expr_Value (Arg);
7900
7901                   begin
7902                      if Val < Expr_Value (Type_Low_Bound (CPU_Id))
7903                           or else
7904                         Val > Expr_Value (Type_High_Bound (CPU_Id))
7905                      then
7906                         Error_Pragma_Arg
7907                           ("main subprogram CPU is out of range", Arg1);
7908                      end if;
7909                   end;
7910                end if;
7911
7912                Set_Main_CPU
7913                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
7914
7915             --  Task case
7916
7917             elsif Nkind (P) = N_Task_Definition then
7918                Arg := Get_Pragma_Arg (Arg1);
7919
7920                --  The expression must be analyzed in the special manner
7921                --  described in "Handling of Default and Per-Object
7922                --  Expressions" in sem.ads.
7923
7924                Preanalyze_Spec_Expression (Arg, RTE (RE_CPU_Range));
7925
7926             --  Anything else is incorrect
7927
7928             else
7929                Pragma_Misplaced;
7930             end if;
7931
7932             if Has_Pragma_CPU (P) then
7933                Error_Pragma ("duplicate pragma% not allowed");
7934             else
7935                Set_Has_Pragma_CPU (P, True);
7936
7937                if Nkind (P) = N_Task_Definition then
7938                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
7939                end if;
7940             end if;
7941          end CPU;
7942
7943          -----------
7944          -- Debug --
7945          -----------
7946
7947          --  pragma Debug ([boolean_EXPRESSION,] PROCEDURE_CALL_STATEMENT);
7948
7949          when Pragma_Debug => Debug : declare
7950             Cond : Node_Id;
7951             Call : Node_Id;
7952
7953          begin
7954             GNAT_Pragma;
7955
7956             --  Skip analysis if disabled
7957
7958             if Debug_Pragmas_Disabled then
7959                Rewrite (N, Make_Null_Statement (Loc));
7960                Analyze (N);
7961                return;
7962             end if;
7963
7964             Cond :=
7965               New_Occurrence_Of
7966                 (Boolean_Literals (Debug_Pragmas_Enabled and Expander_Active),
7967                  Loc);
7968
7969             if Debug_Pragmas_Enabled then
7970                Set_SCO_Pragma_Enabled (Loc);
7971             end if;
7972
7973             if Arg_Count = 2 then
7974                Cond :=
7975                  Make_And_Then (Loc,
7976                    Left_Opnd  => Relocate_Node (Cond),
7977                    Right_Opnd => Get_Pragma_Arg (Arg1));
7978                Call := Get_Pragma_Arg (Arg2);
7979             else
7980                Call := Get_Pragma_Arg (Arg1);
7981             end if;
7982
7983             if Nkind_In (Call,
7984                  N_Indexed_Component,
7985                  N_Function_Call,
7986                  N_Identifier,
7987                  N_Expanded_Name,
7988                  N_Selected_Component)
7989             then
7990                --  If this pragma Debug comes from source, its argument was
7991                --  parsed as a name form (which is syntactically identical).
7992                --  In a generic context a parameterless call will be left as
7993                --  an expanded name (if global) or selected_component if local.
7994                --  Change it to a procedure call statement now.
7995
7996                Change_Name_To_Procedure_Call_Statement (Call);
7997
7998             elsif Nkind (Call) = N_Procedure_Call_Statement then
7999
8000                --  Already in the form of a procedure call statement: nothing
8001                --  to do (could happen in case of an internally generated
8002                --  pragma Debug).
8003
8004                null;
8005
8006             else
8007                --  All other cases: diagnose error
8008
8009                Error_Msg
8010                  ("argument of pragma ""Debug"" is not procedure call",
8011                   Sloc (Call));
8012                return;
8013             end if;
8014
8015             --  Rewrite into a conditional with an appropriate condition. We
8016             --  wrap the procedure call in a block so that overhead from e.g.
8017             --  use of the secondary stack does not generate execution overhead
8018             --  for suppressed conditions.
8019
8020             --  Normally the analysis that follows will freeze the subprogram
8021             --  being called. However, if the call is to a null procedure,
8022             --  we want to freeze it before creating the block, because the
8023             --  analysis that follows may be done with expansion disabled, in
8024             --  which case the body will not be generated, leading to spurious
8025             --  errors.
8026
8027             if Nkind (Call) = N_Procedure_Call_Statement
8028               and then Is_Entity_Name (Name (Call))
8029             then
8030                Analyze (Name (Call));
8031                Freeze_Before (N, Entity (Name (Call)));
8032             end if;
8033
8034             Rewrite (N, Make_Implicit_If_Statement (N,
8035               Condition => Cond,
8036                  Then_Statements => New_List (
8037                    Make_Block_Statement (Loc,
8038                      Handled_Statement_Sequence =>
8039                        Make_Handled_Sequence_Of_Statements (Loc,
8040                          Statements => New_List (Relocate_Node (Call)))))));
8041             Analyze (N);
8042          end Debug;
8043
8044          ------------------
8045          -- Debug_Policy --
8046          ------------------
8047
8048          --  pragma Debug_Policy (Check | Ignore)
8049
8050          when Pragma_Debug_Policy =>
8051             GNAT_Pragma;
8052             Check_Arg_Count (1);
8053             Check_Arg_Is_One_Of (Arg1, Name_Check, Name_Disable, Name_Ignore);
8054             Debug_Pragmas_Enabled :=
8055               Chars (Get_Pragma_Arg (Arg1)) = Name_Check;
8056             Debug_Pragmas_Disabled :=
8057               Chars (Get_Pragma_Arg (Arg1)) = Name_Disable;
8058
8059          ---------------------
8060          -- Detect_Blocking --
8061          ---------------------
8062
8063          --  pragma Detect_Blocking;
8064
8065          when Pragma_Detect_Blocking =>
8066             Ada_2005_Pragma;
8067             Check_Arg_Count (0);
8068             Check_Valid_Configuration_Pragma;
8069             Detect_Blocking := True;
8070
8071          --------------------------
8072          -- Default_Storage_Pool --
8073          --------------------------
8074
8075          --  pragma Default_Storage_Pool (storage_pool_NAME | null);
8076
8077          when Pragma_Default_Storage_Pool =>
8078             Ada_2012_Pragma;
8079             Check_Arg_Count (1);
8080
8081             --  Default_Storage_Pool can appear as a configuration pragma, or
8082             --  in a declarative part or a package spec.
8083
8084             if not Is_Configuration_Pragma then
8085                Check_Is_In_Decl_Part_Or_Package_Spec;
8086             end if;
8087
8088             --  Case of Default_Storage_Pool (null);
8089
8090             if Nkind (Expression (Arg1)) = N_Null then
8091                Analyze (Expression (Arg1));
8092
8093                --  This is an odd case, this is not really an expression, so
8094                --  we don't have a type for it. So just set the type to Empty.
8095
8096                Set_Etype (Expression (Arg1), Empty);
8097
8098             --  Case of Default_Storage_Pool (storage_pool_NAME);
8099
8100             else
8101                --  If it's a configuration pragma, then the only allowed
8102                --  argument is "null".
8103
8104                if Is_Configuration_Pragma then
8105                   Error_Pragma_Arg ("NULL expected", Arg1);
8106                end if;
8107
8108                --  The expected type for a non-"null" argument is
8109                --  Root_Storage_Pool'Class.
8110
8111                Analyze_And_Resolve
8112                  (Get_Pragma_Arg (Arg1),
8113                   Typ => Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
8114             end if;
8115
8116             --  Finally, record the pool name (or null). Freeze.Freeze_Entity
8117             --  for an access type will use this information to set the
8118             --  appropriate attributes of the access type.
8119
8120             Default_Pool := Expression (Arg1);
8121
8122          ------------------------------------
8123          -- Disable_Atomic_Synchronization --
8124          ------------------------------------
8125
8126          --  pragma Disable_Atomic_Synchronization [(Entity)];
8127
8128          when Pragma_Disable_Atomic_Synchronization =>
8129             Process_Disable_Enable_Atomic_Sync (Name_Suppress);
8130
8131          -------------------
8132          -- Discard_Names --
8133          -------------------
8134
8135          --  pragma Discard_Names [([On =>] LOCAL_NAME)];
8136
8137          when Pragma_Discard_Names => Discard_Names : declare
8138             E    : Entity_Id;
8139             E_Id : Entity_Id;
8140
8141          begin
8142             Check_Ada_83_Warning;
8143
8144             --  Deal with configuration pragma case
8145
8146             if Arg_Count = 0 and then Is_Configuration_Pragma then
8147                Global_Discard_Names := True;
8148                return;
8149
8150             --  Otherwise, check correct appropriate context
8151
8152             else
8153                Check_Is_In_Decl_Part_Or_Package_Spec;
8154
8155                if Arg_Count = 0 then
8156
8157                   --  If there is no parameter, then from now on this pragma
8158                   --  applies to any enumeration, exception or tagged type
8159                   --  defined in the current declarative part, and recursively
8160                   --  to any nested scope.
8161
8162                   Set_Discard_Names (Current_Scope);
8163                   return;
8164
8165                else
8166                   Check_Arg_Count (1);
8167                   Check_Optional_Identifier (Arg1, Name_On);
8168                   Check_Arg_Is_Local_Name (Arg1);
8169
8170                   E_Id := Get_Pragma_Arg (Arg1);
8171
8172                   if Etype (E_Id) = Any_Type then
8173                      return;
8174                   else
8175                      E := Entity (E_Id);
8176                   end if;
8177
8178                   if (Is_First_Subtype (E)
8179                       and then
8180                         (Is_Enumeration_Type (E) or else Is_Tagged_Type (E)))
8181                     or else Ekind (E) = E_Exception
8182                   then
8183                      Set_Discard_Names (E);
8184                   else
8185                      Error_Pragma_Arg
8186                        ("inappropriate entity for pragma%", Arg1);
8187                   end if;
8188
8189                end if;
8190             end if;
8191          end Discard_Names;
8192
8193          ------------------------
8194          -- Dispatching_Domain --
8195          ------------------------
8196
8197          --  pragma Dispatching_Domain (EXPRESSION);
8198
8199          when Pragma_Dispatching_Domain => Dispatching_Domain : declare
8200             P   : constant Node_Id := Parent (N);
8201             Arg : Node_Id;
8202
8203          begin
8204             Ada_2012_Pragma;
8205             Check_No_Identifiers;
8206             Check_Arg_Count (1);
8207
8208             --  This pragma is born obsolete, but not the aspect
8209
8210             if not From_Aspect_Specification (N) then
8211                Check_Restriction
8212                  (No_Obsolescent_Features, Pragma_Identifier (N));
8213             end if;
8214
8215             if Nkind (P) = N_Task_Definition then
8216                Arg := Get_Pragma_Arg (Arg1);
8217
8218                --  The expression must be analyzed in the special manner
8219                --  described in "Handling of Default and Per-Object
8220                --  Expressions" in sem.ads.
8221
8222                Preanalyze_Spec_Expression (Arg, RTE (RE_Dispatching_Domain));
8223
8224             --  Anything else is incorrect
8225
8226             else
8227                Pragma_Misplaced;
8228             end if;
8229
8230             if Has_Pragma_Dispatching_Domain (P) then
8231                Error_Pragma ("duplicate pragma% not allowed");
8232             else
8233                Set_Has_Pragma_Dispatching_Domain (P, True);
8234
8235                if Nkind (P) = N_Task_Definition then
8236                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
8237                end if;
8238             end if;
8239          end Dispatching_Domain;
8240
8241          ---------------
8242          -- Elaborate --
8243          ---------------
8244
8245          --  pragma Elaborate (library_unit_NAME {, library_unit_NAME});
8246
8247          when Pragma_Elaborate => Elaborate : declare
8248             Arg   : Node_Id;
8249             Citem : Node_Id;
8250
8251          begin
8252             --  Pragma must be in context items list of a compilation unit
8253
8254             if not Is_In_Context_Clause then
8255                Pragma_Misplaced;
8256             end if;
8257
8258             --  Must be at least one argument
8259
8260             if Arg_Count = 0 then
8261                Error_Pragma ("pragma% requires at least one argument");
8262             end if;
8263
8264             --  In Ada 83 mode, there can be no items following it in the
8265             --  context list except other pragmas and implicit with clauses
8266             --  (e.g. those added by use of Rtsfind). In Ada 95 mode, this
8267             --  placement rule does not apply.
8268
8269             if Ada_Version = Ada_83 and then Comes_From_Source (N) then
8270                Citem := Next (N);
8271                while Present (Citem) loop
8272                   if Nkind (Citem) = N_Pragma
8273                     or else (Nkind (Citem) = N_With_Clause
8274                               and then Implicit_With (Citem))
8275                   then
8276                      null;
8277                   else
8278                      Error_Pragma
8279                        ("(Ada 83) pragma% must be at end of context clause");
8280                   end if;
8281
8282                   Next (Citem);
8283                end loop;
8284             end if;
8285
8286             --  Finally, the arguments must all be units mentioned in a with
8287             --  clause in the same context clause. Note we already checked (in
8288             --  Par.Prag) that the arguments are all identifiers or selected
8289             --  components.
8290
8291             Arg := Arg1;
8292             Outer : while Present (Arg) loop
8293                Citem := First (List_Containing (N));
8294                Inner : while Citem /= N loop
8295                   if Nkind (Citem) = N_With_Clause
8296                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8297                   then
8298                      Set_Elaborate_Present (Citem, True);
8299                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8300                      Generate_Reference (Entity (Name (Citem)), Citem);
8301
8302                      --  With the pragma present, elaboration calls on
8303                      --  subprograms from the named unit need no further
8304                      --  checks, as long as the pragma appears in the current
8305                      --  compilation unit. If the pragma appears in some unit
8306                      --  in the context, there might still be a need for an
8307                      --  Elaborate_All_Desirable from the current compilation
8308                      --  to the named unit, so we keep the check enabled.
8309
8310                      if In_Extended_Main_Source_Unit (N) then
8311                         Set_Suppress_Elaboration_Warnings
8312                           (Entity (Name (Citem)));
8313                      end if;
8314
8315                      exit Inner;
8316                   end if;
8317
8318                   Next (Citem);
8319                end loop Inner;
8320
8321                if Citem = N then
8322                   Error_Pragma_Arg
8323                     ("argument of pragma% is not withed unit", Arg);
8324                end if;
8325
8326                Next (Arg);
8327             end loop Outer;
8328
8329             --  Give a warning if operating in static mode with -gnatwl
8330             --  (elaboration warnings enabled) switch set.
8331
8332             if Elab_Warnings and not Dynamic_Elaboration_Checks then
8333                Error_Msg_N
8334                  ("?use of pragma Elaborate may not be safe", N);
8335                Error_Msg_N
8336                  ("?use pragma Elaborate_All instead if possible", N);
8337             end if;
8338          end Elaborate;
8339
8340          -------------------
8341          -- Elaborate_All --
8342          -------------------
8343
8344          --  pragma Elaborate_All (library_unit_NAME {, library_unit_NAME});
8345
8346          when Pragma_Elaborate_All => Elaborate_All : declare
8347             Arg   : Node_Id;
8348             Citem : Node_Id;
8349
8350          begin
8351             Check_Ada_83_Warning;
8352
8353             --  Pragma must be in context items list of a compilation unit
8354
8355             if not Is_In_Context_Clause then
8356                Pragma_Misplaced;
8357             end if;
8358
8359             --  Must be at least one argument
8360
8361             if Arg_Count = 0 then
8362                Error_Pragma ("pragma% requires at least one argument");
8363             end if;
8364
8365             --  Note: unlike pragma Elaborate, pragma Elaborate_All does not
8366             --  have to appear at the end of the context clause, but may
8367             --  appear mixed in with other items, even in Ada 83 mode.
8368
8369             --  Final check: the arguments must all be units mentioned in
8370             --  a with clause in the same context clause. Note that we
8371             --  already checked (in Par.Prag) that all the arguments are
8372             --  either identifiers or selected components.
8373
8374             Arg := Arg1;
8375             Outr : while Present (Arg) loop
8376                Citem := First (List_Containing (N));
8377                Innr : while Citem /= N loop
8378                   if Nkind (Citem) = N_With_Clause
8379                     and then Same_Name (Name (Citem), Get_Pragma_Arg (Arg))
8380                   then
8381                      Set_Elaborate_All_Present (Citem, True);
8382                      Set_Unit_Name (Get_Pragma_Arg (Arg), Name (Citem));
8383
8384                      --  Suppress warnings and elaboration checks on the named
8385                      --  unit if the pragma is in the current compilation, as
8386                      --  for pragma Elaborate.
8387
8388                      if In_Extended_Main_Source_Unit (N) then
8389                         Set_Suppress_Elaboration_Warnings
8390                           (Entity (Name (Citem)));
8391                      end if;
8392                      exit Innr;
8393                   end if;
8394
8395                   Next (Citem);
8396                end loop Innr;
8397
8398                if Citem = N then
8399                   Set_Error_Posted (N);
8400                   Error_Pragma_Arg
8401                     ("argument of pragma% is not withed unit", Arg);
8402                end if;
8403
8404                Next (Arg);
8405             end loop Outr;
8406          end Elaborate_All;
8407
8408          --------------------
8409          -- Elaborate_Body --
8410          --------------------
8411
8412          --  pragma Elaborate_Body [( library_unit_NAME )];
8413
8414          when Pragma_Elaborate_Body => Elaborate_Body : declare
8415             Cunit_Node : Node_Id;
8416             Cunit_Ent  : Entity_Id;
8417
8418          begin
8419             Check_Ada_83_Warning;
8420             Check_Valid_Library_Unit_Pragma;
8421
8422             if Nkind (N) = N_Null_Statement then
8423                return;
8424             end if;
8425
8426             Cunit_Node := Cunit (Current_Sem_Unit);
8427             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
8428
8429             if Nkind_In (Unit (Cunit_Node), N_Package_Body,
8430                                             N_Subprogram_Body)
8431             then
8432                Error_Pragma ("pragma% must refer to a spec, not a body");
8433             else
8434                Set_Body_Required (Cunit_Node, True);
8435                Set_Has_Pragma_Elaborate_Body (Cunit_Ent);
8436
8437                --  If we are in dynamic elaboration mode, then we suppress
8438                --  elaboration warnings for the unit, since it is definitely
8439                --  fine NOT to do dynamic checks at the first level (and such
8440                --  checks will be suppressed because no elaboration boolean
8441                --  is created for Elaborate_Body packages).
8442
8443                --  But in the static model of elaboration, Elaborate_Body is
8444                --  definitely NOT good enough to ensure elaboration safety on
8445                --  its own, since the body may WITH other units that are not
8446                --  safe from an elaboration point of view, so a client must
8447                --  still do an Elaborate_All on such units.
8448
8449                --  Debug flag -gnatdD restores the old behavior of 3.13, where
8450                --  Elaborate_Body always suppressed elab warnings.
8451
8452                if Dynamic_Elaboration_Checks or Debug_Flag_DD then
8453                   Set_Suppress_Elaboration_Warnings (Cunit_Ent);
8454                end if;
8455             end if;
8456          end Elaborate_Body;
8457
8458          ------------------------
8459          -- Elaboration_Checks --
8460          ------------------------
8461
8462          --  pragma Elaboration_Checks (Static | Dynamic);
8463
8464          when Pragma_Elaboration_Checks =>
8465             GNAT_Pragma;
8466             Check_Arg_Count (1);
8467             Check_Arg_Is_One_Of (Arg1, Name_Static, Name_Dynamic);
8468             Dynamic_Elaboration_Checks :=
8469               (Chars (Get_Pragma_Arg (Arg1)) = Name_Dynamic);
8470
8471          ---------------
8472          -- Eliminate --
8473          ---------------
8474
8475          --  pragma Eliminate (
8476          --      [Unit_Name  =>] IDENTIFIER | SELECTED_COMPONENT,
8477          --    [,[Entity     =>] IDENTIFIER |
8478          --                      SELECTED_COMPONENT |
8479          --                      STRING_LITERAL]
8480          --    [,                OVERLOADING_RESOLUTION]);
8481
8482          --  OVERLOADING_RESOLUTION ::= PARAMETER_AND_RESULT_TYPE_PROFILE |
8483          --                             SOURCE_LOCATION
8484
8485          --  PARAMETER_AND_RESULT_TYPE_PROFILE ::= PROCEDURE_PROFILE |
8486          --                                        FUNCTION_PROFILE
8487
8488          --  PROCEDURE_PROFILE ::= Parameter_Types => PARAMETER_TYPES
8489
8490          --  FUNCTION_PROFILE ::= [Parameter_Types => PARAMETER_TYPES,]
8491          --                       Result_Type => result_SUBTYPE_NAME]
8492
8493          --  PARAMETER_TYPES ::= (SUBTYPE_NAME {, SUBTYPE_NAME})
8494          --  SUBTYPE_NAME    ::= STRING_LITERAL
8495
8496          --  SOURCE_LOCATION ::= Source_Location => SOURCE_TRACE
8497          --  SOURCE_TRACE    ::= STRING_LITERAL
8498
8499          when Pragma_Eliminate => Eliminate : declare
8500             Args  : Args_List (1 .. 5);
8501             Names : constant Name_List (1 .. 5) := (
8502                       Name_Unit_Name,
8503                       Name_Entity,
8504                       Name_Parameter_Types,
8505                       Name_Result_Type,
8506                       Name_Source_Location);
8507
8508             Unit_Name       : Node_Id renames Args (1);
8509             Entity          : Node_Id renames Args (2);
8510             Parameter_Types : Node_Id renames Args (3);
8511             Result_Type     : Node_Id renames Args (4);
8512             Source_Location : Node_Id renames Args (5);
8513
8514          begin
8515             GNAT_Pragma;
8516             Check_Valid_Configuration_Pragma;
8517             Gather_Associations (Names, Args);
8518
8519             if No (Unit_Name) then
8520                Error_Pragma ("missing Unit_Name argument for pragma%");
8521             end if;
8522
8523             if No (Entity)
8524               and then (Present (Parameter_Types)
8525                           or else
8526                         Present (Result_Type)
8527                           or else
8528                         Present (Source_Location))
8529             then
8530                Error_Pragma ("missing Entity argument for pragma%");
8531             end if;
8532
8533             if (Present (Parameter_Types)
8534                   or else
8535                 Present (Result_Type))
8536               and then
8537                 Present (Source_Location)
8538             then
8539                Error_Pragma
8540                  ("parameter profile and source location cannot " &
8541                   "be used together in pragma%");
8542             end if;
8543
8544             Process_Eliminate_Pragma
8545               (N,
8546                Unit_Name,
8547                Entity,
8548                Parameter_Types,
8549                Result_Type,
8550                Source_Location);
8551          end Eliminate;
8552
8553          -----------------------------------
8554          -- Enable_Atomic_Synchronization --
8555          -----------------------------------
8556
8557          --  pragma Enable_Atomic_Synchronization [(Entity)];
8558
8559          when Pragma_Enable_Atomic_Synchronization =>
8560             Process_Disable_Enable_Atomic_Sync (Name_Unsuppress);
8561
8562          ------------
8563          -- Export --
8564          ------------
8565
8566          --  pragma Export (
8567          --    [   Convention    =>] convention_IDENTIFIER,
8568          --    [   Entity        =>] local_NAME
8569          --    [, [External_Name =>] static_string_EXPRESSION ]
8570          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8571
8572          when Pragma_Export => Export : declare
8573             C      : Convention_Id;
8574             Def_Id : Entity_Id;
8575
8576             pragma Warnings (Off, C);
8577
8578          begin
8579             Check_Ada_83_Warning;
8580             Check_Arg_Order
8581               ((Name_Convention,
8582                 Name_Entity,
8583                 Name_External_Name,
8584                 Name_Link_Name));
8585             Check_At_Least_N_Arguments (2);
8586             Check_At_Most_N_Arguments  (4);
8587             Process_Convention (C, Def_Id);
8588
8589             if Ekind (Def_Id) /= E_Constant then
8590                Note_Possible_Modification
8591                  (Get_Pragma_Arg (Arg2), Sure => False);
8592             end if;
8593
8594             Process_Interface_Name (Def_Id, Arg3, Arg4);
8595             Set_Exported (Def_Id, Arg2);
8596
8597             --  If the entity is a deferred constant, propagate the information
8598             --  to the full view, because gigi elaborates the full view only.
8599
8600             if Ekind (Def_Id) = E_Constant
8601               and then Present (Full_View (Def_Id))
8602             then
8603                declare
8604                   Id2 : constant Entity_Id := Full_View (Def_Id);
8605                begin
8606                   Set_Is_Exported    (Id2, Is_Exported          (Def_Id));
8607                   Set_First_Rep_Item (Id2, First_Rep_Item       (Def_Id));
8608                   Set_Interface_Name (Id2, Einfo.Interface_Name (Def_Id));
8609                end;
8610             end if;
8611          end Export;
8612
8613          ----------------------
8614          -- Export_Exception --
8615          ----------------------
8616
8617          --  pragma Export_Exception (
8618          --        [Internal         =>] LOCAL_NAME
8619          --     [, [External         =>] EXTERNAL_SYMBOL]
8620          --     [, [Form     =>] Ada | VMS]
8621          --     [, [Code     =>] static_integer_EXPRESSION]);
8622
8623          when Pragma_Export_Exception => Export_Exception : declare
8624             Args  : Args_List (1 .. 4);
8625             Names : constant Name_List (1 .. 4) := (
8626                       Name_Internal,
8627                       Name_External,
8628                       Name_Form,
8629                       Name_Code);
8630
8631             Internal : Node_Id renames Args (1);
8632             External : Node_Id renames Args (2);
8633             Form     : Node_Id renames Args (3);
8634             Code     : Node_Id renames Args (4);
8635
8636          begin
8637             GNAT_Pragma;
8638
8639             if Inside_A_Generic then
8640                Error_Pragma ("pragma% cannot be used for generic entities");
8641             end if;
8642
8643             Gather_Associations (Names, Args);
8644             Process_Extended_Import_Export_Exception_Pragma (
8645               Arg_Internal => Internal,
8646               Arg_External => External,
8647               Arg_Form     => Form,
8648               Arg_Code     => Code);
8649
8650             if not Is_VMS_Exception (Entity (Internal)) then
8651                Set_Exported (Entity (Internal), Internal);
8652             end if;
8653          end Export_Exception;
8654
8655          ---------------------
8656          -- Export_Function --
8657          ---------------------
8658
8659          --  pragma Export_Function (
8660          --        [Internal         =>] LOCAL_NAME
8661          --     [, [External         =>] EXTERNAL_SYMBOL]
8662          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8663          --     [, [Result_Type      =>] TYPE_DESIGNATOR]
8664          --     [, [Mechanism        =>] MECHANISM]
8665          --     [, [Result_Mechanism =>] MECHANISM_NAME]);
8666
8667          --  EXTERNAL_SYMBOL ::=
8668          --    IDENTIFIER
8669          --  | static_string_EXPRESSION
8670
8671          --  PARAMETER_TYPES ::=
8672          --    null
8673          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8674
8675          --  TYPE_DESIGNATOR ::=
8676          --    subtype_NAME
8677          --  | subtype_Name ' Access
8678
8679          --  MECHANISM ::=
8680          --    MECHANISM_NAME
8681          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8682
8683          --  MECHANISM_ASSOCIATION ::=
8684          --    [formal_parameter_NAME =>] MECHANISM_NAME
8685
8686          --  MECHANISM_NAME ::=
8687          --    Value
8688          --  | Reference
8689          --  | Descriptor [([Class =>] CLASS_NAME)]
8690
8691          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8692
8693          when Pragma_Export_Function => Export_Function : declare
8694             Args  : Args_List (1 .. 6);
8695             Names : constant Name_List (1 .. 6) := (
8696                       Name_Internal,
8697                       Name_External,
8698                       Name_Parameter_Types,
8699                       Name_Result_Type,
8700                       Name_Mechanism,
8701                       Name_Result_Mechanism);
8702
8703             Internal         : Node_Id renames Args (1);
8704             External         : Node_Id renames Args (2);
8705             Parameter_Types  : Node_Id renames Args (3);
8706             Result_Type      : Node_Id renames Args (4);
8707             Mechanism        : Node_Id renames Args (5);
8708             Result_Mechanism : Node_Id renames Args (6);
8709
8710          begin
8711             GNAT_Pragma;
8712             Gather_Associations (Names, Args);
8713             Process_Extended_Import_Export_Subprogram_Pragma (
8714               Arg_Internal         => Internal,
8715               Arg_External         => External,
8716               Arg_Parameter_Types  => Parameter_Types,
8717               Arg_Result_Type      => Result_Type,
8718               Arg_Mechanism        => Mechanism,
8719               Arg_Result_Mechanism => Result_Mechanism);
8720          end Export_Function;
8721
8722          -------------------
8723          -- Export_Object --
8724          -------------------
8725
8726          --  pragma Export_Object (
8727          --        [Internal =>] LOCAL_NAME
8728          --     [, [External =>] EXTERNAL_SYMBOL]
8729          --     [, [Size     =>] EXTERNAL_SYMBOL]);
8730
8731          --  EXTERNAL_SYMBOL ::=
8732          --    IDENTIFIER
8733          --  | static_string_EXPRESSION
8734
8735          --  PARAMETER_TYPES ::=
8736          --    null
8737          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8738
8739          --  TYPE_DESIGNATOR ::=
8740          --    subtype_NAME
8741          --  | subtype_Name ' Access
8742
8743          --  MECHANISM ::=
8744          --    MECHANISM_NAME
8745          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8746
8747          --  MECHANISM_ASSOCIATION ::=
8748          --    [formal_parameter_NAME =>] MECHANISM_NAME
8749
8750          --  MECHANISM_NAME ::=
8751          --    Value
8752          --  | Reference
8753          --  | Descriptor [([Class =>] CLASS_NAME)]
8754
8755          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8756
8757          when Pragma_Export_Object => Export_Object : declare
8758             Args  : Args_List (1 .. 3);
8759             Names : constant Name_List (1 .. 3) := (
8760                       Name_Internal,
8761                       Name_External,
8762                       Name_Size);
8763
8764             Internal : Node_Id renames Args (1);
8765             External : Node_Id renames Args (2);
8766             Size     : Node_Id renames Args (3);
8767
8768          begin
8769             GNAT_Pragma;
8770             Gather_Associations (Names, Args);
8771             Process_Extended_Import_Export_Object_Pragma (
8772               Arg_Internal => Internal,
8773               Arg_External => External,
8774               Arg_Size     => Size);
8775          end Export_Object;
8776
8777          ----------------------
8778          -- Export_Procedure --
8779          ----------------------
8780
8781          --  pragma Export_Procedure (
8782          --        [Internal         =>] LOCAL_NAME
8783          --     [, [External         =>] EXTERNAL_SYMBOL]
8784          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8785          --     [, [Mechanism        =>] MECHANISM]);
8786
8787          --  EXTERNAL_SYMBOL ::=
8788          --    IDENTIFIER
8789          --  | static_string_EXPRESSION
8790
8791          --  PARAMETER_TYPES ::=
8792          --    null
8793          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8794
8795          --  TYPE_DESIGNATOR ::=
8796          --    subtype_NAME
8797          --  | subtype_Name ' Access
8798
8799          --  MECHANISM ::=
8800          --    MECHANISM_NAME
8801          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8802
8803          --  MECHANISM_ASSOCIATION ::=
8804          --    [formal_parameter_NAME =>] MECHANISM_NAME
8805
8806          --  MECHANISM_NAME ::=
8807          --    Value
8808          --  | Reference
8809          --  | Descriptor [([Class =>] CLASS_NAME)]
8810
8811          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8812
8813          when Pragma_Export_Procedure => Export_Procedure : declare
8814             Args  : Args_List (1 .. 4);
8815             Names : constant Name_List (1 .. 4) := (
8816                       Name_Internal,
8817                       Name_External,
8818                       Name_Parameter_Types,
8819                       Name_Mechanism);
8820
8821             Internal        : Node_Id renames Args (1);
8822             External        : Node_Id renames Args (2);
8823             Parameter_Types : Node_Id renames Args (3);
8824             Mechanism       : Node_Id renames Args (4);
8825
8826          begin
8827             GNAT_Pragma;
8828             Gather_Associations (Names, Args);
8829             Process_Extended_Import_Export_Subprogram_Pragma (
8830               Arg_Internal        => Internal,
8831               Arg_External        => External,
8832               Arg_Parameter_Types => Parameter_Types,
8833               Arg_Mechanism       => Mechanism);
8834          end Export_Procedure;
8835
8836          ------------------
8837          -- Export_Value --
8838          ------------------
8839
8840          --  pragma Export_Value (
8841          --     [Value     =>] static_integer_EXPRESSION,
8842          --     [Link_Name =>] static_string_EXPRESSION);
8843
8844          when Pragma_Export_Value =>
8845             GNAT_Pragma;
8846             Check_Arg_Order ((Name_Value, Name_Link_Name));
8847             Check_Arg_Count (2);
8848
8849             Check_Optional_Identifier (Arg1, Name_Value);
8850             Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
8851
8852             Check_Optional_Identifier (Arg2, Name_Link_Name);
8853             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
8854
8855          -----------------------------
8856          -- Export_Valued_Procedure --
8857          -----------------------------
8858
8859          --  pragma Export_Valued_Procedure (
8860          --        [Internal         =>] LOCAL_NAME
8861          --     [, [External         =>] EXTERNAL_SYMBOL,]
8862          --     [, [Parameter_Types  =>] (PARAMETER_TYPES)]
8863          --     [, [Mechanism        =>] MECHANISM]);
8864
8865          --  EXTERNAL_SYMBOL ::=
8866          --    IDENTIFIER
8867          --  | static_string_EXPRESSION
8868
8869          --  PARAMETER_TYPES ::=
8870          --    null
8871          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
8872
8873          --  TYPE_DESIGNATOR ::=
8874          --    subtype_NAME
8875          --  | subtype_Name ' Access
8876
8877          --  MECHANISM ::=
8878          --    MECHANISM_NAME
8879          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
8880
8881          --  MECHANISM_ASSOCIATION ::=
8882          --    [formal_parameter_NAME =>] MECHANISM_NAME
8883
8884          --  MECHANISM_NAME ::=
8885          --    Value
8886          --  | Reference
8887          --  | Descriptor [([Class =>] CLASS_NAME)]
8888
8889          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
8890
8891          when Pragma_Export_Valued_Procedure =>
8892          Export_Valued_Procedure : declare
8893             Args  : Args_List (1 .. 4);
8894             Names : constant Name_List (1 .. 4) := (
8895                       Name_Internal,
8896                       Name_External,
8897                       Name_Parameter_Types,
8898                       Name_Mechanism);
8899
8900             Internal        : Node_Id renames Args (1);
8901             External        : Node_Id renames Args (2);
8902             Parameter_Types : Node_Id renames Args (3);
8903             Mechanism       : Node_Id renames Args (4);
8904
8905          begin
8906             GNAT_Pragma;
8907             Gather_Associations (Names, Args);
8908             Process_Extended_Import_Export_Subprogram_Pragma (
8909               Arg_Internal        => Internal,
8910               Arg_External        => External,
8911               Arg_Parameter_Types => Parameter_Types,
8912               Arg_Mechanism       => Mechanism);
8913          end Export_Valued_Procedure;
8914
8915          -------------------
8916          -- Extend_System --
8917          -------------------
8918
8919          --  pragma Extend_System ([Name =>] Identifier);
8920
8921          when Pragma_Extend_System => Extend_System : declare
8922          begin
8923             GNAT_Pragma;
8924             Check_Valid_Configuration_Pragma;
8925             Check_Arg_Count (1);
8926             Check_Optional_Identifier (Arg1, Name_Name);
8927             Check_Arg_Is_Identifier (Arg1);
8928
8929             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
8930
8931             if Name_Len > 4
8932               and then Name_Buffer (1 .. 4) = "aux_"
8933             then
8934                if Present (System_Extend_Pragma_Arg) then
8935                   if Chars (Get_Pragma_Arg (Arg1)) =
8936                      Chars (Expression (System_Extend_Pragma_Arg))
8937                   then
8938                      null;
8939                   else
8940                      Error_Msg_Sloc := Sloc (System_Extend_Pragma_Arg);
8941                      Error_Pragma ("pragma% conflicts with that #");
8942                   end if;
8943
8944                else
8945                   System_Extend_Pragma_Arg := Arg1;
8946
8947                   if not GNAT_Mode then
8948                      System_Extend_Unit := Arg1;
8949                   end if;
8950                end if;
8951             else
8952                Error_Pragma ("incorrect name for pragma%, must be Aux_xxx");
8953             end if;
8954          end Extend_System;
8955
8956          ------------------------
8957          -- Extensions_Allowed --
8958          ------------------------
8959
8960          --  pragma Extensions_Allowed (ON | OFF);
8961
8962          when Pragma_Extensions_Allowed =>
8963             GNAT_Pragma;
8964             Check_Arg_Count (1);
8965             Check_No_Identifiers;
8966             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
8967
8968             if Chars (Get_Pragma_Arg (Arg1)) = Name_On then
8969                Extensions_Allowed := True;
8970                Ada_Version := Ada_Version_Type'Last;
8971
8972             else
8973                Extensions_Allowed := False;
8974                Ada_Version := Ada_Version_Explicit;
8975             end if;
8976
8977          --------------
8978          -- External --
8979          --------------
8980
8981          --  pragma External (
8982          --    [   Convention    =>] convention_IDENTIFIER,
8983          --    [   Entity        =>] local_NAME
8984          --    [, [External_Name =>] static_string_EXPRESSION ]
8985          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
8986
8987          when Pragma_External => External : declare
8988                Def_Id : Entity_Id;
8989
8990                C : Convention_Id;
8991                pragma Warnings (Off, C);
8992
8993          begin
8994             GNAT_Pragma;
8995             Check_Arg_Order
8996               ((Name_Convention,
8997                 Name_Entity,
8998                 Name_External_Name,
8999                 Name_Link_Name));
9000             Check_At_Least_N_Arguments (2);
9001             Check_At_Most_N_Arguments  (4);
9002             Process_Convention (C, Def_Id);
9003             Note_Possible_Modification
9004               (Get_Pragma_Arg (Arg2), Sure => False);
9005             Process_Interface_Name (Def_Id, Arg3, Arg4);
9006             Set_Exported (Def_Id, Arg2);
9007          end External;
9008
9009          --------------------------
9010          -- External_Name_Casing --
9011          --------------------------
9012
9013          --  pragma External_Name_Casing (
9014          --    UPPERCASE | LOWERCASE
9015          --    [, AS_IS | UPPERCASE | LOWERCASE]);
9016
9017          when Pragma_External_Name_Casing => External_Name_Casing : declare
9018          begin
9019             GNAT_Pragma;
9020             Check_No_Identifiers;
9021
9022             if Arg_Count = 2 then
9023                Check_Arg_Is_One_Of
9024                  (Arg2, Name_As_Is, Name_Uppercase, Name_Lowercase);
9025
9026                case Chars (Get_Pragma_Arg (Arg2)) is
9027                   when Name_As_Is     =>
9028                      Opt.External_Name_Exp_Casing := As_Is;
9029
9030                   when Name_Uppercase =>
9031                      Opt.External_Name_Exp_Casing := Uppercase;
9032
9033                   when Name_Lowercase =>
9034                      Opt.External_Name_Exp_Casing := Lowercase;
9035
9036                   when others =>
9037                      null;
9038                end case;
9039
9040             else
9041                Check_Arg_Count (1);
9042             end if;
9043
9044             Check_Arg_Is_One_Of (Arg1, Name_Uppercase, Name_Lowercase);
9045
9046             case Chars (Get_Pragma_Arg (Arg1)) is
9047                when Name_Uppercase =>
9048                   Opt.External_Name_Imp_Casing := Uppercase;
9049
9050                when Name_Lowercase =>
9051                   Opt.External_Name_Imp_Casing := Lowercase;
9052
9053                when others =>
9054                   null;
9055             end case;
9056          end External_Name_Casing;
9057
9058          --------------------------
9059          -- Favor_Top_Level --
9060          --------------------------
9061
9062          --  pragma Favor_Top_Level (type_NAME);
9063
9064          when Pragma_Favor_Top_Level => Favor_Top_Level : declare
9065                Named_Entity : Entity_Id;
9066
9067          begin
9068             GNAT_Pragma;
9069             Check_No_Identifiers;
9070             Check_Arg_Count (1);
9071             Check_Arg_Is_Local_Name (Arg1);
9072             Named_Entity := Entity (Get_Pragma_Arg (Arg1));
9073
9074             --  If it's an access-to-subprogram type (in particular, not a
9075             --  subtype), set the flag on that type.
9076
9077             if Is_Access_Subprogram_Type (Named_Entity) then
9078                Set_Can_Use_Internal_Rep (Named_Entity, False);
9079
9080             --  Otherwise it's an error (name denotes the wrong sort of entity)
9081
9082             else
9083                Error_Pragma_Arg
9084                  ("access-to-subprogram type expected",
9085                   Get_Pragma_Arg (Arg1));
9086             end if;
9087          end Favor_Top_Level;
9088
9089          ---------------
9090          -- Fast_Math --
9091          ---------------
9092
9093          --  pragma Fast_Math;
9094
9095          when Pragma_Fast_Math =>
9096             GNAT_Pragma;
9097             Check_No_Identifiers;
9098             Check_Valid_Configuration_Pragma;
9099             Fast_Math := True;
9100
9101          ---------------------------
9102          -- Finalize_Storage_Only --
9103          ---------------------------
9104
9105          --  pragma Finalize_Storage_Only (first_subtype_LOCAL_NAME);
9106
9107          when Pragma_Finalize_Storage_Only => Finalize_Storage : declare
9108             Assoc   : constant Node_Id := Arg1;
9109             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
9110             Typ     : Entity_Id;
9111
9112          begin
9113             GNAT_Pragma;
9114             Check_No_Identifiers;
9115             Check_Arg_Count (1);
9116             Check_Arg_Is_Local_Name (Arg1);
9117
9118             Find_Type (Type_Id);
9119             Typ := Entity (Type_Id);
9120
9121             if Typ = Any_Type
9122               or else Rep_Item_Too_Early (Typ, N)
9123             then
9124                return;
9125             else
9126                Typ := Underlying_Type (Typ);
9127             end if;
9128
9129             if not Is_Controlled (Typ) then
9130                Error_Pragma ("pragma% must specify controlled type");
9131             end if;
9132
9133             Check_First_Subtype (Arg1);
9134
9135             if Finalize_Storage_Only (Typ) then
9136                Error_Pragma ("duplicate pragma%, only one allowed");
9137
9138             elsif not Rep_Item_Too_Late (Typ, N) then
9139                Set_Finalize_Storage_Only (Base_Type (Typ), True);
9140             end if;
9141          end Finalize_Storage;
9142
9143          --------------------------
9144          -- Float_Representation --
9145          --------------------------
9146
9147          --  pragma Float_Representation (FLOAT_REP[, float_type_LOCAL_NAME]);
9148
9149          --  FLOAT_REP ::= VAX_Float | IEEE_Float
9150
9151          when Pragma_Float_Representation => Float_Representation : declare
9152             Argx : Node_Id;
9153             Digs : Nat;
9154             Ent  : Entity_Id;
9155
9156          begin
9157             GNAT_Pragma;
9158
9159             if Arg_Count = 1 then
9160                Check_Valid_Configuration_Pragma;
9161             else
9162                Check_Arg_Count (2);
9163                Check_Optional_Identifier (Arg2, Name_Entity);
9164                Check_Arg_Is_Local_Name (Arg2);
9165             end if;
9166
9167             Check_No_Identifier (Arg1);
9168             Check_Arg_Is_One_Of (Arg1, Name_VAX_Float, Name_IEEE_Float);
9169
9170             if not OpenVMS_On_Target then
9171                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9172                   Error_Pragma
9173                     ("?pragma% ignored (applies only to Open'V'M'S)");
9174                end if;
9175
9176                return;
9177             end if;
9178
9179             --  One argument case
9180
9181             if Arg_Count = 1 then
9182                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9183                   if Opt.Float_Format = 'I' then
9184                      Error_Pragma ("'I'E'E'E format previously specified");
9185                   end if;
9186
9187                   Opt.Float_Format := 'V';
9188
9189                else
9190                   if Opt.Float_Format = 'V' then
9191                      Error_Pragma ("'V'A'X format previously specified");
9192                   end if;
9193
9194                   Opt.Float_Format := 'I';
9195                end if;
9196
9197                Set_Standard_Fpt_Formats;
9198
9199             --  Two argument case
9200
9201             else
9202                Argx := Get_Pragma_Arg (Arg2);
9203
9204                if not Is_Entity_Name (Argx)
9205                  or else not Is_Floating_Point_Type (Entity (Argx))
9206                then
9207                   Error_Pragma_Arg
9208                     ("second argument of% pragma must be floating-point type",
9209                      Arg2);
9210                end if;
9211
9212                Ent  := Entity (Argx);
9213                Digs := UI_To_Int (Digits_Value (Ent));
9214
9215                --  Two arguments, VAX_Float case
9216
9217                if Chars (Get_Pragma_Arg (Arg1)) = Name_VAX_Float then
9218                   case Digs is
9219                      when  6 => Set_F_Float (Ent);
9220                      when  9 => Set_D_Float (Ent);
9221                      when 15 => Set_G_Float (Ent);
9222
9223                      when others =>
9224                         Error_Pragma_Arg
9225                           ("wrong digits value, must be 6,9 or 15", Arg2);
9226                   end case;
9227
9228                --  Two arguments, IEEE_Float case
9229
9230                else
9231                   case Digs is
9232                      when  6 => Set_IEEE_Short (Ent);
9233                      when 15 => Set_IEEE_Long  (Ent);
9234
9235                      when others =>
9236                         Error_Pragma_Arg
9237                           ("wrong digits value, must be 6 or 15", Arg2);
9238                   end case;
9239                end if;
9240             end if;
9241          end Float_Representation;
9242
9243          -----------
9244          -- Ident --
9245          -----------
9246
9247          --  pragma Ident (static_string_EXPRESSION)
9248
9249          --  Note: pragma Comment shares this processing. Pragma Comment is
9250          --  identical to Ident, except that the restriction of the argument to
9251          --  31 characters and the placement restrictions are not enforced for
9252          --  pragma Comment.
9253
9254          when Pragma_Ident | Pragma_Comment => Ident : declare
9255             Str : Node_Id;
9256
9257          begin
9258             GNAT_Pragma;
9259             Check_Arg_Count (1);
9260             Check_No_Identifiers;
9261             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
9262             Store_Note (N);
9263
9264             --  For pragma Ident, preserve DEC compatibility by requiring the
9265             --  pragma to appear in a declarative part or package spec.
9266
9267             if Prag_Id = Pragma_Ident then
9268                Check_Is_In_Decl_Part_Or_Package_Spec;
9269             end if;
9270
9271             Str := Expr_Value_S (Get_Pragma_Arg (Arg1));
9272
9273             declare
9274                CS : Node_Id;
9275                GP : Node_Id;
9276
9277             begin
9278                GP := Parent (Parent (N));
9279
9280                if Nkind_In (GP, N_Package_Declaration,
9281                                 N_Generic_Package_Declaration)
9282                then
9283                   GP := Parent (GP);
9284                end if;
9285
9286                --  If we have a compilation unit, then record the ident value,
9287                --  checking for improper duplication.
9288
9289                if Nkind (GP) = N_Compilation_Unit then
9290                   CS := Ident_String (Current_Sem_Unit);
9291
9292                   if Present (CS) then
9293
9294                      --  For Ident, we do not permit multiple instances
9295
9296                      if Prag_Id = Pragma_Ident then
9297                         Error_Pragma ("duplicate% pragma not permitted");
9298
9299                      --  For Comment, we concatenate the string, unless we want
9300                      --  to preserve the tree structure for ASIS.
9301
9302                      elsif not ASIS_Mode then
9303                         Start_String (Strval (CS));
9304                         Store_String_Char (' ');
9305                         Store_String_Chars (Strval (Str));
9306                         Set_Strval (CS, End_String);
9307                      end if;
9308
9309                   else
9310                      --  In VMS, the effect of IDENT is achieved by passing
9311                      --  --identification=name as a --for-linker switch.
9312
9313                      if OpenVMS_On_Target then
9314                         Start_String;
9315                         Store_String_Chars
9316                           ("--for-linker=--identification=");
9317                         String_To_Name_Buffer (Strval (Str));
9318                         Store_String_Chars (Name_Buffer (1 .. Name_Len));
9319
9320                         --  Only the last processed IDENT is saved. The main
9321                         --  purpose is so an IDENT associated with a main
9322                         --  procedure will be used in preference to an IDENT
9323                         --  associated with a with'd package.
9324
9325                         Replace_Linker_Option_String
9326                           (End_String, "--for-linker=--identification=");
9327                      end if;
9328
9329                      Set_Ident_String (Current_Sem_Unit, Str);
9330                   end if;
9331
9332                --  For subunits, we just ignore the Ident, since in GNAT these
9333                --  are not separate object files, and hence not separate units
9334                --  in the unit table.
9335
9336                elsif Nkind (GP) = N_Subunit then
9337                   null;
9338
9339                --  Otherwise we have a misplaced pragma Ident, but we ignore
9340                --  this if we are in an instantiation, since it comes from
9341                --  a generic, and has no relevance to the instantiation.
9342
9343                elsif Prag_Id = Pragma_Ident then
9344                   if Instantiation_Location (Loc) = No_Location then
9345                      Error_Pragma ("pragma% only allowed at outer level");
9346                   end if;
9347                end if;
9348             end;
9349          end Ident;
9350
9351          ----------------------------
9352          -- Implementation_Defined --
9353          ----------------------------
9354
9355          --  pragma Implementation_Defined (local_NAME);
9356
9357          --  Marks previously declared entity as implementation defined. For
9358          --  an overloaded entity, applies to the most recent homonym.
9359
9360          --  pragma Implementation_Defined;
9361
9362          --  The form with no arguments appears anywhere within a scope, most
9363          --  typically a package spec, and indicates that all entities that are
9364          --  defined within the package spec are Implementation_Defined.
9365
9366          when Pragma_Implementation_Defined => Implementation_Defined : declare
9367             Ent : Entity_Id;
9368
9369          begin
9370             Check_No_Identifiers;
9371
9372             --  Form with no arguments
9373
9374             if Arg_Count = 0 then
9375                Set_Is_Implementation_Defined (Current_Scope);
9376
9377             --  Form with one argument
9378
9379             else
9380                Check_Arg_Count (1);
9381                Check_Arg_Is_Local_Name (Arg1);
9382                Ent := Entity (Get_Pragma_Arg (Arg1));
9383                Set_Is_Implementation_Defined (Ent);
9384             end if;
9385          end Implementation_Defined;
9386
9387          -----------------
9388          -- Implemented --
9389          -----------------
9390
9391          --  pragma Implemented (procedure_LOCAL_NAME, implementation_kind);
9392          --  implementation_kind ::=
9393          --    By_Entry | By_Protected_Procedure | By_Any | Optional
9394
9395          --  "By_Any" and "Optional" are treated as synonyms in order to
9396          --  support Ada 2012 aspect Synchronization.
9397
9398          when Pragma_Implemented => Implemented : declare
9399             Proc_Id : Entity_Id;
9400             Typ     : Entity_Id;
9401
9402          begin
9403             Ada_2012_Pragma;
9404             Check_Arg_Count (2);
9405             Check_No_Identifiers;
9406             Check_Arg_Is_Identifier (Arg1);
9407             Check_Arg_Is_Local_Name (Arg1);
9408             Check_Arg_Is_One_Of (Arg2,
9409               Name_By_Any,
9410               Name_By_Entry,
9411               Name_By_Protected_Procedure,
9412               Name_Optional);
9413
9414             --  Extract the name of the local procedure
9415
9416             Proc_Id := Entity (Get_Pragma_Arg (Arg1));
9417
9418             --  Ada 2012 (AI05-0030): The procedure_LOCAL_NAME must denote a
9419             --  primitive procedure of a synchronized tagged type.
9420
9421             if Ekind (Proc_Id) = E_Procedure
9422               and then Is_Primitive (Proc_Id)
9423               and then Present (First_Formal (Proc_Id))
9424             then
9425                Typ := Etype (First_Formal (Proc_Id));
9426
9427                if Is_Tagged_Type (Typ)
9428                  and then
9429
9430                   --  Check for a protected, a synchronized or a task interface
9431
9432                    ((Is_Interface (Typ)
9433                        and then Is_Synchronized_Interface (Typ))
9434
9435                   --  Check for a protected type or a task type that implements
9436                   --  an interface.
9437
9438                    or else
9439                     (Is_Concurrent_Record_Type (Typ)
9440                        and then Present (Interfaces (Typ)))
9441
9442                   --  Check for a private record extension with keyword
9443                   --  "synchronized".
9444
9445                    or else
9446                     (Ekind_In (Typ, E_Record_Type_With_Private,
9447                                     E_Record_Subtype_With_Private)
9448                        and then Synchronized_Present (Parent (Typ))))
9449                then
9450                   null;
9451                else
9452                   Error_Pragma_Arg
9453                     ("controlling formal must be of synchronized " &
9454                      "tagged type", Arg1);
9455                   return;
9456                end if;
9457
9458             --  Procedures declared inside a protected type must be accepted
9459
9460             elsif Ekind (Proc_Id) = E_Procedure
9461               and then Is_Protected_Type (Scope (Proc_Id))
9462             then
9463                null;
9464
9465             --  The first argument is not a primitive procedure
9466
9467             else
9468                Error_Pragma_Arg
9469                  ("pragma % must be applied to a primitive procedure", Arg1);
9470                return;
9471             end if;
9472
9473             --  Ada 2012 (AI05-0030): Cannot apply the implementation_kind
9474             --  By_Protected_Procedure to the primitive procedure of a task
9475             --  interface.
9476
9477             if Chars (Arg2) = Name_By_Protected_Procedure
9478               and then Is_Interface (Typ)
9479               and then Is_Task_Interface (Typ)
9480             then
9481                Error_Pragma_Arg
9482                  ("implementation kind By_Protected_Procedure cannot be " &
9483                   "applied to a task interface primitive", Arg2);
9484                return;
9485             end if;
9486
9487             Record_Rep_Item (Proc_Id, N);
9488          end Implemented;
9489
9490          ----------------------
9491          -- Implicit_Packing --
9492          ----------------------
9493
9494          --  pragma Implicit_Packing;
9495
9496          when Pragma_Implicit_Packing =>
9497             GNAT_Pragma;
9498             Check_Arg_Count (0);
9499             Implicit_Packing := True;
9500
9501          ------------
9502          -- Import --
9503          ------------
9504
9505          --  pragma Import (
9506          --       [Convention    =>] convention_IDENTIFIER,
9507          --       [Entity        =>] local_NAME
9508          --    [, [External_Name =>] static_string_EXPRESSION ]
9509          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
9510
9511          when Pragma_Import =>
9512             Check_Ada_83_Warning;
9513             Check_Arg_Order
9514               ((Name_Convention,
9515                 Name_Entity,
9516                 Name_External_Name,
9517                 Name_Link_Name));
9518             Check_At_Least_N_Arguments (2);
9519             Check_At_Most_N_Arguments  (4);
9520             Process_Import_Or_Interface;
9521
9522          ----------------------
9523          -- Import_Exception --
9524          ----------------------
9525
9526          --  pragma Import_Exception (
9527          --        [Internal         =>] LOCAL_NAME
9528          --     [, [External         =>] EXTERNAL_SYMBOL]
9529          --     [, [Form     =>] Ada | VMS]
9530          --     [, [Code     =>] static_integer_EXPRESSION]);
9531
9532          when Pragma_Import_Exception => Import_Exception : declare
9533             Args  : Args_List (1 .. 4);
9534             Names : constant Name_List (1 .. 4) := (
9535                       Name_Internal,
9536                       Name_External,
9537                       Name_Form,
9538                       Name_Code);
9539
9540             Internal : Node_Id renames Args (1);
9541             External : Node_Id renames Args (2);
9542             Form     : Node_Id renames Args (3);
9543             Code     : Node_Id renames Args (4);
9544
9545          begin
9546             GNAT_Pragma;
9547             Gather_Associations (Names, Args);
9548
9549             if Present (External) and then Present (Code) then
9550                Error_Pragma
9551                  ("cannot give both External and Code options for pragma%");
9552             end if;
9553
9554             Process_Extended_Import_Export_Exception_Pragma (
9555               Arg_Internal => Internal,
9556               Arg_External => External,
9557               Arg_Form     => Form,
9558               Arg_Code     => Code);
9559
9560             if not Is_VMS_Exception (Entity (Internal)) then
9561                Set_Imported (Entity (Internal));
9562             end if;
9563          end Import_Exception;
9564
9565          ---------------------
9566          -- Import_Function --
9567          ---------------------
9568
9569          --  pragma Import_Function (
9570          --        [Internal                 =>] LOCAL_NAME,
9571          --     [, [External                 =>] EXTERNAL_SYMBOL]
9572          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9573          --     [, [Result_Type              =>] SUBTYPE_MARK]
9574          --     [, [Mechanism                =>] MECHANISM]
9575          --     [, [Result_Mechanism         =>] MECHANISM_NAME]
9576          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9577
9578          --  EXTERNAL_SYMBOL ::=
9579          --    IDENTIFIER
9580          --  | static_string_EXPRESSION
9581
9582          --  PARAMETER_TYPES ::=
9583          --    null
9584          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9585
9586          --  TYPE_DESIGNATOR ::=
9587          --    subtype_NAME
9588          --  | subtype_Name ' Access
9589
9590          --  MECHANISM ::=
9591          --    MECHANISM_NAME
9592          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9593
9594          --  MECHANISM_ASSOCIATION ::=
9595          --    [formal_parameter_NAME =>] MECHANISM_NAME
9596
9597          --  MECHANISM_NAME ::=
9598          --    Value
9599          --  | Reference
9600          --  | Descriptor [([Class =>] CLASS_NAME)]
9601
9602          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9603
9604          when Pragma_Import_Function => Import_Function : declare
9605             Args  : Args_List (1 .. 7);
9606             Names : constant Name_List (1 .. 7) := (
9607                       Name_Internal,
9608                       Name_External,
9609                       Name_Parameter_Types,
9610                       Name_Result_Type,
9611                       Name_Mechanism,
9612                       Name_Result_Mechanism,
9613                       Name_First_Optional_Parameter);
9614
9615             Internal                 : Node_Id renames Args (1);
9616             External                 : Node_Id renames Args (2);
9617             Parameter_Types          : Node_Id renames Args (3);
9618             Result_Type              : Node_Id renames Args (4);
9619             Mechanism                : Node_Id renames Args (5);
9620             Result_Mechanism         : Node_Id renames Args (6);
9621             First_Optional_Parameter : Node_Id renames Args (7);
9622
9623          begin
9624             GNAT_Pragma;
9625             Gather_Associations (Names, Args);
9626             Process_Extended_Import_Export_Subprogram_Pragma (
9627               Arg_Internal                 => Internal,
9628               Arg_External                 => External,
9629               Arg_Parameter_Types          => Parameter_Types,
9630               Arg_Result_Type              => Result_Type,
9631               Arg_Mechanism                => Mechanism,
9632               Arg_Result_Mechanism         => Result_Mechanism,
9633               Arg_First_Optional_Parameter => First_Optional_Parameter);
9634          end Import_Function;
9635
9636          -------------------
9637          -- Import_Object --
9638          -------------------
9639
9640          --  pragma Import_Object (
9641          --        [Internal =>] LOCAL_NAME
9642          --     [, [External =>] EXTERNAL_SYMBOL]
9643          --     [, [Size     =>] EXTERNAL_SYMBOL]);
9644
9645          --  EXTERNAL_SYMBOL ::=
9646          --    IDENTIFIER
9647          --  | static_string_EXPRESSION
9648
9649          when Pragma_Import_Object => Import_Object : declare
9650             Args  : Args_List (1 .. 3);
9651             Names : constant Name_List (1 .. 3) := (
9652                       Name_Internal,
9653                       Name_External,
9654                       Name_Size);
9655
9656             Internal : Node_Id renames Args (1);
9657             External : Node_Id renames Args (2);
9658             Size     : Node_Id renames Args (3);
9659
9660          begin
9661             GNAT_Pragma;
9662             Gather_Associations (Names, Args);
9663             Process_Extended_Import_Export_Object_Pragma (
9664               Arg_Internal => Internal,
9665               Arg_External => External,
9666               Arg_Size     => Size);
9667          end Import_Object;
9668
9669          ----------------------
9670          -- Import_Procedure --
9671          ----------------------
9672
9673          --  pragma Import_Procedure (
9674          --        [Internal                 =>] LOCAL_NAME
9675          --     [, [External                 =>] EXTERNAL_SYMBOL]
9676          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9677          --     [, [Mechanism                =>] MECHANISM]
9678          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9679
9680          --  EXTERNAL_SYMBOL ::=
9681          --    IDENTIFIER
9682          --  | static_string_EXPRESSION
9683
9684          --  PARAMETER_TYPES ::=
9685          --    null
9686          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9687
9688          --  TYPE_DESIGNATOR ::=
9689          --    subtype_NAME
9690          --  | subtype_Name ' Access
9691
9692          --  MECHANISM ::=
9693          --    MECHANISM_NAME
9694          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9695
9696          --  MECHANISM_ASSOCIATION ::=
9697          --    [formal_parameter_NAME =>] MECHANISM_NAME
9698
9699          --  MECHANISM_NAME ::=
9700          --    Value
9701          --  | Reference
9702          --  | Descriptor [([Class =>] CLASS_NAME)]
9703
9704          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9705
9706          when Pragma_Import_Procedure => Import_Procedure : declare
9707             Args  : Args_List (1 .. 5);
9708             Names : constant Name_List (1 .. 5) := (
9709                       Name_Internal,
9710                       Name_External,
9711                       Name_Parameter_Types,
9712                       Name_Mechanism,
9713                       Name_First_Optional_Parameter);
9714
9715             Internal                 : Node_Id renames Args (1);
9716             External                 : Node_Id renames Args (2);
9717             Parameter_Types          : Node_Id renames Args (3);
9718             Mechanism                : Node_Id renames Args (4);
9719             First_Optional_Parameter : Node_Id renames Args (5);
9720
9721          begin
9722             GNAT_Pragma;
9723             Gather_Associations (Names, Args);
9724             Process_Extended_Import_Export_Subprogram_Pragma (
9725               Arg_Internal                 => Internal,
9726               Arg_External                 => External,
9727               Arg_Parameter_Types          => Parameter_Types,
9728               Arg_Mechanism                => Mechanism,
9729               Arg_First_Optional_Parameter => First_Optional_Parameter);
9730          end Import_Procedure;
9731
9732          -----------------------------
9733          -- Import_Valued_Procedure --
9734          -----------------------------
9735
9736          --  pragma Import_Valued_Procedure (
9737          --        [Internal                 =>] LOCAL_NAME
9738          --     [, [External                 =>] EXTERNAL_SYMBOL]
9739          --     [, [Parameter_Types          =>] (PARAMETER_TYPES)]
9740          --     [, [Mechanism                =>] MECHANISM]
9741          --     [, [First_Optional_Parameter =>] IDENTIFIER]);
9742
9743          --  EXTERNAL_SYMBOL ::=
9744          --    IDENTIFIER
9745          --  | static_string_EXPRESSION
9746
9747          --  PARAMETER_TYPES ::=
9748          --    null
9749          --  | TYPE_DESIGNATOR @{, TYPE_DESIGNATOR@}
9750
9751          --  TYPE_DESIGNATOR ::=
9752          --    subtype_NAME
9753          --  | subtype_Name ' Access
9754
9755          --  MECHANISM ::=
9756          --    MECHANISM_NAME
9757          --  | (MECHANISM_ASSOCIATION @{, MECHANISM_ASSOCIATION@})
9758
9759          --  MECHANISM_ASSOCIATION ::=
9760          --    [formal_parameter_NAME =>] MECHANISM_NAME
9761
9762          --  MECHANISM_NAME ::=
9763          --    Value
9764          --  | Reference
9765          --  | Descriptor [([Class =>] CLASS_NAME)]
9766
9767          --  CLASS_NAME ::= ubs | ubsb | uba | s | sb | a | nca
9768
9769          when Pragma_Import_Valued_Procedure =>
9770          Import_Valued_Procedure : declare
9771             Args  : Args_List (1 .. 5);
9772             Names : constant Name_List (1 .. 5) := (
9773                       Name_Internal,
9774                       Name_External,
9775                       Name_Parameter_Types,
9776                       Name_Mechanism,
9777                       Name_First_Optional_Parameter);
9778
9779             Internal                 : Node_Id renames Args (1);
9780             External                 : Node_Id renames Args (2);
9781             Parameter_Types          : Node_Id renames Args (3);
9782             Mechanism                : Node_Id renames Args (4);
9783             First_Optional_Parameter : Node_Id renames Args (5);
9784
9785          begin
9786             GNAT_Pragma;
9787             Gather_Associations (Names, Args);
9788             Process_Extended_Import_Export_Subprogram_Pragma (
9789               Arg_Internal                 => Internal,
9790               Arg_External                 => External,
9791               Arg_Parameter_Types          => Parameter_Types,
9792               Arg_Mechanism                => Mechanism,
9793               Arg_First_Optional_Parameter => First_Optional_Parameter);
9794          end Import_Valued_Procedure;
9795
9796          -----------------
9797          -- Independent --
9798          -----------------
9799
9800          --  pragma Independent (LOCAL_NAME);
9801
9802          when Pragma_Independent => Independent : declare
9803             E_Id : Node_Id;
9804             E    : Entity_Id;
9805             D    : Node_Id;
9806             K    : Node_Kind;
9807
9808          begin
9809             Check_Ada_83_Warning;
9810             Ada_2012_Pragma;
9811             Check_No_Identifiers;
9812             Check_Arg_Count (1);
9813             Check_Arg_Is_Local_Name (Arg1);
9814             E_Id := Get_Pragma_Arg (Arg1);
9815
9816             if Etype (E_Id) = Any_Type then
9817                return;
9818             end if;
9819
9820             E := Entity (E_Id);
9821             D := Declaration_Node (E);
9822             K := Nkind (D);
9823
9824             --  Check duplicate before we chain ourselves!
9825
9826             Check_Duplicate_Pragma (E);
9827
9828             --  Check appropriate entity
9829
9830             if Is_Type (E) then
9831                if Rep_Item_Too_Early (E, N)
9832                     or else
9833                   Rep_Item_Too_Late (E, N)
9834                then
9835                   return;
9836                else
9837                   Check_First_Subtype (Arg1);
9838                end if;
9839
9840             elsif K = N_Object_Declaration
9841               or else (K = N_Component_Declaration
9842                        and then Original_Record_Component (E) = E)
9843             then
9844                if Rep_Item_Too_Late (E, N) then
9845                   return;
9846                end if;
9847
9848             else
9849                Error_Pragma_Arg
9850                  ("inappropriate entity for pragma%", Arg1);
9851             end if;
9852
9853             Independence_Checks.Append ((N, E));
9854          end Independent;
9855
9856          ----------------------------
9857          -- Independent_Components --
9858          ----------------------------
9859
9860          --  pragma Atomic_Components (array_LOCAL_NAME);
9861
9862          --  This processing is shared by Volatile_Components
9863
9864          when Pragma_Independent_Components => Independent_Components : declare
9865             E_Id : Node_Id;
9866             E    : Entity_Id;
9867             D    : Node_Id;
9868             K    : Node_Kind;
9869
9870          begin
9871             Check_Ada_83_Warning;
9872             Ada_2012_Pragma;
9873             Check_No_Identifiers;
9874             Check_Arg_Count (1);
9875             Check_Arg_Is_Local_Name (Arg1);
9876             E_Id := Get_Pragma_Arg (Arg1);
9877
9878             if Etype (E_Id) = Any_Type then
9879                return;
9880             end if;
9881
9882             E := Entity (E_Id);
9883
9884             --  Check duplicate before we chain ourselves!
9885
9886             Check_Duplicate_Pragma (E);
9887
9888             --  Check appropriate entity
9889
9890             if Rep_Item_Too_Early (E, N)
9891                  or else
9892                Rep_Item_Too_Late (E, N)
9893             then
9894                return;
9895             end if;
9896
9897             D := Declaration_Node (E);
9898             K := Nkind (D);
9899
9900             if (K = N_Full_Type_Declaration
9901                  and then (Is_Array_Type (E) or else Is_Record_Type (E)))
9902               or else
9903                 ((Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
9904                    and then Nkind (D) = N_Object_Declaration
9905                    and then Nkind (Object_Definition (D)) =
9906                                        N_Constrained_Array_Definition)
9907             then
9908                Independence_Checks.Append ((N, E));
9909
9910             else
9911                Error_Pragma_Arg ("inappropriate entity for pragma%", Arg1);
9912             end if;
9913          end Independent_Components;
9914
9915          ------------------------
9916          -- Initialize_Scalars --
9917          ------------------------
9918
9919          --  pragma Initialize_Scalars;
9920
9921          when Pragma_Initialize_Scalars =>
9922             GNAT_Pragma;
9923             Check_Arg_Count (0);
9924             Check_Valid_Configuration_Pragma;
9925             Check_Restriction (No_Initialize_Scalars, N);
9926
9927             --  Initialize_Scalars creates false positives in CodePeer, and
9928             --  incorrect negative results in Alfa mode, so ignore this pragma
9929             --  in these modes.
9930
9931             if not Restriction_Active (No_Initialize_Scalars)
9932               and then not (CodePeer_Mode or Alfa_Mode)
9933             then
9934                Init_Or_Norm_Scalars := True;
9935                Initialize_Scalars := True;
9936             end if;
9937
9938          ------------
9939          -- Inline --
9940          ------------
9941
9942          --  pragma Inline ( NAME {, NAME} );
9943
9944          when Pragma_Inline =>
9945
9946             --  Pragma is active if inlining option is active
9947
9948             Process_Inline (Inline_Active);
9949
9950          -------------------
9951          -- Inline_Always --
9952          -------------------
9953
9954          --  pragma Inline_Always ( NAME {, NAME} );
9955
9956          when Pragma_Inline_Always =>
9957             GNAT_Pragma;
9958
9959             --  Pragma always active unless in CodePeer or Alfa mode, since
9960             --  this causes walk order issues.
9961
9962             if not (CodePeer_Mode or Alfa_Mode) then
9963                Process_Inline (True);
9964             end if;
9965
9966          --------------------
9967          -- Inline_Generic --
9968          --------------------
9969
9970          --  pragma Inline_Generic (NAME {, NAME});
9971
9972          when Pragma_Inline_Generic =>
9973             GNAT_Pragma;
9974             Process_Generic_List;
9975
9976          ----------------------
9977          -- Inspection_Point --
9978          ----------------------
9979
9980          --  pragma Inspection_Point [(object_NAME {, object_NAME})];
9981
9982          when Pragma_Inspection_Point => Inspection_Point : declare
9983             Arg : Node_Id;
9984             Exp : Node_Id;
9985
9986          begin
9987             if Arg_Count > 0 then
9988                Arg := Arg1;
9989                loop
9990                   Exp := Get_Pragma_Arg (Arg);
9991                   Analyze (Exp);
9992
9993                   if not Is_Entity_Name (Exp)
9994                     or else not Is_Object (Entity (Exp))
9995                   then
9996                      Error_Pragma_Arg ("object name required", Arg);
9997                   end if;
9998
9999                   Next (Arg);
10000                   exit when No (Arg);
10001                end loop;
10002             end if;
10003          end Inspection_Point;
10004
10005          ---------------
10006          -- Interface --
10007          ---------------
10008
10009          --  pragma Interface (
10010          --    [   Convention    =>] convention_IDENTIFIER,
10011          --    [   Entity        =>] local_NAME
10012          --    [, [External_Name =>] static_string_EXPRESSION ]
10013          --    [, [Link_Name     =>] static_string_EXPRESSION ]);
10014
10015          when Pragma_Interface =>
10016             GNAT_Pragma;
10017             Check_Arg_Order
10018               ((Name_Convention,
10019                 Name_Entity,
10020                 Name_External_Name,
10021                 Name_Link_Name));
10022             Check_At_Least_N_Arguments (2);
10023             Check_At_Most_N_Arguments  (4);
10024             Process_Import_Or_Interface;
10025
10026             --  In Ada 2005, the permission to use Interface (a reserved word)
10027             --  as a pragma name is considered an obsolescent feature.
10028
10029             if Ada_Version >= Ada_2005 then
10030                Check_Restriction
10031                  (No_Obsolescent_Features, Pragma_Identifier (N));
10032             end if;
10033
10034          --------------------
10035          -- Interface_Name --
10036          --------------------
10037
10038          --  pragma Interface_Name (
10039          --    [  Entity        =>] local_NAME
10040          --    [,[External_Name =>] static_string_EXPRESSION ]
10041          --    [,[Link_Name     =>] static_string_EXPRESSION ]);
10042
10043          when Pragma_Interface_Name => Interface_Name : declare
10044             Id     : Node_Id;
10045             Def_Id : Entity_Id;
10046             Hom_Id : Entity_Id;
10047             Found  : Boolean;
10048
10049          begin
10050             GNAT_Pragma;
10051             Check_Arg_Order
10052               ((Name_Entity, Name_External_Name, Name_Link_Name));
10053             Check_At_Least_N_Arguments (2);
10054             Check_At_Most_N_Arguments  (3);
10055             Id := Get_Pragma_Arg (Arg1);
10056             Analyze (Id);
10057
10058             if not Is_Entity_Name (Id) then
10059                Error_Pragma_Arg
10060                  ("first argument for pragma% must be entity name", Arg1);
10061             elsif Etype (Id) = Any_Type then
10062                return;
10063             else
10064                Def_Id := Entity (Id);
10065             end if;
10066
10067             --  Special DEC-compatible processing for the object case, forces
10068             --  object to be imported.
10069
10070             if Ekind (Def_Id) = E_Variable then
10071                Kill_Size_Check_Code (Def_Id);
10072                Note_Possible_Modification (Id, Sure => False);
10073
10074                --  Initialization is not allowed for imported variable
10075
10076                if Present (Expression (Parent (Def_Id)))
10077                  and then Comes_From_Source (Expression (Parent (Def_Id)))
10078                then
10079                   Error_Msg_Sloc := Sloc (Def_Id);
10080                   Error_Pragma_Arg
10081                     ("no initialization allowed for declaration of& #",
10082                      Arg2);
10083
10084                else
10085                   --  For compatibility, support VADS usage of providing both
10086                   --  pragmas Interface and Interface_Name to obtain the effect
10087                   --  of a single Import pragma.
10088
10089                   if Is_Imported (Def_Id)
10090                     and then Present (First_Rep_Item (Def_Id))
10091                     and then Nkind (First_Rep_Item (Def_Id)) = N_Pragma
10092                     and then
10093                       Pragma_Name (First_Rep_Item (Def_Id)) = Name_Interface
10094                   then
10095                      null;
10096                   else
10097                      Set_Imported (Def_Id);
10098                   end if;
10099
10100                   Set_Is_Public (Def_Id);
10101                   Process_Interface_Name (Def_Id, Arg2, Arg3);
10102                end if;
10103
10104             --  Otherwise must be subprogram
10105
10106             elsif not Is_Subprogram (Def_Id) then
10107                Error_Pragma_Arg
10108                  ("argument of pragma% is not subprogram", Arg1);
10109
10110             else
10111                Check_At_Most_N_Arguments (3);
10112                Hom_Id := Def_Id;
10113                Found := False;
10114
10115                --  Loop through homonyms
10116
10117                loop
10118                   Def_Id := Get_Base_Subprogram (Hom_Id);
10119
10120                   if Is_Imported (Def_Id) then
10121                      Process_Interface_Name (Def_Id, Arg2, Arg3);
10122                      Found := True;
10123                   end if;
10124
10125                   exit when From_Aspect_Specification (N);
10126                   Hom_Id := Homonym (Hom_Id);
10127
10128                   exit when No (Hom_Id)
10129                     or else Scope (Hom_Id) /= Current_Scope;
10130                end loop;
10131
10132                if not Found then
10133                   Error_Pragma_Arg
10134                     ("argument of pragma% is not imported subprogram",
10135                      Arg1);
10136                end if;
10137             end if;
10138          end Interface_Name;
10139
10140          -----------------------
10141          -- Interrupt_Handler --
10142          -----------------------
10143
10144          --  pragma Interrupt_Handler (handler_NAME);
10145
10146          when Pragma_Interrupt_Handler =>
10147             Check_Ada_83_Warning;
10148             Check_Arg_Count (1);
10149             Check_No_Identifiers;
10150
10151             if No_Run_Time_Mode then
10152                Error_Msg_CRT ("Interrupt_Handler pragma", N);
10153             else
10154                Check_Interrupt_Or_Attach_Handler;
10155                Process_Interrupt_Or_Attach_Handler;
10156             end if;
10157
10158          ------------------------
10159          -- Interrupt_Priority --
10160          ------------------------
10161
10162          --  pragma Interrupt_Priority [(EXPRESSION)];
10163
10164          when Pragma_Interrupt_Priority => Interrupt_Priority : declare
10165             P   : constant Node_Id := Parent (N);
10166             Arg : Node_Id;
10167
10168          begin
10169             Check_Ada_83_Warning;
10170
10171             if Arg_Count /= 0 then
10172                Arg := Get_Pragma_Arg (Arg1);
10173                Check_Arg_Count (1);
10174                Check_No_Identifiers;
10175
10176                --  The expression must be analyzed in the special manner
10177                --  described in "Handling of Default and Per-Object
10178                --  Expressions" in sem.ads.
10179
10180                Preanalyze_Spec_Expression (Arg, RTE (RE_Interrupt_Priority));
10181             end if;
10182
10183             if not Nkind_In (P, N_Task_Definition, N_Protected_Definition) then
10184                Pragma_Misplaced;
10185                return;
10186
10187             elsif Has_Pragma_Priority (P) then
10188                Error_Pragma ("duplicate pragma% not allowed");
10189
10190             else
10191                Set_Has_Pragma_Priority (P, True);
10192                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
10193             end if;
10194          end Interrupt_Priority;
10195
10196          ---------------------
10197          -- Interrupt_State --
10198          ---------------------
10199
10200          --  pragma Interrupt_State (
10201          --    [Name  =>] INTERRUPT_ID,
10202          --    [State =>] INTERRUPT_STATE);
10203
10204          --  INTERRUPT_ID => IDENTIFIER | static_integer_EXPRESSION
10205          --  INTERRUPT_STATE => System | Runtime | User
10206
10207          --  Note: if the interrupt id is given as an identifier, then it must
10208          --  be one of the identifiers in Ada.Interrupts.Names. Otherwise it is
10209          --  given as a static integer expression which must be in the range of
10210          --  Ada.Interrupts.Interrupt_ID.
10211
10212          when Pragma_Interrupt_State => Interrupt_State : declare
10213
10214             Int_Id : constant Entity_Id := RTE (RE_Interrupt_ID);
10215             --  This is the entity Ada.Interrupts.Interrupt_ID;
10216
10217             State_Type : Character;
10218             --  Set to 's'/'r'/'u' for System/Runtime/User
10219
10220             IST_Num : Pos;
10221             --  Index to entry in Interrupt_States table
10222
10223             Int_Val : Uint;
10224             --  Value of interrupt
10225
10226             Arg1X : constant Node_Id := Get_Pragma_Arg (Arg1);
10227             --  The first argument to the pragma
10228
10229             Int_Ent : Entity_Id;
10230             --  Interrupt entity in Ada.Interrupts.Names
10231
10232          begin
10233             GNAT_Pragma;
10234             Check_Arg_Order ((Name_Name, Name_State));
10235             Check_Arg_Count (2);
10236
10237             Check_Optional_Identifier (Arg1, Name_Name);
10238             Check_Optional_Identifier (Arg2, Name_State);
10239             Check_Arg_Is_Identifier (Arg2);
10240
10241             --  First argument is identifier
10242
10243             if Nkind (Arg1X) = N_Identifier then
10244
10245                --  Search list of names in Ada.Interrupts.Names
10246
10247                Int_Ent := First_Entity (RTE (RE_Names));
10248                loop
10249                   if No (Int_Ent) then
10250                      Error_Pragma_Arg ("invalid interrupt name", Arg1);
10251
10252                   elsif Chars (Int_Ent) = Chars (Arg1X) then
10253                      Int_Val := Expr_Value (Constant_Value (Int_Ent));
10254                      exit;
10255                   end if;
10256
10257                   Next_Entity (Int_Ent);
10258                end loop;
10259
10260             --  First argument is not an identifier, so it must be a static
10261             --  expression of type Ada.Interrupts.Interrupt_ID.
10262
10263             else
10264                Check_Arg_Is_Static_Expression (Arg1, Any_Integer);
10265                Int_Val := Expr_Value (Arg1X);
10266
10267                if Int_Val < Expr_Value (Type_Low_Bound (Int_Id))
10268                     or else
10269                   Int_Val > Expr_Value (Type_High_Bound (Int_Id))
10270                then
10271                   Error_Pragma_Arg
10272                     ("value not in range of type " &
10273                      """Ada.Interrupts.Interrupt_'I'D""", Arg1);
10274                end if;
10275             end if;
10276
10277             --  Check OK state
10278
10279             case Chars (Get_Pragma_Arg (Arg2)) is
10280                when Name_Runtime => State_Type := 'r';
10281                when Name_System  => State_Type := 's';
10282                when Name_User    => State_Type := 'u';
10283
10284                when others =>
10285                   Error_Pragma_Arg ("invalid interrupt state", Arg2);
10286             end case;
10287
10288             --  Check if entry is already stored
10289
10290             IST_Num := Interrupt_States.First;
10291             loop
10292                --  If entry not found, add it
10293
10294                if IST_Num > Interrupt_States.Last then
10295                   Interrupt_States.Append
10296                     ((Interrupt_Number => UI_To_Int (Int_Val),
10297                       Interrupt_State  => State_Type,
10298                       Pragma_Loc       => Loc));
10299                   exit;
10300
10301                --  Case of entry for the same entry
10302
10303                elsif Int_Val = Interrupt_States.Table (IST_Num).
10304                                                            Interrupt_Number
10305                then
10306                   --  If state matches, done, no need to make redundant entry
10307
10308                   exit when
10309                     State_Type = Interrupt_States.Table (IST_Num).
10310                                                            Interrupt_State;
10311
10312                   --  Otherwise if state does not match, error
10313
10314                   Error_Msg_Sloc :=
10315                     Interrupt_States.Table (IST_Num).Pragma_Loc;
10316                   Error_Pragma_Arg
10317                     ("state conflicts with that given #", Arg2);
10318                   exit;
10319                end if;
10320
10321                IST_Num := IST_Num + 1;
10322             end loop;
10323          end Interrupt_State;
10324
10325          ---------------
10326          -- Invariant --
10327          ---------------
10328
10329          --  pragma Invariant
10330          --    ([Entity =>]    type_LOCAL_NAME,
10331          --     [Check  =>]    EXPRESSION
10332          --     [,[Message =>] String_Expression]);
10333
10334          when Pragma_Invariant => Invariant : declare
10335             Type_Id : Node_Id;
10336             Typ     : Entity_Id;
10337
10338             Discard : Boolean;
10339             pragma Unreferenced (Discard);
10340
10341          begin
10342             GNAT_Pragma;
10343             Check_At_Least_N_Arguments (2);
10344             Check_At_Most_N_Arguments (3);
10345             Check_Optional_Identifier (Arg1, Name_Entity);
10346             Check_Optional_Identifier (Arg2, Name_Check);
10347
10348             if Arg_Count = 3 then
10349                Check_Optional_Identifier (Arg3, Name_Message);
10350                Check_Arg_Is_Static_Expression (Arg3, Standard_String);
10351             end if;
10352
10353             Check_Arg_Is_Local_Name (Arg1);
10354
10355             Type_Id := Get_Pragma_Arg (Arg1);
10356             Find_Type (Type_Id);
10357             Typ := Entity (Type_Id);
10358
10359             if Typ = Any_Type then
10360                return;
10361
10362             --  An invariant must apply to a private type, or appear in the
10363             --  private part of a package spec and apply to a completion.
10364
10365             elsif Ekind_In (Typ, E_Private_Type,
10366                                  E_Record_Type_With_Private,
10367                                  E_Limited_Private_Type)
10368             then
10369                null;
10370
10371             elsif In_Private_Part (Current_Scope)
10372               and then Has_Private_Declaration (Typ)
10373             then
10374                null;
10375
10376             elsif In_Private_Part (Current_Scope) then
10377                Error_Pragma_Arg
10378                  ("pragma% only allowed for private type " &
10379                   "declared in visible part", Arg1);
10380
10381             else
10382                Error_Pragma_Arg
10383                  ("pragma% only allowed for private type", Arg1);
10384             end if;
10385
10386             --  Note that the type has at least one invariant, and also that
10387             --  it has inheritable invariants if we have Invariant'Class.
10388
10389             Set_Has_Invariants (Typ);
10390
10391             if Class_Present (N) then
10392                Set_Has_Inheritable_Invariants (Typ);
10393             end if;
10394
10395             --  The remaining processing is simply to link the pragma on to
10396             --  the rep item chain, for processing when the type is frozen.
10397             --  This is accomplished by a call to Rep_Item_Too_Late.
10398
10399             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
10400          end Invariant;
10401
10402          ----------------------
10403          -- Java_Constructor --
10404          ----------------------
10405
10406          --  pragma Java_Constructor ([Entity =>] LOCAL_NAME);
10407
10408          --  Also handles pragma CIL_Constructor
10409
10410          when Pragma_CIL_Constructor | Pragma_Java_Constructor =>
10411          Java_Constructor : declare
10412             Convention  : Convention_Id;
10413             Def_Id      : Entity_Id;
10414             Hom_Id      : Entity_Id;
10415             Id          : Entity_Id;
10416             This_Formal : Entity_Id;
10417
10418          begin
10419             GNAT_Pragma;
10420             Check_Arg_Count (1);
10421             Check_Optional_Identifier (Arg1, Name_Entity);
10422             Check_Arg_Is_Local_Name (Arg1);
10423
10424             Id := Get_Pragma_Arg (Arg1);
10425             Find_Program_Unit_Name (Id);
10426
10427             --  If we did not find the name, we are done
10428
10429             if Etype (Id) = Any_Type then
10430                return;
10431             end if;
10432
10433             --  Check wrong use of pragma in wrong VM target
10434
10435             if VM_Target = No_VM then
10436                return;
10437
10438             elsif VM_Target = CLI_Target
10439               and then Prag_Id = Pragma_Java_Constructor
10440             then
10441                Error_Pragma ("must use pragma 'C'I'L_'Constructor");
10442
10443             elsif VM_Target = JVM_Target
10444               and then Prag_Id = Pragma_CIL_Constructor
10445             then
10446                Error_Pragma ("must use pragma 'Java_'Constructor");
10447             end if;
10448
10449             case Prag_Id is
10450                when Pragma_CIL_Constructor  => Convention := Convention_CIL;
10451                when Pragma_Java_Constructor => Convention := Convention_Java;
10452                when others                  => null;
10453             end case;
10454
10455             Hom_Id := Entity (Id);
10456
10457             --  Loop through homonyms
10458
10459             loop
10460                Def_Id := Get_Base_Subprogram (Hom_Id);
10461
10462                --  The constructor is required to be a function
10463
10464                if Ekind (Def_Id) /= E_Function then
10465                   if VM_Target = JVM_Target then
10466                      Error_Pragma_Arg
10467                        ("pragma% requires function returning a " &
10468                         "'Java access type", Def_Id);
10469                   else
10470                      Error_Pragma_Arg
10471                        ("pragma% requires function returning a " &
10472                         "'C'I'L access type", Def_Id);
10473                   end if;
10474                end if;
10475
10476                --  Check arguments: For tagged type the first formal must be
10477                --  named "this" and its type must be a named access type
10478                --  designating a class-wide tagged type that has convention
10479                --  CIL/Java. The first formal must also have a null default
10480                --  value. For example:
10481
10482                --      type Typ is tagged ...
10483                --      type Ref is access all Typ;
10484                --      pragma Convention (CIL, Typ);
10485
10486                --      function New_Typ (This : Ref) return Ref;
10487                --      function New_Typ (This : Ref; I : Integer) return Ref;
10488                --      pragma Cil_Constructor (New_Typ);
10489
10490                --  Reason: The first formal must NOT be a primitive of the
10491                --  tagged type.
10492
10493                --  This rule also applies to constructors of delegates used
10494                --  to interface with standard target libraries. For example:
10495
10496                --      type Delegate is access procedure ...
10497                --      pragma Import (CIL, Delegate, ...);
10498
10499                --      function new_Delegate
10500                --        (This : Delegate := null; ... ) return Delegate;
10501
10502                --  For value-types this rule does not apply.
10503
10504                if not Is_Value_Type (Etype (Def_Id)) then
10505                   if No (First_Formal (Def_Id)) then
10506                      Error_Msg_Name_1 := Pname;
10507                      Error_Msg_N ("% function must have parameters", Def_Id);
10508                      return;
10509                   end if;
10510
10511                   --  In the JRE library we have several occurrences in which
10512                   --  the "this" parameter is not the first formal.
10513
10514                   This_Formal := First_Formal (Def_Id);
10515
10516                   --  In the JRE library we have several occurrences in which
10517                   --  the "this" parameter is not the first formal. Search for
10518                   --  it.
10519
10520                   if VM_Target = JVM_Target then
10521                      while Present (This_Formal)
10522                        and then Get_Name_String (Chars (This_Formal)) /= "this"
10523                      loop
10524                         Next_Formal (This_Formal);
10525                      end loop;
10526
10527                      if No (This_Formal) then
10528                         This_Formal := First_Formal (Def_Id);
10529                      end if;
10530                   end if;
10531
10532                   --  Warning: The first parameter should be named "this".
10533                   --  We temporarily allow it because we have the following
10534                   --  case in the Java runtime (file s-osinte.ads) ???
10535
10536                   --    function new_Thread
10537                   --      (Self_Id : System.Address) return Thread_Id;
10538                   --    pragma Java_Constructor (new_Thread);
10539
10540                   if VM_Target = JVM_Target
10541                     and then Get_Name_String (Chars (First_Formal (Def_Id)))
10542                                = "self_id"
10543                     and then Etype (First_Formal (Def_Id)) = RTE (RE_Address)
10544                   then
10545                      null;
10546
10547                   elsif Get_Name_String (Chars (This_Formal)) /= "this" then
10548                      Error_Msg_Name_1 := Pname;
10549                      Error_Msg_N
10550                        ("first formal of % function must be named `this`",
10551                         Parent (This_Formal));
10552
10553                   elsif not Is_Access_Type (Etype (This_Formal)) then
10554                      Error_Msg_Name_1 := Pname;
10555                      Error_Msg_N
10556                        ("first formal of % function must be an access type",
10557                         Parameter_Type (Parent (This_Formal)));
10558
10559                   --  For delegates the type of the first formal must be a
10560                   --  named access-to-subprogram type (see previous example)
10561
10562                   elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type
10563                     and then Ekind (Etype (This_Formal))
10564                                /= E_Access_Subprogram_Type
10565                   then
10566                      Error_Msg_Name_1 := Pname;
10567                      Error_Msg_N
10568                        ("first formal of % function must be a named access" &
10569                         " to subprogram type",
10570                         Parameter_Type (Parent (This_Formal)));
10571
10572                   --  Warning: We should reject anonymous access types because
10573                   --  the constructor must not be handled as a primitive of the
10574                   --  tagged type. We temporarily allow it because this profile
10575                   --  is currently generated by cil2ada???
10576
10577                   elsif Ekind (Etype (Def_Id)) /= E_Access_Subprogram_Type
10578                     and then not Ekind_In (Etype (This_Formal),
10579                                              E_Access_Type,
10580                                              E_General_Access_Type,
10581                                              E_Anonymous_Access_Type)
10582                   then
10583                      Error_Msg_Name_1 := Pname;
10584                      Error_Msg_N
10585                        ("first formal of % function must be a named access" &
10586                         " type",
10587                         Parameter_Type (Parent (This_Formal)));
10588
10589                   elsif Atree.Convention
10590                          (Designated_Type (Etype (This_Formal))) /= Convention
10591                   then
10592                      Error_Msg_Name_1 := Pname;
10593
10594                      if Convention = Convention_Java then
10595                         Error_Msg_N
10596                           ("pragma% requires convention 'Cil in designated" &
10597                            " type",
10598                            Parameter_Type (Parent (This_Formal)));
10599                      else
10600                         Error_Msg_N
10601                           ("pragma% requires convention 'Java in designated" &
10602                            " type",
10603                            Parameter_Type (Parent (This_Formal)));
10604                      end if;
10605
10606                   elsif No (Expression (Parent (This_Formal)))
10607                     or else Nkind (Expression (Parent (This_Formal))) /= N_Null
10608                   then
10609                      Error_Msg_Name_1 := Pname;
10610                      Error_Msg_N
10611                        ("pragma% requires first formal with default `null`",
10612                         Parameter_Type (Parent (This_Formal)));
10613                   end if;
10614                end if;
10615
10616                --  Check result type: the constructor must be a function
10617                --  returning:
10618                --   * a value type (only allowed in the CIL compiler)
10619                --   * an access-to-subprogram type with convention Java/CIL
10620                --   * an access-type designating a type that has convention
10621                --     Java/CIL.
10622
10623                if Is_Value_Type (Etype (Def_Id)) then
10624                   null;
10625
10626                --  Access-to-subprogram type with convention Java/CIL
10627
10628                elsif Ekind (Etype (Def_Id)) = E_Access_Subprogram_Type then
10629                   if Atree.Convention (Etype (Def_Id)) /= Convention then
10630                      if Convention = Convention_Java then
10631                         Error_Pragma_Arg
10632                           ("pragma% requires function returning a " &
10633                            "'Java access type", Arg1);
10634                      else
10635                         pragma Assert (Convention = Convention_CIL);
10636                         Error_Pragma_Arg
10637                           ("pragma% requires function returning a " &
10638                            "'C'I'L access type", Arg1);
10639                      end if;
10640                   end if;
10641
10642                elsif Ekind (Etype (Def_Id)) in Access_Kind then
10643                   if not Ekind_In (Etype (Def_Id), E_Access_Type,
10644                                                    E_General_Access_Type)
10645                     or else
10646                       Atree.Convention
10647                         (Designated_Type (Etype (Def_Id))) /= Convention
10648                   then
10649                      Error_Msg_Name_1 := Pname;
10650
10651                      if Convention = Convention_Java then
10652                         Error_Pragma_Arg
10653                           ("pragma% requires function returning a named" &
10654                            "'Java access type", Arg1);
10655                      else
10656                         Error_Pragma_Arg
10657                           ("pragma% requires function returning a named" &
10658                            "'C'I'L access type", Arg1);
10659                      end if;
10660                   end if;
10661                end if;
10662
10663                Set_Is_Constructor (Def_Id);
10664                Set_Convention     (Def_Id, Convention);
10665                Set_Is_Imported    (Def_Id);
10666
10667                exit when From_Aspect_Specification (N);
10668                Hom_Id := Homonym (Hom_Id);
10669
10670                exit when No (Hom_Id) or else Scope (Hom_Id) /= Current_Scope;
10671             end loop;
10672          end Java_Constructor;
10673
10674          ----------------------
10675          -- Java_Interface --
10676          ----------------------
10677
10678          --  pragma Java_Interface ([Entity =>] LOCAL_NAME);
10679
10680          when Pragma_Java_Interface => Java_Interface : declare
10681             Arg : Node_Id;
10682             Typ : Entity_Id;
10683
10684          begin
10685             GNAT_Pragma;
10686             Check_Arg_Count (1);
10687             Check_Optional_Identifier (Arg1, Name_Entity);
10688             Check_Arg_Is_Local_Name (Arg1);
10689
10690             Arg := Get_Pragma_Arg (Arg1);
10691             Analyze (Arg);
10692
10693             if Etype (Arg) = Any_Type then
10694                return;
10695             end if;
10696
10697             if not Is_Entity_Name (Arg)
10698               or else not Is_Type (Entity (Arg))
10699             then
10700                Error_Pragma_Arg ("pragma% requires a type mark", Arg1);
10701             end if;
10702
10703             Typ := Underlying_Type (Entity (Arg));
10704
10705             --  For now simply check some of the semantic constraints on the
10706             --  type. This currently leaves out some restrictions on interface
10707             --  types, namely that the parent type must be java.lang.Object.Typ
10708             --  and that all primitives of the type should be declared
10709             --  abstract. ???
10710
10711             if not Is_Tagged_Type (Typ) or else not Is_Abstract_Type (Typ) then
10712                Error_Pragma_Arg ("pragma% requires an abstract "
10713                  & "tagged type", Arg1);
10714
10715             elsif not Has_Discriminants (Typ)
10716               or else Ekind (Etype (First_Discriminant (Typ)))
10717                         /= E_Anonymous_Access_Type
10718               or else
10719                 not Is_Class_Wide_Type
10720                       (Designated_Type (Etype (First_Discriminant (Typ))))
10721             then
10722                Error_Pragma_Arg
10723                  ("type must have a class-wide access discriminant", Arg1);
10724             end if;
10725          end Java_Interface;
10726
10727          ----------------
10728          -- Keep_Names --
10729          ----------------
10730
10731          --  pragma Keep_Names ([On => ] local_NAME);
10732
10733          when Pragma_Keep_Names => Keep_Names : declare
10734             Arg : Node_Id;
10735
10736          begin
10737             GNAT_Pragma;
10738             Check_Arg_Count (1);
10739             Check_Optional_Identifier (Arg1, Name_On);
10740             Check_Arg_Is_Local_Name (Arg1);
10741
10742             Arg := Get_Pragma_Arg (Arg1);
10743             Analyze (Arg);
10744
10745             if Etype (Arg) = Any_Type then
10746                return;
10747             end if;
10748
10749             if not Is_Entity_Name (Arg)
10750               or else Ekind (Entity (Arg)) /= E_Enumeration_Type
10751             then
10752                Error_Pragma_Arg
10753                  ("pragma% requires a local enumeration type", Arg1);
10754             end if;
10755
10756             Set_Discard_Names (Entity (Arg), False);
10757          end Keep_Names;
10758
10759          -------------
10760          -- License --
10761          -------------
10762
10763          --  pragma License (RESTRICTED | UNRESTRICTED | GPL | MODIFIED_GPL);
10764
10765          when Pragma_License =>
10766             GNAT_Pragma;
10767             Check_Arg_Count (1);
10768             Check_No_Identifiers;
10769             Check_Valid_Configuration_Pragma;
10770             Check_Arg_Is_Identifier (Arg1);
10771
10772             declare
10773                Sind : constant Source_File_Index :=
10774                         Source_Index (Current_Sem_Unit);
10775
10776             begin
10777                case Chars (Get_Pragma_Arg (Arg1)) is
10778                   when Name_GPL =>
10779                      Set_License (Sind, GPL);
10780
10781                   when Name_Modified_GPL =>
10782                      Set_License (Sind, Modified_GPL);
10783
10784                   when Name_Restricted =>
10785                      Set_License (Sind, Restricted);
10786
10787                   when Name_Unrestricted =>
10788                      Set_License (Sind, Unrestricted);
10789
10790                   when others =>
10791                      Error_Pragma_Arg ("invalid license name", Arg1);
10792                end case;
10793             end;
10794
10795          ---------------
10796          -- Link_With --
10797          ---------------
10798
10799          --  pragma Link_With (string_EXPRESSION {, string_EXPRESSION});
10800
10801          when Pragma_Link_With => Link_With : declare
10802             Arg : Node_Id;
10803
10804          begin
10805             GNAT_Pragma;
10806
10807             if Operating_Mode = Generate_Code
10808               and then In_Extended_Main_Source_Unit (N)
10809             then
10810                Check_At_Least_N_Arguments (1);
10811                Check_No_Identifiers;
10812                Check_Is_In_Decl_Part_Or_Package_Spec;
10813                Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10814                Start_String;
10815
10816                Arg := Arg1;
10817                while Present (Arg) loop
10818                   Check_Arg_Is_Static_Expression (Arg, Standard_String);
10819
10820                   --  Store argument, converting sequences of spaces to a
10821                   --  single null character (this is one of the differences
10822                   --  in processing between Link_With and Linker_Options).
10823
10824                   Arg_Store : declare
10825                      C : constant Char_Code := Get_Char_Code (' ');
10826                      S : constant String_Id :=
10827                            Strval (Expr_Value_S (Get_Pragma_Arg (Arg)));
10828                      L : constant Nat := String_Length (S);
10829                      F : Nat := 1;
10830
10831                      procedure Skip_Spaces;
10832                      --  Advance F past any spaces
10833
10834                      -----------------
10835                      -- Skip_Spaces --
10836                      -----------------
10837
10838                      procedure Skip_Spaces is
10839                      begin
10840                         while F <= L and then Get_String_Char (S, F) = C loop
10841                            F := F + 1;
10842                         end loop;
10843                      end Skip_Spaces;
10844
10845                   --  Start of processing for Arg_Store
10846
10847                   begin
10848                      Skip_Spaces; -- skip leading spaces
10849
10850                      --  Loop through characters, changing any embedded
10851                      --  sequence of spaces to a single null character (this
10852                      --  is how Link_With/Linker_Options differ)
10853
10854                      while F <= L loop
10855                         if Get_String_Char (S, F) = C then
10856                            Skip_Spaces;
10857                            exit when F > L;
10858                            Store_String_Char (ASCII.NUL);
10859
10860                         else
10861                            Store_String_Char (Get_String_Char (S, F));
10862                            F := F + 1;
10863                         end if;
10864                      end loop;
10865                   end Arg_Store;
10866
10867                   Arg := Next (Arg);
10868
10869                   if Present (Arg) then
10870                      Store_String_Char (ASCII.NUL);
10871                   end if;
10872                end loop;
10873
10874                Store_Linker_Option_String (End_String);
10875             end if;
10876          end Link_With;
10877
10878          ------------------
10879          -- Linker_Alias --
10880          ------------------
10881
10882          --  pragma Linker_Alias (
10883          --      [Entity =>]  LOCAL_NAME
10884          --      [Target =>]  static_string_EXPRESSION);
10885
10886          when Pragma_Linker_Alias =>
10887             GNAT_Pragma;
10888             Check_Arg_Order ((Name_Entity, Name_Target));
10889             Check_Arg_Count (2);
10890             Check_Optional_Identifier (Arg1, Name_Entity);
10891             Check_Optional_Identifier (Arg2, Name_Target);
10892             Check_Arg_Is_Library_Level_Local_Name (Arg1);
10893             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
10894
10895             --  The only processing required is to link this item on to the
10896             --  list of rep items for the given entity. This is accomplished
10897             --  by the call to Rep_Item_Too_Late (when no error is detected
10898             --  and False is returned).
10899
10900             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
10901                return;
10902             else
10903                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
10904             end if;
10905
10906          ------------------------
10907          -- Linker_Constructor --
10908          ------------------------
10909
10910          --  pragma Linker_Constructor (procedure_LOCAL_NAME);
10911
10912          --  Code is shared with Linker_Destructor
10913
10914          -----------------------
10915          -- Linker_Destructor --
10916          -----------------------
10917
10918          --  pragma Linker_Destructor (procedure_LOCAL_NAME);
10919
10920          when Pragma_Linker_Constructor |
10921               Pragma_Linker_Destructor =>
10922          Linker_Constructor : declare
10923             Arg1_X : Node_Id;
10924             Proc   : Entity_Id;
10925
10926          begin
10927             GNAT_Pragma;
10928             Check_Arg_Count (1);
10929             Check_No_Identifiers;
10930             Check_Arg_Is_Local_Name (Arg1);
10931             Arg1_X := Get_Pragma_Arg (Arg1);
10932             Analyze (Arg1_X);
10933             Proc := Find_Unique_Parameterless_Procedure (Arg1_X, Arg1);
10934
10935             if not Is_Library_Level_Entity (Proc) then
10936                Error_Pragma_Arg
10937                 ("argument for pragma% must be library level entity", Arg1);
10938             end if;
10939
10940             --  The only processing required is to link this item on to the
10941             --  list of rep items for the given entity. This is accomplished
10942             --  by the call to Rep_Item_Too_Late (when no error is detected
10943             --  and False is returned).
10944
10945             if Rep_Item_Too_Late (Proc, N) then
10946                return;
10947             else
10948                Set_Has_Gigi_Rep_Item (Proc);
10949             end if;
10950          end Linker_Constructor;
10951
10952          --------------------
10953          -- Linker_Options --
10954          --------------------
10955
10956          --  pragma Linker_Options (string_EXPRESSION {, string_EXPRESSION});
10957
10958          when Pragma_Linker_Options => Linker_Options : declare
10959             Arg : Node_Id;
10960
10961          begin
10962             Check_Ada_83_Warning;
10963             Check_No_Identifiers;
10964             Check_Arg_Count (1);
10965             Check_Is_In_Decl_Part_Or_Package_Spec;
10966             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
10967             Start_String (Strval (Expr_Value_S (Get_Pragma_Arg (Arg1))));
10968
10969             Arg := Arg2;
10970             while Present (Arg) loop
10971                Check_Arg_Is_Static_Expression (Arg, Standard_String);
10972                Store_String_Char (ASCII.NUL);
10973                Store_String_Chars
10974                  (Strval (Expr_Value_S (Get_Pragma_Arg (Arg))));
10975                Arg := Next (Arg);
10976             end loop;
10977
10978             if Operating_Mode = Generate_Code
10979               and then In_Extended_Main_Source_Unit (N)
10980             then
10981                Store_Linker_Option_String (End_String);
10982             end if;
10983          end Linker_Options;
10984
10985          --------------------
10986          -- Linker_Section --
10987          --------------------
10988
10989          --  pragma Linker_Section (
10990          --      [Entity  =>]  LOCAL_NAME
10991          --      [Section =>]  static_string_EXPRESSION);
10992
10993          when Pragma_Linker_Section =>
10994             GNAT_Pragma;
10995             Check_Arg_Order ((Name_Entity, Name_Section));
10996             Check_Arg_Count (2);
10997             Check_Optional_Identifier (Arg1, Name_Entity);
10998             Check_Optional_Identifier (Arg2, Name_Section);
10999             Check_Arg_Is_Library_Level_Local_Name (Arg1);
11000             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
11001
11002             --  This pragma applies only to objects
11003
11004             if not Is_Object (Entity (Get_Pragma_Arg (Arg1))) then
11005                Error_Pragma_Arg ("pragma% applies only to objects", Arg1);
11006             end if;
11007
11008             --  The only processing required is to link this item on to the
11009             --  list of rep items for the given entity. This is accomplished
11010             --  by the call to Rep_Item_Too_Late (when no error is detected
11011             --  and False is returned).
11012
11013             if Rep_Item_Too_Late (Entity (Get_Pragma_Arg (Arg1)), N) then
11014                return;
11015             else
11016                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
11017             end if;
11018
11019          ----------
11020          -- List --
11021          ----------
11022
11023          --  pragma List (On | Off)
11024
11025          --  There is nothing to do here, since we did all the processing for
11026          --  this pragma in Par.Prag (so that it works properly even in syntax
11027          --  only mode).
11028
11029          when Pragma_List =>
11030             null;
11031
11032          --------------------
11033          -- Locking_Policy --
11034          --------------------
11035
11036          --  pragma Locking_Policy (policy_IDENTIFIER);
11037
11038          when Pragma_Locking_Policy => declare
11039             subtype LP_Range is Name_Id
11040               range First_Locking_Policy_Name .. Last_Locking_Policy_Name;
11041             LP_Val : LP_Range;
11042             LP     : Character;
11043          begin
11044             Check_Ada_83_Warning;
11045             Check_Arg_Count (1);
11046             Check_No_Identifiers;
11047             Check_Arg_Is_Locking_Policy (Arg1);
11048             Check_Valid_Configuration_Pragma;
11049             LP_Val := Chars (Get_Pragma_Arg (Arg1));
11050
11051             case LP_Val is
11052                when Name_Ceiling_Locking            => LP := 'C';
11053                when Name_Inheritance_Locking        => LP := 'I';
11054                when Name_Concurrent_Readers_Locking => LP := 'R';
11055             end case;
11056
11057             if Locking_Policy /= ' '
11058               and then Locking_Policy /= LP
11059             then
11060                Error_Msg_Sloc := Locking_Policy_Sloc;
11061                Error_Pragma ("locking policy incompatible with policy#");
11062
11063             --  Set new policy, but always preserve System_Location since we
11064             --  like the error message with the run time name.
11065
11066             else
11067                Locking_Policy := LP;
11068
11069                if Locking_Policy_Sloc /= System_Location then
11070                   Locking_Policy_Sloc := Loc;
11071                end if;
11072             end if;
11073          end;
11074
11075          ----------------
11076          -- Long_Float --
11077          ----------------
11078
11079          --  pragma Long_Float (D_Float | G_Float);
11080
11081          when Pragma_Long_Float => Long_Float : declare
11082          begin
11083             GNAT_Pragma;
11084             Check_Valid_Configuration_Pragma;
11085             Check_Arg_Count (1);
11086             Check_No_Identifier (Arg1);
11087             Check_Arg_Is_One_Of (Arg1, Name_D_Float, Name_G_Float);
11088
11089             if not OpenVMS_On_Target then
11090                Error_Pragma ("?pragma% ignored (applies only to Open'V'M'S)");
11091             end if;
11092
11093             --  D_Float case
11094
11095             if Chars (Get_Pragma_Arg (Arg1)) = Name_D_Float then
11096                if Opt.Float_Format_Long = 'G' then
11097                   Error_Pragma_Arg
11098                     ("G_Float previously specified", Arg1);
11099
11100                elsif Current_Sem_Unit /= Main_Unit
11101                  and then Opt.Float_Format_Long /= 'D'
11102                then
11103                   Error_Pragma_Arg
11104                     ("main unit not compiled with pragma Long_Float (D_Float)",
11105                      "\pragma% must be used consistently for whole partition",
11106                      Arg1);
11107
11108                else
11109                   Opt.Float_Format_Long := 'D';
11110                end if;
11111
11112             --  G_Float case (this is the default, does not need overriding)
11113
11114             else
11115                if Opt.Float_Format_Long = 'D' then
11116                   Error_Pragma ("D_Float previously specified");
11117
11118                elsif Current_Sem_Unit /= Main_Unit
11119                  and then Opt.Float_Format_Long /= 'G'
11120                then
11121                   Error_Pragma_Arg
11122                     ("main unit not compiled with pragma Long_Float (G_Float)",
11123                      "\pragma% must be used consistently for whole partition",
11124                      Arg1);
11125
11126                else
11127                   Opt.Float_Format_Long := 'G';
11128                end if;
11129             end if;
11130
11131             Set_Standard_Fpt_Formats;
11132          end Long_Float;
11133
11134          -----------------------
11135          -- Machine_Attribute --
11136          -----------------------
11137
11138          --  pragma Machine_Attribute (
11139          --       [Entity         =>] LOCAL_NAME,
11140          --       [Attribute_Name =>] static_string_EXPRESSION
11141          --    [, [Info           =>] static_EXPRESSION] );
11142
11143          when Pragma_Machine_Attribute => Machine_Attribute : declare
11144             Def_Id : Entity_Id;
11145
11146          begin
11147             GNAT_Pragma;
11148             Check_Arg_Order ((Name_Entity, Name_Attribute_Name, Name_Info));
11149
11150             if Arg_Count = 3 then
11151                Check_Optional_Identifier (Arg3, Name_Info);
11152                Check_Arg_Is_Static_Expression (Arg3);
11153             else
11154                Check_Arg_Count (2);
11155             end if;
11156
11157             Check_Optional_Identifier (Arg1, Name_Entity);
11158             Check_Optional_Identifier (Arg2, Name_Attribute_Name);
11159             Check_Arg_Is_Local_Name (Arg1);
11160             Check_Arg_Is_Static_Expression (Arg2, Standard_String);
11161             Def_Id := Entity (Get_Pragma_Arg (Arg1));
11162
11163             if Is_Access_Type (Def_Id) then
11164                Def_Id := Designated_Type (Def_Id);
11165             end if;
11166
11167             if Rep_Item_Too_Early (Def_Id, N) then
11168                return;
11169             end if;
11170
11171             Def_Id := Underlying_Type (Def_Id);
11172
11173             --  The only processing required is to link this item on to the
11174             --  list of rep items for the given entity. This is accomplished
11175             --  by the call to Rep_Item_Too_Late (when no error is detected
11176             --  and False is returned).
11177
11178             if Rep_Item_Too_Late (Def_Id, N) then
11179                return;
11180             else
11181                Set_Has_Gigi_Rep_Item (Entity (Get_Pragma_Arg (Arg1)));
11182             end if;
11183          end Machine_Attribute;
11184
11185          ----------
11186          -- Main --
11187          ----------
11188
11189          --  pragma Main
11190          --   (MAIN_OPTION [, MAIN_OPTION]);
11191
11192          --  MAIN_OPTION ::=
11193          --    [STACK_SIZE              =>] static_integer_EXPRESSION
11194          --  | [TASK_STACK_SIZE_DEFAULT =>] static_integer_EXPRESSION
11195          --  | [TIME_SLICING_ENABLED    =>] static_boolean_EXPRESSION
11196
11197          when Pragma_Main => Main : declare
11198             Args  : Args_List (1 .. 3);
11199             Names : constant Name_List (1 .. 3) := (
11200                       Name_Stack_Size,
11201                       Name_Task_Stack_Size_Default,
11202                       Name_Time_Slicing_Enabled);
11203
11204             Nod : Node_Id;
11205
11206          begin
11207             GNAT_Pragma;
11208             Gather_Associations (Names, Args);
11209
11210             for J in 1 .. 2 loop
11211                if Present (Args (J)) then
11212                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11213                end if;
11214             end loop;
11215
11216             if Present (Args (3)) then
11217                Check_Arg_Is_Static_Expression (Args (3), Standard_Boolean);
11218             end if;
11219
11220             Nod := Next (N);
11221             while Present (Nod) loop
11222                if Nkind (Nod) = N_Pragma
11223                  and then Pragma_Name (Nod) = Name_Main
11224                then
11225                   Error_Msg_Name_1 := Pname;
11226                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11227                end if;
11228
11229                Next (Nod);
11230             end loop;
11231          end Main;
11232
11233          ------------------
11234          -- Main_Storage --
11235          ------------------
11236
11237          --  pragma Main_Storage
11238          --   (MAIN_STORAGE_OPTION [, MAIN_STORAGE_OPTION]);
11239
11240          --  MAIN_STORAGE_OPTION ::=
11241          --    [WORKING_STORAGE =>] static_SIMPLE_EXPRESSION
11242          --  | [TOP_GUARD =>] static_SIMPLE_EXPRESSION
11243
11244          when Pragma_Main_Storage => Main_Storage : declare
11245             Args  : Args_List (1 .. 2);
11246             Names : constant Name_List (1 .. 2) := (
11247                       Name_Working_Storage,
11248                       Name_Top_Guard);
11249
11250             Nod : Node_Id;
11251
11252          begin
11253             GNAT_Pragma;
11254             Gather_Associations (Names, Args);
11255
11256             for J in 1 .. 2 loop
11257                if Present (Args (J)) then
11258                   Check_Arg_Is_Static_Expression (Args (J), Any_Integer);
11259                end if;
11260             end loop;
11261
11262             Check_In_Main_Program;
11263
11264             Nod := Next (N);
11265             while Present (Nod) loop
11266                if Nkind (Nod) = N_Pragma
11267                  and then Pragma_Name (Nod) = Name_Main_Storage
11268                then
11269                   Error_Msg_Name_1 := Pname;
11270                   Error_Msg_N ("duplicate pragma% not permitted", Nod);
11271                end if;
11272
11273                Next (Nod);
11274             end loop;
11275          end Main_Storage;
11276
11277          -----------------
11278          -- Memory_Size --
11279          -----------------
11280
11281          --  pragma Memory_Size (NUMERIC_LITERAL)
11282
11283          when Pragma_Memory_Size =>
11284             GNAT_Pragma;
11285
11286             --  Memory size is simply ignored
11287
11288             Check_No_Identifiers;
11289             Check_Arg_Count (1);
11290             Check_Arg_Is_Integer_Literal (Arg1);
11291
11292          -------------
11293          -- No_Body --
11294          -------------
11295
11296          --  pragma No_Body;
11297
11298          --  The only correct use of this pragma is on its own in a file, in
11299          --  which case it is specially processed (see Gnat1drv.Check_Bad_Body
11300          --  and Frontend, which use Sinput.L.Source_File_Is_Pragma_No_Body to
11301          --  check for a file containing nothing but a No_Body pragma). If we
11302          --  attempt to process it during normal semantics processing, it means
11303          --  it was misplaced.
11304
11305          when Pragma_No_Body =>
11306             GNAT_Pragma;
11307             Pragma_Misplaced;
11308
11309          ---------------
11310          -- No_Return --
11311          ---------------
11312
11313          --  pragma No_Return (procedure_LOCAL_NAME {, procedure_Local_Name});
11314
11315          when Pragma_No_Return => No_Return : declare
11316             Id    : Node_Id;
11317             E     : Entity_Id;
11318             Found : Boolean;
11319             Arg   : Node_Id;
11320
11321          begin
11322             Ada_2005_Pragma;
11323             Check_At_Least_N_Arguments (1);
11324
11325             --  Loop through arguments of pragma
11326
11327             Arg := Arg1;
11328             while Present (Arg) loop
11329                Check_Arg_Is_Local_Name (Arg);
11330                Id := Get_Pragma_Arg (Arg);
11331                Analyze (Id);
11332
11333                if not Is_Entity_Name (Id) then
11334                   Error_Pragma_Arg ("entity name required", Arg);
11335                end if;
11336
11337                if Etype (Id) = Any_Type then
11338                   raise Pragma_Exit;
11339                end if;
11340
11341                --  Loop to find matching procedures
11342
11343                E := Entity (Id);
11344                Found := False;
11345                while Present (E)
11346                  and then Scope (E) = Current_Scope
11347                loop
11348                   if Ekind_In (E, E_Procedure, E_Generic_Procedure) then
11349                      Set_No_Return (E);
11350
11351                      --  Set flag on any alias as well
11352
11353                      if Is_Overloadable (E) and then Present (Alias (E)) then
11354                         Set_No_Return (Alias (E));
11355                      end if;
11356
11357                      Found := True;
11358                   end if;
11359
11360                   exit when From_Aspect_Specification (N);
11361                   E := Homonym (E);
11362                end loop;
11363
11364                if not Found then
11365                   Error_Pragma_Arg ("no procedure & found for pragma%", Arg);
11366                end if;
11367
11368                Next (Arg);
11369             end loop;
11370          end No_Return;
11371
11372          -----------------
11373          -- No_Run_Time --
11374          -----------------
11375
11376          --  pragma No_Run_Time;
11377
11378          --  Note: this pragma is retained for backwards compatibility. See
11379          --  body of Rtsfind for full details on its handling.
11380
11381          when Pragma_No_Run_Time =>
11382             GNAT_Pragma;
11383             Check_Valid_Configuration_Pragma;
11384             Check_Arg_Count (0);
11385
11386             No_Run_Time_Mode           := True;
11387             Configurable_Run_Time_Mode := True;
11388
11389             --  Set Duration to 32 bits if word size is 32
11390
11391             if Ttypes.System_Word_Size = 32 then
11392                Duration_32_Bits_On_Target := True;
11393             end if;
11394
11395             --  Set appropriate restrictions
11396
11397             Set_Restriction (No_Finalization, N);
11398             Set_Restriction (No_Exception_Handlers, N);
11399             Set_Restriction (Max_Tasks, N, 0);
11400             Set_Restriction (No_Tasking, N);
11401
11402          ------------------------
11403          -- No_Strict_Aliasing --
11404          ------------------------
11405
11406          --  pragma No_Strict_Aliasing [([Entity =>] type_LOCAL_NAME)];
11407
11408          when Pragma_No_Strict_Aliasing => No_Strict_Aliasing : declare
11409             E_Id : Entity_Id;
11410
11411          begin
11412             GNAT_Pragma;
11413             Check_At_Most_N_Arguments (1);
11414
11415             if Arg_Count = 0 then
11416                Check_Valid_Configuration_Pragma;
11417                Opt.No_Strict_Aliasing := True;
11418
11419             else
11420                Check_Optional_Identifier (Arg2, Name_Entity);
11421                Check_Arg_Is_Local_Name (Arg1);
11422                E_Id := Entity (Get_Pragma_Arg (Arg1));
11423
11424                if E_Id = Any_Type then
11425                   return;
11426                elsif No (E_Id) or else not Is_Access_Type (E_Id) then
11427                   Error_Pragma_Arg ("pragma% requires access type", Arg1);
11428                end if;
11429
11430                Set_No_Strict_Aliasing (Implementation_Base_Type (E_Id));
11431             end if;
11432          end No_Strict_Aliasing;
11433
11434          -----------------------
11435          -- Normalize_Scalars --
11436          -----------------------
11437
11438          --  pragma Normalize_Scalars;
11439
11440          when Pragma_Normalize_Scalars =>
11441             Check_Ada_83_Warning;
11442             Check_Arg_Count (0);
11443             Check_Valid_Configuration_Pragma;
11444
11445             --  Normalize_Scalars creates false positives in CodePeer, and
11446             --  incorrect negative results in Alfa mode, so ignore this pragma
11447             --  in these modes.
11448
11449             if not (CodePeer_Mode or Alfa_Mode) then
11450                Normalize_Scalars := True;
11451                Init_Or_Norm_Scalars := True;
11452             end if;
11453
11454          -----------------
11455          -- Obsolescent --
11456          -----------------
11457
11458          --  pragma Obsolescent;
11459
11460          --  pragma Obsolescent (
11461          --    [Message =>] static_string_EXPRESSION
11462          --  [,[Version =>] Ada_05]]);
11463
11464          --  pragma Obsolescent (
11465          --    [Entity  =>] NAME
11466          --  [,[Message =>] static_string_EXPRESSION
11467          --  [,[Version =>] Ada_05]] );
11468
11469          when Pragma_Obsolescent => Obsolescent : declare
11470             Ename : Node_Id;
11471             Decl  : Node_Id;
11472
11473             procedure Set_Obsolescent (E : Entity_Id);
11474             --  Given an entity Ent, mark it as obsolescent if appropriate
11475
11476             ---------------------
11477             -- Set_Obsolescent --
11478             ---------------------
11479
11480             procedure Set_Obsolescent (E : Entity_Id) is
11481                Active : Boolean;
11482                Ent    : Entity_Id;
11483                S      : String_Id;
11484
11485             begin
11486                Active := True;
11487                Ent    := E;
11488
11489                --  Entity name was given
11490
11491                if Present (Ename) then
11492
11493                   --  If entity name matches, we are fine. Save entity in
11494                   --  pragma argument, for ASIS use.
11495
11496                   if Chars (Ename) = Chars (Ent) then
11497                      Set_Entity (Ename, Ent);
11498                      Generate_Reference (Ent, Ename);
11499
11500                   --  If entity name does not match, only possibility is an
11501                   --  enumeration literal from an enumeration type declaration.
11502
11503                   elsif Ekind (Ent) /= E_Enumeration_Type then
11504                      Error_Pragma
11505                        ("pragma % entity name does not match declaration");
11506
11507                   else
11508                      Ent := First_Literal (E);
11509                      loop
11510                         if No (Ent) then
11511                            Error_Pragma
11512                              ("pragma % entity name does not match any " &
11513                               "enumeration literal");
11514
11515                         elsif Chars (Ent) = Chars (Ename) then
11516                            Set_Entity (Ename, Ent);
11517                            Generate_Reference (Ent, Ename);
11518                            exit;
11519
11520                         else
11521                            Ent := Next_Literal (Ent);
11522                         end if;
11523                      end loop;
11524                   end if;
11525                end if;
11526
11527                --  Ent points to entity to be marked
11528
11529                if Arg_Count >= 1 then
11530
11531                   --  Deal with static string argument
11532
11533                   Check_Arg_Is_Static_Expression (Arg1, Standard_String);
11534                   S := Strval (Get_Pragma_Arg (Arg1));
11535
11536                   for J in 1 .. String_Length (S) loop
11537                      if not In_Character_Range (Get_String_Char (S, J)) then
11538                         Error_Pragma_Arg
11539                           ("pragma% argument does not allow wide characters",
11540                            Arg1);
11541                      end if;
11542                   end loop;
11543
11544                   Obsolescent_Warnings.Append
11545                     ((Ent => Ent, Msg => Strval (Get_Pragma_Arg (Arg1))));
11546
11547                   --  Check for Ada_05 parameter
11548
11549                   if Arg_Count /= 1 then
11550                      Check_Arg_Count (2);
11551
11552                      declare
11553                         Argx : constant Node_Id := Get_Pragma_Arg (Arg2);
11554
11555                      begin
11556                         Check_Arg_Is_Identifier (Argx);
11557
11558                         if Chars (Argx) /= Name_Ada_05 then
11559                            Error_Msg_Name_2 := Name_Ada_05;
11560                            Error_Pragma_Arg
11561                              ("only allowed argument for pragma% is %", Argx);
11562                         end if;
11563
11564                         if Ada_Version_Explicit < Ada_2005
11565                           or else not Warn_On_Ada_2005_Compatibility
11566                         then
11567                            Active := False;
11568                         end if;
11569                      end;
11570                   end if;
11571                end if;
11572
11573                --  Set flag if pragma active
11574
11575                if Active then
11576                   Set_Is_Obsolescent (Ent);
11577                end if;
11578
11579                return;
11580             end Set_Obsolescent;
11581
11582          --  Start of processing for pragma Obsolescent
11583
11584          begin
11585             GNAT_Pragma;
11586
11587             Check_At_Most_N_Arguments (3);
11588
11589             --  See if first argument specifies an entity name
11590
11591             if Arg_Count >= 1
11592               and then
11593                 (Chars (Arg1) = Name_Entity
11594                    or else
11595                      Nkind_In (Get_Pragma_Arg (Arg1), N_Character_Literal,
11596                                                       N_Identifier,
11597                                                       N_Operator_Symbol))
11598             then
11599                Ename := Get_Pragma_Arg (Arg1);
11600
11601                --  Eliminate first argument, so we can share processing
11602
11603                Arg1 := Arg2;
11604                Arg2 := Arg3;
11605                Arg_Count := Arg_Count - 1;
11606
11607             --  No Entity name argument given
11608
11609             else
11610                Ename := Empty;
11611             end if;
11612
11613             if Arg_Count >= 1 then
11614                Check_Optional_Identifier (Arg1, Name_Message);
11615
11616                if Arg_Count = 2 then
11617                   Check_Optional_Identifier (Arg2, Name_Version);
11618                end if;
11619             end if;
11620
11621             --  Get immediately preceding declaration
11622
11623             Decl := Prev (N);
11624             while Present (Decl) and then Nkind (Decl) = N_Pragma loop
11625                Prev (Decl);
11626             end loop;
11627
11628             --  Cases where we do not follow anything other than another pragma
11629
11630             if No (Decl) then
11631
11632                --  First case: library level compilation unit declaration with
11633                --  the pragma immediately following the declaration.
11634
11635                if Nkind (Parent (N)) = N_Compilation_Unit_Aux then
11636                   Set_Obsolescent
11637                     (Defining_Entity (Unit (Parent (Parent (N)))));
11638                   return;
11639
11640                --  Case 2: library unit placement for package
11641
11642                else
11643                   declare
11644                      Ent : constant Entity_Id := Find_Lib_Unit_Name;
11645                   begin
11646                      if Is_Package_Or_Generic_Package (Ent) then
11647                         Set_Obsolescent (Ent);
11648                         return;
11649                      end if;
11650                   end;
11651                end if;
11652
11653             --  Cases where we must follow a declaration
11654
11655             else
11656                if         Nkind (Decl) not in N_Declaration
11657                  and then Nkind (Decl) not in N_Later_Decl_Item
11658                  and then Nkind (Decl) not in N_Generic_Declaration
11659                  and then Nkind (Decl) not in N_Renaming_Declaration
11660                then
11661                   Error_Pragma
11662                     ("pragma% misplaced, "
11663                      & "must immediately follow a declaration");
11664
11665                else
11666                   Set_Obsolescent (Defining_Entity (Decl));
11667                   return;
11668                end if;
11669             end if;
11670          end Obsolescent;
11671
11672          --------------
11673          -- Optimize --
11674          --------------
11675
11676          --  pragma Optimize (Time | Space | Off);
11677
11678          --  The actual check for optimize is done in Gigi. Note that this
11679          --  pragma does not actually change the optimization setting, it
11680          --  simply checks that it is consistent with the pragma.
11681
11682          when Pragma_Optimize =>
11683             Check_No_Identifiers;
11684             Check_Arg_Count (1);
11685             Check_Arg_Is_One_Of (Arg1, Name_Time, Name_Space, Name_Off);
11686
11687          ------------------------
11688          -- Optimize_Alignment --
11689          ------------------------
11690
11691          --  pragma Optimize_Alignment (Time | Space | Off);
11692
11693          when Pragma_Optimize_Alignment => Optimize_Alignment : begin
11694             GNAT_Pragma;
11695             Check_No_Identifiers;
11696             Check_Arg_Count (1);
11697             Check_Valid_Configuration_Pragma;
11698
11699             declare
11700                Nam : constant Name_Id := Chars (Get_Pragma_Arg (Arg1));
11701             begin
11702                case Nam is
11703                   when Name_Time =>
11704                      Opt.Optimize_Alignment := 'T';
11705                   when Name_Space =>
11706                      Opt.Optimize_Alignment := 'S';
11707                   when Name_Off =>
11708                      Opt.Optimize_Alignment := 'O';
11709                   when others =>
11710                      Error_Pragma_Arg ("invalid argument for pragma%", Arg1);
11711                end case;
11712             end;
11713
11714             --  Set indication that mode is set locally. If we are in fact in a
11715             --  configuration pragma file, this setting is harmless since the
11716             --  switch will get reset anyway at the start of each unit.
11717
11718             Optimize_Alignment_Local := True;
11719          end Optimize_Alignment;
11720
11721          -------------
11722          -- Ordered --
11723          -------------
11724
11725          --  pragma Ordered (first_enumeration_subtype_LOCAL_NAME);
11726
11727          when Pragma_Ordered => Ordered : declare
11728             Assoc   : constant Node_Id := Arg1;
11729             Type_Id : Node_Id;
11730             Typ     : Entity_Id;
11731
11732          begin
11733             GNAT_Pragma;
11734             Check_No_Identifiers;
11735             Check_Arg_Count (1);
11736             Check_Arg_Is_Local_Name (Arg1);
11737
11738             Type_Id := Get_Pragma_Arg (Assoc);
11739             Find_Type (Type_Id);
11740             Typ := Entity (Type_Id);
11741
11742             if Typ = Any_Type then
11743                return;
11744             else
11745                Typ := Underlying_Type (Typ);
11746             end if;
11747
11748             if not Is_Enumeration_Type (Typ) then
11749                Error_Pragma ("pragma% must specify enumeration type");
11750             end if;
11751
11752             Check_First_Subtype (Arg1);
11753             Set_Has_Pragma_Ordered (Base_Type (Typ));
11754          end Ordered;
11755
11756          ----------
11757          -- Pack --
11758          ----------
11759
11760          --  pragma Pack (first_subtype_LOCAL_NAME);
11761
11762          when Pragma_Pack => Pack : declare
11763             Assoc   : constant Node_Id := Arg1;
11764             Type_Id : Node_Id;
11765             Typ     : Entity_Id;
11766             Ctyp    : Entity_Id;
11767             Ignore  : Boolean := False;
11768
11769          begin
11770             Check_No_Identifiers;
11771             Check_Arg_Count (1);
11772             Check_Arg_Is_Local_Name (Arg1);
11773
11774             Type_Id := Get_Pragma_Arg (Assoc);
11775             Find_Type (Type_Id);
11776             Typ := Entity (Type_Id);
11777
11778             if Typ = Any_Type
11779               or else Rep_Item_Too_Early (Typ, N)
11780             then
11781                return;
11782             else
11783                Typ := Underlying_Type (Typ);
11784             end if;
11785
11786             if not Is_Array_Type (Typ) and then not Is_Record_Type (Typ) then
11787                Error_Pragma ("pragma% must specify array or record type");
11788             end if;
11789
11790             Check_First_Subtype (Arg1);
11791             Check_Duplicate_Pragma (Typ);
11792
11793             --  Array type
11794
11795             if Is_Array_Type (Typ) then
11796                Ctyp := Component_Type (Typ);
11797
11798                --  Ignore pack that does nothing
11799
11800                if Known_Static_Esize (Ctyp)
11801                  and then Known_Static_RM_Size (Ctyp)
11802                  and then Esize (Ctyp) = RM_Size (Ctyp)
11803                  and then Addressable (Esize (Ctyp))
11804                then
11805                   Ignore := True;
11806                end if;
11807
11808                --  Process OK pragma Pack. Note that if there is a separate
11809                --  component clause present, the Pack will be cancelled. This
11810                --  processing is in Freeze.
11811
11812                if not Rep_Item_Too_Late (Typ, N) then
11813
11814                   --  In the context of static code analysis, we do not need
11815                   --  complex front-end expansions related to pragma Pack,
11816                   --  so disable handling of pragma Pack in these cases.
11817
11818                   if CodePeer_Mode or Alfa_Mode then
11819                      null;
11820
11821                   --  Don't attempt any packing for VM targets. We possibly
11822                   --  could deal with some cases of array bit-packing, but we
11823                   --  don't bother, since this is not a typical kind of
11824                   --  representation in the VM context anyway (and would not
11825                   --  for example work nicely with the debugger).
11826
11827                   elsif VM_Target /= No_VM then
11828                      if not GNAT_Mode then
11829                         Error_Pragma
11830                           ("?pragma% ignored in this configuration");
11831                      end if;
11832
11833                   --  Normal case where we do the pack action
11834
11835                   else
11836                      if not Ignore then
11837                         Set_Is_Packed            (Base_Type (Typ));
11838                         Set_Has_Non_Standard_Rep (Base_Type (Typ));
11839                      end if;
11840
11841                      Set_Has_Pragma_Pack (Base_Type (Typ));
11842                   end if;
11843                end if;
11844
11845             --  For record types, the pack is always effective
11846
11847             else pragma Assert (Is_Record_Type (Typ));
11848                if not Rep_Item_Too_Late (Typ, N) then
11849
11850                   --  Ignore pack request with warning in VM mode (skip warning
11851                   --  if we are compiling GNAT run time library).
11852
11853                   if VM_Target /= No_VM then
11854                      if not GNAT_Mode then
11855                         Error_Pragma
11856                           ("?pragma% ignored in this configuration");
11857                      end if;
11858
11859                   --  Normal case of pack request active
11860
11861                   else
11862                      Set_Is_Packed            (Base_Type (Typ));
11863                      Set_Has_Pragma_Pack      (Base_Type (Typ));
11864                      Set_Has_Non_Standard_Rep (Base_Type (Typ));
11865                   end if;
11866                end if;
11867             end if;
11868          end Pack;
11869
11870          ----------
11871          -- Page --
11872          ----------
11873
11874          --  pragma Page;
11875
11876          --  There is nothing to do here, since we did all the processing for
11877          --  this pragma in Par.Prag (so that it works properly even in syntax
11878          --  only mode).
11879
11880          when Pragma_Page =>
11881             null;
11882
11883          -------------
11884          -- Passive --
11885          -------------
11886
11887          --  pragma Passive [(PASSIVE_FORM)];
11888
11889          --  PASSIVE_FORM ::= Semaphore | No
11890
11891          when Pragma_Passive =>
11892             GNAT_Pragma;
11893
11894             if Nkind (Parent (N)) /= N_Task_Definition then
11895                Error_Pragma ("pragma% must be within task definition");
11896             end if;
11897
11898             if Arg_Count /= 0 then
11899                Check_Arg_Count (1);
11900                Check_Arg_Is_One_Of (Arg1, Name_Semaphore, Name_No);
11901             end if;
11902
11903          ----------------------------------
11904          -- Preelaborable_Initialization --
11905          ----------------------------------
11906
11907          --  pragma Preelaborable_Initialization (DIRECT_NAME);
11908
11909          when Pragma_Preelaborable_Initialization => Preelab_Init : declare
11910             Ent : Entity_Id;
11911
11912          begin
11913             Ada_2005_Pragma;
11914             Check_Arg_Count (1);
11915             Check_No_Identifiers;
11916             Check_Arg_Is_Identifier (Arg1);
11917             Check_Arg_Is_Local_Name (Arg1);
11918             Check_First_Subtype (Arg1);
11919             Ent := Entity (Get_Pragma_Arg (Arg1));
11920
11921             if not (Is_Private_Type (Ent)
11922                       or else
11923                     Is_Protected_Type (Ent)
11924                       or else
11925                     (Is_Generic_Type (Ent) and then Is_Derived_Type (Ent)))
11926             then
11927                Error_Pragma_Arg
11928                  ("pragma % can only be applied to private, formal derived or "
11929                   & "protected type",
11930                   Arg1);
11931             end if;
11932
11933             --  Give an error if the pragma is applied to a protected type that
11934             --  does not qualify (due to having entries, or due to components
11935             --  that do not qualify).
11936
11937             if Is_Protected_Type (Ent)
11938               and then not Has_Preelaborable_Initialization (Ent)
11939             then
11940                Error_Msg_N
11941                  ("protected type & does not have preelaborable " &
11942                   "initialization", Ent);
11943
11944             --  Otherwise mark the type as definitely having preelaborable
11945             --  initialization.
11946
11947             else
11948                Set_Known_To_Have_Preelab_Init (Ent);
11949             end if;
11950
11951             if Has_Pragma_Preelab_Init (Ent)
11952               and then Warn_On_Redundant_Constructs
11953             then
11954                Error_Pragma ("?duplicate pragma%!");
11955             else
11956                Set_Has_Pragma_Preelab_Init (Ent);
11957             end if;
11958          end Preelab_Init;
11959
11960          --------------------
11961          -- Persistent_BSS --
11962          --------------------
11963
11964          --  pragma Persistent_BSS [(object_NAME)];
11965
11966          when Pragma_Persistent_BSS => Persistent_BSS :  declare
11967             Decl : Node_Id;
11968             Ent  : Entity_Id;
11969             Prag : Node_Id;
11970
11971          begin
11972             GNAT_Pragma;
11973             Check_At_Most_N_Arguments (1);
11974
11975             --  Case of application to specific object (one argument)
11976
11977             if Arg_Count = 1 then
11978                Check_Arg_Is_Library_Level_Local_Name (Arg1);
11979
11980                if not Is_Entity_Name (Get_Pragma_Arg (Arg1))
11981                  or else not
11982                   Ekind_In (Entity (Get_Pragma_Arg (Arg1)), E_Variable,
11983                                                             E_Constant)
11984                then
11985                   Error_Pragma_Arg ("pragma% only applies to objects", Arg1);
11986                end if;
11987
11988                Ent := Entity (Get_Pragma_Arg (Arg1));
11989                Decl := Parent (Ent);
11990
11991                if Rep_Item_Too_Late (Ent, N) then
11992                   return;
11993                end if;
11994
11995                if Present (Expression (Decl)) then
11996                   Error_Pragma_Arg
11997                     ("object for pragma% cannot have initialization", Arg1);
11998                end if;
11999
12000                if not Is_Potentially_Persistent_Type (Etype (Ent)) then
12001                   Error_Pragma_Arg
12002                     ("object type for pragma% is not potentially persistent",
12003                      Arg1);
12004                end if;
12005
12006                Check_Duplicate_Pragma (Ent);
12007
12008                Prag :=
12009                  Make_Linker_Section_Pragma
12010                    (Ent, Sloc (N), ".persistent.bss");
12011                Insert_After (N, Prag);
12012                Analyze (Prag);
12013
12014             --  Case of use as configuration pragma with no arguments
12015
12016             else
12017                Check_Valid_Configuration_Pragma;
12018                Persistent_BSS_Mode := True;
12019             end if;
12020          end Persistent_BSS;
12021
12022          -------------
12023          -- Polling --
12024          -------------
12025
12026          --  pragma Polling (ON | OFF);
12027
12028          when Pragma_Polling =>
12029             GNAT_Pragma;
12030             Check_Arg_Count (1);
12031             Check_No_Identifiers;
12032             Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
12033             Polling_Required := (Chars (Get_Pragma_Arg (Arg1)) = Name_On);
12034
12035          -------------------
12036          -- Postcondition --
12037          -------------------
12038
12039          --  pragma Postcondition ([Check   =>] Boolean_EXPRESSION
12040          --                      [,[Message =>] String_EXPRESSION]);
12041
12042          when Pragma_Postcondition => Postcondition : declare
12043             In_Body : Boolean;
12044             pragma Warnings (Off, In_Body);
12045
12046          begin
12047             GNAT_Pragma;
12048             Check_At_Least_N_Arguments (1);
12049             Check_At_Most_N_Arguments (2);
12050             Check_Optional_Identifier (Arg1, Name_Check);
12051
12052             --  All we need to do here is call the common check procedure,
12053             --  the remainder of the processing is found in Sem_Ch6/Sem_Ch7.
12054
12055             Check_Precondition_Postcondition (In_Body);
12056          end Postcondition;
12057
12058          ------------------
12059          -- Precondition --
12060          ------------------
12061
12062          --  pragma Precondition ([Check   =>] Boolean_EXPRESSION
12063          --                     [,[Message =>] String_EXPRESSION]);
12064
12065          when Pragma_Precondition => Precondition : declare
12066             In_Body : Boolean;
12067
12068          begin
12069             GNAT_Pragma;
12070             Check_At_Least_N_Arguments (1);
12071             Check_At_Most_N_Arguments (2);
12072             Check_Optional_Identifier (Arg1, Name_Check);
12073             Check_Precondition_Postcondition (In_Body);
12074
12075             --  If in spec, nothing more to do. If in body, then we convert the
12076             --  pragma to pragma Check (Precondition, cond [, msg]). Note we do
12077             --  this whether or not precondition checks are enabled. That works
12078             --  fine since pragma Check will do this check, and will also
12079             --  analyze the condition itself in the proper context.
12080
12081             if In_Body then
12082                Rewrite (N,
12083                  Make_Pragma (Loc,
12084                    Chars => Name_Check,
12085                    Pragma_Argument_Associations => New_List (
12086                      Make_Pragma_Argument_Association (Loc,
12087                        Expression => Make_Identifier (Loc, Name_Precondition)),
12088
12089                      Make_Pragma_Argument_Association (Sloc (Arg1),
12090                        Expression => Relocate_Node (Get_Pragma_Arg (Arg1))))));
12091
12092                if Arg_Count = 2 then
12093                   Append_To (Pragma_Argument_Associations (N),
12094                     Make_Pragma_Argument_Association (Sloc (Arg2),
12095                       Expression => Relocate_Node (Get_Pragma_Arg (Arg2))));
12096                end if;
12097
12098                Analyze (N);
12099             end if;
12100          end Precondition;
12101
12102          ---------------
12103          -- Predicate --
12104          ---------------
12105
12106          --  pragma Predicate
12107          --    ([Entity =>] type_LOCAL_NAME,
12108          --     [Check  =>] EXPRESSION);
12109
12110          when Pragma_Predicate => Predicate : declare
12111             Type_Id : Node_Id;
12112             Typ     : Entity_Id;
12113
12114             Discard : Boolean;
12115             pragma Unreferenced (Discard);
12116
12117          begin
12118             GNAT_Pragma;
12119             Check_Arg_Count (2);
12120             Check_Optional_Identifier (Arg1, Name_Entity);
12121             Check_Optional_Identifier (Arg2, Name_Check);
12122
12123             Check_Arg_Is_Local_Name (Arg1);
12124
12125             Type_Id := Get_Pragma_Arg (Arg1);
12126             Find_Type (Type_Id);
12127             Typ := Entity (Type_Id);
12128
12129             if Typ = Any_Type then
12130                return;
12131             end if;
12132
12133             --  The remaining processing is simply to link the pragma on to
12134             --  the rep item chain, for processing when the type is frozen.
12135             --  This is accomplished by a call to Rep_Item_Too_Late. We also
12136             --  mark the type as having predicates.
12137
12138             Set_Has_Predicates (Typ);
12139             Discard := Rep_Item_Too_Late (Typ, N, FOnly => True);
12140          end Predicate;
12141
12142          ------------------
12143          -- Preelaborate --
12144          ------------------
12145
12146          --  pragma Preelaborate [(library_unit_NAME)];
12147
12148          --  Set the flag Is_Preelaborated of program unit name entity
12149
12150          when Pragma_Preelaborate => Preelaborate : declare
12151             Pa  : constant Node_Id   := Parent (N);
12152             Pk  : constant Node_Kind := Nkind (Pa);
12153             Ent : Entity_Id;
12154
12155          begin
12156             Check_Ada_83_Warning;
12157             Check_Valid_Library_Unit_Pragma;
12158
12159             if Nkind (N) = N_Null_Statement then
12160                return;
12161             end if;
12162
12163             Ent := Find_Lib_Unit_Name;
12164             Check_Duplicate_Pragma (Ent);
12165
12166             --  This filters out pragmas inside generic parent then
12167             --  show up inside instantiation
12168
12169             if Present (Ent)
12170               and then not (Pk = N_Package_Specification
12171                              and then Present (Generic_Parent (Pa)))
12172             then
12173                if not Debug_Flag_U then
12174                   Set_Is_Preelaborated (Ent);
12175                   Set_Suppress_Elaboration_Warnings (Ent);
12176                end if;
12177             end if;
12178          end Preelaborate;
12179
12180          ---------------------
12181          -- Preelaborate_05 --
12182          ---------------------
12183
12184          --  pragma Preelaborate_05 [(library_unit_NAME)];
12185
12186          --  This pragma is useable only in GNAT_Mode, where it is used like
12187          --  pragma Preelaborate but it is only effective in Ada 2005 mode
12188          --  (otherwise it is ignored). This is used to implement AI-362 which
12189          --  recategorizes some run-time packages in Ada 2005 mode.
12190
12191          when Pragma_Preelaborate_05 => Preelaborate_05 : declare
12192             Ent : Entity_Id;
12193
12194          begin
12195             GNAT_Pragma;
12196             Check_Valid_Library_Unit_Pragma;
12197
12198             if not GNAT_Mode then
12199                Error_Pragma ("pragma% only available in GNAT mode");
12200             end if;
12201
12202             if Nkind (N) = N_Null_Statement then
12203                return;
12204             end if;
12205
12206             --  This is one of the few cases where we need to test the value of
12207             --  Ada_Version_Explicit rather than Ada_Version (which is always
12208             --  set to Ada_2012 in a predefined unit), we need to know the
12209             --  explicit version set to know if this pragma is active.
12210
12211             if Ada_Version_Explicit >= Ada_2005 then
12212                Ent := Find_Lib_Unit_Name;
12213                Set_Is_Preelaborated (Ent);
12214                Set_Suppress_Elaboration_Warnings (Ent);
12215             end if;
12216          end Preelaborate_05;
12217
12218          --------------
12219          -- Priority --
12220          --------------
12221
12222          --  pragma Priority (EXPRESSION);
12223
12224          when Pragma_Priority => Priority : declare
12225             P   : constant Node_Id := Parent (N);
12226             Arg : Node_Id;
12227
12228          begin
12229             Check_No_Identifiers;
12230             Check_Arg_Count (1);
12231
12232             --  Subprogram case
12233
12234             if Nkind (P) = N_Subprogram_Body then
12235                Check_In_Main_Program;
12236
12237                Arg := Get_Pragma_Arg (Arg1);
12238                Analyze_And_Resolve (Arg, Standard_Integer);
12239
12240                --  Must be static
12241
12242                if not Is_Static_Expression (Arg) then
12243                   Flag_Non_Static_Expr
12244                     ("main subprogram priority is not static!", Arg);
12245                   raise Pragma_Exit;
12246
12247                --  If constraint error, then we already signalled an error
12248
12249                elsif Raises_Constraint_Error (Arg) then
12250                   null;
12251
12252                --  Otherwise check in range
12253
12254                else
12255                   declare
12256                      Val : constant Uint := Expr_Value (Arg);
12257
12258                   begin
12259                      if Val < 0
12260                        or else Val > Expr_Value (Expression
12261                                        (Parent (RTE (RE_Max_Priority))))
12262                      then
12263                         Error_Pragma_Arg
12264                           ("main subprogram priority is out of range", Arg1);
12265                      end if;
12266                   end;
12267                end if;
12268
12269                Set_Main_Priority
12270                     (Current_Sem_Unit, UI_To_Int (Expr_Value (Arg)));
12271
12272                --  Load an arbitrary entity from System.Tasking to make sure
12273                --  this package is implicitly with'ed, since we need to have
12274                --  the tasking run-time active for the pragma Priority to have
12275                --  any effect.
12276
12277                declare
12278                   Discard : Entity_Id;
12279                   pragma Warnings (Off, Discard);
12280                begin
12281                   Discard := RTE (RE_Task_List);
12282                end;
12283
12284             --  Task or Protected, must be of type Integer
12285
12286             elsif Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12287                Arg := Get_Pragma_Arg (Arg1);
12288
12289                --  The expression must be analyzed in the special manner
12290                --  described in "Handling of Default and Per-Object
12291                --  Expressions" in sem.ads.
12292
12293                Preanalyze_Spec_Expression (Arg, Standard_Integer);
12294
12295                if not Is_Static_Expression (Arg) then
12296                   Check_Restriction (Static_Priorities, Arg);
12297                end if;
12298
12299             --  Anything else is incorrect
12300
12301             else
12302                Pragma_Misplaced;
12303             end if;
12304
12305             if Has_Pragma_Priority (P) then
12306                Error_Pragma ("duplicate pragma% not allowed");
12307             else
12308                Set_Has_Pragma_Priority (P, True);
12309
12310                if Nkind_In (P, N_Protected_Definition, N_Task_Definition) then
12311                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12312                   --  exp_ch9 should use this ???
12313                end if;
12314             end if;
12315          end Priority;
12316
12317          -----------------------------------
12318          -- Priority_Specific_Dispatching --
12319          -----------------------------------
12320
12321          --  pragma Priority_Specific_Dispatching (
12322          --    policy_IDENTIFIER,
12323          --    first_priority_EXPRESSION,
12324          --    last_priority_EXPRESSION);
12325
12326          when Pragma_Priority_Specific_Dispatching =>
12327          Priority_Specific_Dispatching : declare
12328             Prio_Id : constant Entity_Id := RTE (RE_Any_Priority);
12329             --  This is the entity System.Any_Priority;
12330
12331             DP          : Character;
12332             Lower_Bound : Node_Id;
12333             Upper_Bound : Node_Id;
12334             Lower_Val   : Uint;
12335             Upper_Val   : Uint;
12336
12337          begin
12338             Ada_2005_Pragma;
12339             Check_Arg_Count (3);
12340             Check_No_Identifiers;
12341             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
12342             Check_Valid_Configuration_Pragma;
12343             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12344             DP := Fold_Upper (Name_Buffer (1));
12345
12346             Lower_Bound := Get_Pragma_Arg (Arg2);
12347             Check_Arg_Is_Static_Expression (Lower_Bound, Standard_Integer);
12348             Lower_Val := Expr_Value (Lower_Bound);
12349
12350             Upper_Bound := Get_Pragma_Arg (Arg3);
12351             Check_Arg_Is_Static_Expression (Upper_Bound, Standard_Integer);
12352             Upper_Val := Expr_Value (Upper_Bound);
12353
12354             --  It is not allowed to use Task_Dispatching_Policy and
12355             --  Priority_Specific_Dispatching in the same partition.
12356
12357             if Task_Dispatching_Policy /= ' ' then
12358                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12359                Error_Pragma
12360                  ("pragma% incompatible with Task_Dispatching_Policy#");
12361
12362             --  Check lower bound in range
12363
12364             elsif Lower_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12365                     or else
12366                   Lower_Val > Expr_Value (Type_High_Bound (Prio_Id))
12367             then
12368                Error_Pragma_Arg
12369                  ("first_priority is out of range", Arg2);
12370
12371             --  Check upper bound in range
12372
12373             elsif Upper_Val < Expr_Value (Type_Low_Bound (Prio_Id))
12374                     or else
12375                   Upper_Val > Expr_Value (Type_High_Bound (Prio_Id))
12376             then
12377                Error_Pragma_Arg
12378                  ("last_priority is out of range", Arg3);
12379
12380             --  Check that the priority range is valid
12381
12382             elsif Lower_Val > Upper_Val then
12383                Error_Pragma
12384                  ("last_priority_expression must be greater than" &
12385                   " or equal to first_priority_expression");
12386
12387             --  Store the new policy, but always preserve System_Location since
12388             --  we like the error message with the run-time name.
12389
12390             else
12391                --  Check overlapping in the priority ranges specified in other
12392                --  Priority_Specific_Dispatching pragmas within the same
12393                --  partition. We can only check those we know about!
12394
12395                for J in
12396                   Specific_Dispatching.First .. Specific_Dispatching.Last
12397                loop
12398                   if Specific_Dispatching.Table (J).First_Priority in
12399                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12400                   or else Specific_Dispatching.Table (J).Last_Priority in
12401                     UI_To_Int (Lower_Val) .. UI_To_Int (Upper_Val)
12402                   then
12403                      Error_Msg_Sloc :=
12404                        Specific_Dispatching.Table (J).Pragma_Loc;
12405                         Error_Pragma
12406                           ("priority range overlaps with "
12407                            & "Priority_Specific_Dispatching#");
12408                   end if;
12409                end loop;
12410
12411                --  The use of Priority_Specific_Dispatching is incompatible
12412                --  with Task_Dispatching_Policy.
12413
12414                if Task_Dispatching_Policy /= ' ' then
12415                   Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
12416                      Error_Pragma
12417                        ("Priority_Specific_Dispatching incompatible "
12418                         & "with Task_Dispatching_Policy#");
12419                end if;
12420
12421                --  The use of Priority_Specific_Dispatching forces ceiling
12422                --  locking policy.
12423
12424                if Locking_Policy /= ' ' and then Locking_Policy /= 'C' then
12425                   Error_Msg_Sloc := Locking_Policy_Sloc;
12426                      Error_Pragma
12427                        ("Priority_Specific_Dispatching incompatible "
12428                         & "with Locking_Policy#");
12429
12430                --  Set the Ceiling_Locking policy, but preserve System_Location
12431                --  since we like the error message with the run time name.
12432
12433                else
12434                   Locking_Policy := 'C';
12435
12436                   if Locking_Policy_Sloc /= System_Location then
12437                      Locking_Policy_Sloc := Loc;
12438                   end if;
12439                end if;
12440
12441                --  Add entry in the table
12442
12443                Specific_Dispatching.Append
12444                     ((Dispatching_Policy => DP,
12445                       First_Priority     => UI_To_Int (Lower_Val),
12446                       Last_Priority      => UI_To_Int (Upper_Val),
12447                       Pragma_Loc         => Loc));
12448             end if;
12449          end Priority_Specific_Dispatching;
12450
12451          -------------
12452          -- Profile --
12453          -------------
12454
12455          --  pragma Profile (profile_IDENTIFIER);
12456
12457          --  profile_IDENTIFIER => Restricted | Ravenscar
12458
12459          when Pragma_Profile =>
12460             Ada_2005_Pragma;
12461             Check_Arg_Count (1);
12462             Check_Valid_Configuration_Pragma;
12463             Check_No_Identifiers;
12464
12465             declare
12466                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12467
12468             begin
12469                if Chars (Argx) = Name_Ravenscar then
12470                   Set_Ravenscar_Profile (N);
12471
12472                elsif Chars (Argx) = Name_Restricted then
12473                   Set_Profile_Restrictions
12474                     (Restricted,
12475                      N, Warn => Treat_Restrictions_As_Warnings);
12476
12477                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12478                   Set_Profile_Restrictions
12479                     (No_Implementation_Extensions,
12480                      N, Warn => Treat_Restrictions_As_Warnings);
12481
12482                else
12483                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12484                end if;
12485             end;
12486
12487          ----------------------
12488          -- Profile_Warnings --
12489          ----------------------
12490
12491          --  pragma Profile_Warnings (profile_IDENTIFIER);
12492
12493          --  profile_IDENTIFIER => Restricted | Ravenscar
12494
12495          when Pragma_Profile_Warnings =>
12496             GNAT_Pragma;
12497             Check_Arg_Count (1);
12498             Check_Valid_Configuration_Pragma;
12499             Check_No_Identifiers;
12500
12501             declare
12502                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
12503
12504             begin
12505                if Chars (Argx) = Name_Ravenscar then
12506                   Set_Profile_Restrictions (Ravenscar, N, Warn => True);
12507
12508                elsif Chars (Argx) = Name_Restricted then
12509                   Set_Profile_Restrictions (Restricted, N, Warn => True);
12510
12511                elsif Chars (Argx) = Name_No_Implementation_Extensions then
12512                   Set_Profile_Restrictions
12513                     (No_Implementation_Extensions, N, Warn => True);
12514
12515                else
12516                   Error_Pragma_Arg ("& is not a valid profile", Argx);
12517                end if;
12518             end;
12519
12520          --------------------------
12521          -- Propagate_Exceptions --
12522          --------------------------
12523
12524          --  pragma Propagate_Exceptions;
12525
12526          --  Note: this pragma is obsolete and has no effect
12527
12528          when Pragma_Propagate_Exceptions =>
12529             GNAT_Pragma;
12530             Check_Arg_Count (0);
12531
12532             if In_Extended_Main_Source_Unit (N) then
12533                Propagate_Exceptions := True;
12534             end if;
12535
12536          ------------------
12537          -- Psect_Object --
12538          ------------------
12539
12540          --  pragma Psect_Object (
12541          --        [Internal =>] LOCAL_NAME,
12542          --     [, [External =>] EXTERNAL_SYMBOL]
12543          --     [, [Size     =>] EXTERNAL_SYMBOL]);
12544
12545          when Pragma_Psect_Object | Pragma_Common_Object =>
12546          Psect_Object : declare
12547             Args  : Args_List (1 .. 3);
12548             Names : constant Name_List (1 .. 3) := (
12549                       Name_Internal,
12550                       Name_External,
12551                       Name_Size);
12552
12553             Internal : Node_Id renames Args (1);
12554             External : Node_Id renames Args (2);
12555             Size     : Node_Id renames Args (3);
12556
12557             Def_Id : Entity_Id;
12558
12559             procedure Check_Too_Long (Arg : Node_Id);
12560             --  Posts message if the argument is an identifier with more
12561             --  than 31 characters, or a string literal with more than
12562             --  31 characters, and we are operating under VMS
12563
12564             --------------------
12565             -- Check_Too_Long --
12566             --------------------
12567
12568             procedure Check_Too_Long (Arg : Node_Id) is
12569                X : constant Node_Id := Original_Node (Arg);
12570
12571             begin
12572                if not Nkind_In (X, N_String_Literal, N_Identifier) then
12573                   Error_Pragma_Arg
12574                     ("inappropriate argument for pragma %", Arg);
12575                end if;
12576
12577                if OpenVMS_On_Target then
12578                   if (Nkind (X) = N_String_Literal
12579                        and then String_Length (Strval (X)) > 31)
12580                     or else
12581                      (Nkind (X) = N_Identifier
12582                        and then Length_Of_Name (Chars (X)) > 31)
12583                   then
12584                      Error_Pragma_Arg
12585                        ("argument for pragma % is longer than 31 characters",
12586                         Arg);
12587                   end if;
12588                end if;
12589             end Check_Too_Long;
12590
12591          --  Start of processing for Common_Object/Psect_Object
12592
12593          begin
12594             GNAT_Pragma;
12595             Gather_Associations (Names, Args);
12596             Process_Extended_Import_Export_Internal_Arg (Internal);
12597
12598             Def_Id := Entity (Internal);
12599
12600             if not Ekind_In (Def_Id, E_Constant, E_Variable) then
12601                Error_Pragma_Arg
12602                  ("pragma% must designate an object", Internal);
12603             end if;
12604
12605             Check_Too_Long (Internal);
12606
12607             if Is_Imported (Def_Id) or else Is_Exported (Def_Id) then
12608                Error_Pragma_Arg
12609                  ("cannot use pragma% for imported/exported object",
12610                   Internal);
12611             end if;
12612
12613             if Is_Concurrent_Type (Etype (Internal)) then
12614                Error_Pragma_Arg
12615                  ("cannot specify pragma % for task/protected object",
12616                   Internal);
12617             end if;
12618
12619             if Has_Rep_Pragma (Def_Id, Name_Common_Object)
12620                  or else
12621                Has_Rep_Pragma (Def_Id, Name_Psect_Object)
12622             then
12623                Error_Msg_N ("?duplicate Common/Psect_Object pragma", N);
12624             end if;
12625
12626             if Ekind (Def_Id) = E_Constant then
12627                Error_Pragma_Arg
12628                  ("cannot specify pragma % for a constant", Internal);
12629             end if;
12630
12631             if Is_Record_Type (Etype (Internal)) then
12632                declare
12633                   Ent  : Entity_Id;
12634                   Decl : Entity_Id;
12635
12636                begin
12637                   Ent := First_Entity (Etype (Internal));
12638                   while Present (Ent) loop
12639                      Decl := Declaration_Node (Ent);
12640
12641                      if Ekind (Ent) = E_Component
12642                        and then Nkind (Decl) = N_Component_Declaration
12643                        and then Present (Expression (Decl))
12644                        and then Warn_On_Export_Import
12645                      then
12646                         Error_Msg_N
12647                           ("?object for pragma % has defaults", Internal);
12648                         exit;
12649
12650                      else
12651                         Next_Entity (Ent);
12652                      end if;
12653                   end loop;
12654                end;
12655             end if;
12656
12657             if Present (Size) then
12658                Check_Too_Long (Size);
12659             end if;
12660
12661             if Present (External) then
12662                Check_Arg_Is_External_Name (External);
12663                Check_Too_Long (External);
12664             end if;
12665
12666             --  If all error tests pass, link pragma on to the rep item chain
12667
12668             Record_Rep_Item (Def_Id, N);
12669          end Psect_Object;
12670
12671          ----------
12672          -- Pure --
12673          ----------
12674
12675          --  pragma Pure [(library_unit_NAME)];
12676
12677          when Pragma_Pure => Pure : declare
12678             Ent : Entity_Id;
12679
12680          begin
12681             Check_Ada_83_Warning;
12682             Check_Valid_Library_Unit_Pragma;
12683
12684             if Nkind (N) = N_Null_Statement then
12685                return;
12686             end if;
12687
12688             Ent := Find_Lib_Unit_Name;
12689             Set_Is_Pure (Ent);
12690             Set_Has_Pragma_Pure (Ent);
12691             Set_Suppress_Elaboration_Warnings (Ent);
12692          end Pure;
12693
12694          -------------
12695          -- Pure_05 --
12696          -------------
12697
12698          --  pragma Pure_05 [(library_unit_NAME)];
12699
12700          --  This pragma is useable only in GNAT_Mode, where it is used like
12701          --  pragma Pure but it is only effective in Ada 2005 mode (otherwise
12702          --  it is ignored). It may be used after a pragma Preelaborate, in
12703          --  which case it overrides the effect of the pragma Preelaborate.
12704          --  This is used to implement AI-362 which recategorizes some run-time
12705          --  packages in Ada 2005 mode.
12706
12707          when Pragma_Pure_05 => Pure_05 : declare
12708             Ent : Entity_Id;
12709
12710          begin
12711             GNAT_Pragma;
12712             Check_Valid_Library_Unit_Pragma;
12713
12714             if not GNAT_Mode then
12715                Error_Pragma ("pragma% only available in GNAT mode");
12716             end if;
12717
12718             if Nkind (N) = N_Null_Statement then
12719                return;
12720             end if;
12721
12722             --  This is one of the few cases where we need to test the value of
12723             --  Ada_Version_Explicit rather than Ada_Version (which is always
12724             --  set to Ada_2012 in a predefined unit), we need to know the
12725             --  explicit version set to know if this pragma is active.
12726
12727             if Ada_Version_Explicit >= Ada_2005 then
12728                Ent := Find_Lib_Unit_Name;
12729                Set_Is_Preelaborated (Ent, False);
12730                Set_Is_Pure (Ent);
12731                Set_Suppress_Elaboration_Warnings (Ent);
12732             end if;
12733          end Pure_05;
12734
12735          -------------
12736          -- Pure_12 --
12737          -------------
12738
12739          --  pragma Pure_12 [(library_unit_NAME)];
12740
12741          --  This pragma is useable only in GNAT_Mode, where it is used like
12742          --  pragma Pure but it is only effective in Ada 2012 mode (otherwise
12743          --  it is ignored). It may be used after a pragma Preelaborate, in
12744          --  which case it overrides the effect of the pragma Preelaborate.
12745          --  This is used to implement AI05-0212 which recategorizes some
12746          --  run-time packages in Ada 2012 mode.
12747
12748          when Pragma_Pure_12 => Pure_12 : declare
12749             Ent : Entity_Id;
12750
12751          begin
12752             GNAT_Pragma;
12753             Check_Valid_Library_Unit_Pragma;
12754
12755             if not GNAT_Mode then
12756                Error_Pragma ("pragma% only available in GNAT mode");
12757             end if;
12758
12759             if Nkind (N) = N_Null_Statement then
12760                return;
12761             end if;
12762
12763             --  This is one of the few cases where we need to test the value of
12764             --  Ada_Version_Explicit rather than Ada_Version (which is always
12765             --  set to Ada_2012 in a predefined unit), we need to know the
12766             --  explicit version set to know if this pragma is active.
12767
12768             if Ada_Version_Explicit >= Ada_2012 then
12769                Ent := Find_Lib_Unit_Name;
12770                Set_Is_Preelaborated (Ent, False);
12771                Set_Is_Pure (Ent);
12772                Set_Suppress_Elaboration_Warnings (Ent);
12773             end if;
12774          end Pure_12;
12775
12776          -------------------
12777          -- Pure_Function --
12778          -------------------
12779
12780          --  pragma Pure_Function ([Entity =>] function_LOCAL_NAME);
12781
12782          when Pragma_Pure_Function => Pure_Function : declare
12783             E_Id      : Node_Id;
12784             E         : Entity_Id;
12785             Def_Id    : Entity_Id;
12786             Effective : Boolean := False;
12787
12788          begin
12789             GNAT_Pragma;
12790             Check_Arg_Count (1);
12791             Check_Optional_Identifier (Arg1, Name_Entity);
12792             Check_Arg_Is_Local_Name (Arg1);
12793             E_Id := Get_Pragma_Arg (Arg1);
12794
12795             if Error_Posted (E_Id) then
12796                return;
12797             end if;
12798
12799             --  Loop through homonyms (overloadings) of referenced entity
12800
12801             E := Entity (E_Id);
12802
12803             if Present (E) then
12804                loop
12805                   Def_Id := Get_Base_Subprogram (E);
12806
12807                   if not Ekind_In (Def_Id, E_Function,
12808                                            E_Generic_Function,
12809                                            E_Operator)
12810                   then
12811                      Error_Pragma_Arg
12812                        ("pragma% requires a function name", Arg1);
12813                   end if;
12814
12815                   Set_Is_Pure (Def_Id);
12816
12817                   if not Has_Pragma_Pure_Function (Def_Id) then
12818                      Set_Has_Pragma_Pure_Function (Def_Id);
12819                      Effective := True;
12820                   end if;
12821
12822                   exit when From_Aspect_Specification (N);
12823                   E := Homonym (E);
12824                   exit when No (E) or else Scope (E) /= Current_Scope;
12825                end loop;
12826
12827                if not Effective
12828                  and then Warn_On_Redundant_Constructs
12829                then
12830                   Error_Msg_NE
12831                     ("pragma Pure_Function on& is redundant?",
12832                      N, Entity (E_Id));
12833                end if;
12834             end if;
12835          end Pure_Function;
12836
12837          --------------------
12838          -- Queuing_Policy --
12839          --------------------
12840
12841          --  pragma Queuing_Policy (policy_IDENTIFIER);
12842
12843          when Pragma_Queuing_Policy => declare
12844             QP : Character;
12845
12846          begin
12847             Check_Ada_83_Warning;
12848             Check_Arg_Count (1);
12849             Check_No_Identifiers;
12850             Check_Arg_Is_Queuing_Policy (Arg1);
12851             Check_Valid_Configuration_Pragma;
12852             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
12853             QP := Fold_Upper (Name_Buffer (1));
12854
12855             if Queuing_Policy /= ' '
12856               and then Queuing_Policy /= QP
12857             then
12858                Error_Msg_Sloc := Queuing_Policy_Sloc;
12859                Error_Pragma ("queuing policy incompatible with policy#");
12860
12861             --  Set new policy, but always preserve System_Location since we
12862             --  like the error message with the run time name.
12863
12864             else
12865                Queuing_Policy := QP;
12866
12867                if Queuing_Policy_Sloc /= System_Location then
12868                   Queuing_Policy_Sloc := Loc;
12869                end if;
12870             end if;
12871          end;
12872
12873          -----------------------
12874          -- Relative_Deadline --
12875          -----------------------
12876
12877          --  pragma Relative_Deadline (time_span_EXPRESSION);
12878
12879          when Pragma_Relative_Deadline => Relative_Deadline : declare
12880             P   : constant Node_Id := Parent (N);
12881             Arg : Node_Id;
12882
12883          begin
12884             Ada_2005_Pragma;
12885             Check_No_Identifiers;
12886             Check_Arg_Count (1);
12887
12888             Arg := Get_Pragma_Arg (Arg1);
12889
12890             --  The expression must be analyzed in the special manner described
12891             --  in "Handling of Default and Per-Object Expressions" in sem.ads.
12892
12893             Preanalyze_Spec_Expression (Arg, RTE (RE_Time_Span));
12894
12895             --  Subprogram case
12896
12897             if Nkind (P) = N_Subprogram_Body then
12898                Check_In_Main_Program;
12899
12900             --  Tasks
12901
12902             elsif Nkind (P) = N_Task_Definition then
12903                null;
12904
12905             --  Anything else is incorrect
12906
12907             else
12908                Pragma_Misplaced;
12909             end if;
12910
12911             if Has_Relative_Deadline_Pragma (P) then
12912                Error_Pragma ("duplicate pragma% not allowed");
12913             else
12914                Set_Has_Relative_Deadline_Pragma (P, True);
12915
12916                if Nkind (P) = N_Task_Definition then
12917                   Record_Rep_Item (Defining_Identifier (Parent (P)), N);
12918                end if;
12919             end if;
12920          end Relative_Deadline;
12921
12922          ------------------------
12923          -- Remote_Access_Type --
12924          ------------------------
12925
12926          --  pragma Remote_Access_Type ([Entity =>] formal_type_LOCAL_NAME);
12927
12928          when Pragma_Remote_Access_Type => Remote_Access_Type : declare
12929             E : Entity_Id;
12930
12931          begin
12932             GNAT_Pragma;
12933             Check_Arg_Count (1);
12934             Check_Optional_Identifier (Arg1, Name_Entity);
12935             Check_Arg_Is_Local_Name (Arg1);
12936
12937             E := Entity (Get_Pragma_Arg (Arg1));
12938
12939             if Nkind (Parent (E)) = N_Formal_Type_Declaration
12940               and then Ekind (E) = E_General_Access_Type
12941               and then Is_Class_Wide_Type (Directly_Designated_Type (E))
12942               and then Scope (Root_Type (Directly_Designated_Type (E)))
12943                          = Scope (E)
12944               and then Is_Valid_Remote_Object_Type
12945                          (Root_Type (Directly_Designated_Type (E)))
12946             then
12947                Set_Is_Remote_Types (E);
12948
12949             else
12950                Error_Pragma_Arg
12951                  ("pragma% applies only to formal access to classwide types",
12952                   Arg1);
12953             end if;
12954          end Remote_Access_Type;
12955
12956          ---------------------------
12957          -- Remote_Call_Interface --
12958          ---------------------------
12959
12960          --  pragma Remote_Call_Interface [(library_unit_NAME)];
12961
12962          when Pragma_Remote_Call_Interface => Remote_Call_Interface : declare
12963             Cunit_Node : Node_Id;
12964             Cunit_Ent  : Entity_Id;
12965             K          : Node_Kind;
12966
12967          begin
12968             Check_Ada_83_Warning;
12969             Check_Valid_Library_Unit_Pragma;
12970
12971             if Nkind (N) = N_Null_Statement then
12972                return;
12973             end if;
12974
12975             Cunit_Node := Cunit (Current_Sem_Unit);
12976             K          := Nkind (Unit (Cunit_Node));
12977             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
12978
12979             if K = N_Package_Declaration
12980               or else K = N_Generic_Package_Declaration
12981               or else K = N_Subprogram_Declaration
12982               or else K = N_Generic_Subprogram_Declaration
12983               or else (K = N_Subprogram_Body
12984                          and then Acts_As_Spec (Unit (Cunit_Node)))
12985             then
12986                null;
12987             else
12988                Error_Pragma (
12989                  "pragma% must apply to package or subprogram declaration");
12990             end if;
12991
12992             Set_Is_Remote_Call_Interface (Cunit_Ent);
12993          end Remote_Call_Interface;
12994
12995          ------------------
12996          -- Remote_Types --
12997          ------------------
12998
12999          --  pragma Remote_Types [(library_unit_NAME)];
13000
13001          when Pragma_Remote_Types => Remote_Types : declare
13002             Cunit_Node : Node_Id;
13003             Cunit_Ent  : Entity_Id;
13004
13005          begin
13006             Check_Ada_83_Warning;
13007             Check_Valid_Library_Unit_Pragma;
13008
13009             if Nkind (N) = N_Null_Statement then
13010                return;
13011             end if;
13012
13013             Cunit_Node := Cunit (Current_Sem_Unit);
13014             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
13015
13016             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
13017                                                 N_Generic_Package_Declaration)
13018             then
13019                Error_Pragma
13020                  ("pragma% can only apply to a package declaration");
13021             end if;
13022
13023             Set_Is_Remote_Types (Cunit_Ent);
13024          end Remote_Types;
13025
13026          ---------------
13027          -- Ravenscar --
13028          ---------------
13029
13030          --  pragma Ravenscar;
13031
13032          when Pragma_Ravenscar =>
13033             GNAT_Pragma;
13034             Check_Arg_Count (0);
13035             Check_Valid_Configuration_Pragma;
13036             Set_Ravenscar_Profile (N);
13037
13038             if Warn_On_Obsolescent_Feature then
13039                Error_Msg_N ("pragma Ravenscar is an obsolescent feature?", N);
13040                Error_Msg_N ("|use pragma Profile (Ravenscar) instead", N);
13041             end if;
13042
13043          -------------------------
13044          -- Restricted_Run_Time --
13045          -------------------------
13046
13047          --  pragma Restricted_Run_Time;
13048
13049          when Pragma_Restricted_Run_Time =>
13050             GNAT_Pragma;
13051             Check_Arg_Count (0);
13052             Check_Valid_Configuration_Pragma;
13053             Set_Profile_Restrictions
13054               (Restricted, N, Warn => Treat_Restrictions_As_Warnings);
13055
13056             if Warn_On_Obsolescent_Feature then
13057                Error_Msg_N
13058                  ("pragma Restricted_Run_Time is an obsolescent feature?", N);
13059                Error_Msg_N ("|use pragma Profile (Restricted) instead", N);
13060             end if;
13061
13062          ------------------
13063          -- Restrictions --
13064          ------------------
13065
13066          --  pragma Restrictions (RESTRICTION {, RESTRICTION});
13067
13068          --  RESTRICTION ::=
13069          --    restriction_IDENTIFIER
13070          --  | restriction_parameter_IDENTIFIER => EXPRESSION
13071
13072          when Pragma_Restrictions =>
13073             Process_Restrictions_Or_Restriction_Warnings
13074               (Warn => Treat_Restrictions_As_Warnings);
13075
13076          --------------------------
13077          -- Restriction_Warnings --
13078          --------------------------
13079
13080          --  pragma Restriction_Warnings (RESTRICTION {, RESTRICTION});
13081
13082          --  RESTRICTION ::=
13083          --    restriction_IDENTIFIER
13084          --  | restriction_parameter_IDENTIFIER => EXPRESSION
13085
13086          when Pragma_Restriction_Warnings =>
13087             GNAT_Pragma;
13088             Process_Restrictions_Or_Restriction_Warnings (Warn => True);
13089
13090          ----------------
13091          -- Reviewable --
13092          ----------------
13093
13094          --  pragma Reviewable;
13095
13096          when Pragma_Reviewable =>
13097             Check_Ada_83_Warning;
13098             Check_Arg_Count (0);
13099
13100             --  Call dummy debugging function rv. This is done to assist front
13101             --  end debugging. By placing a Reviewable pragma in the source
13102             --  program, a breakpoint on rv catches this place in the source,
13103             --  allowing convenient stepping to the point of interest.
13104
13105             rv;
13106
13107          --------------------------
13108          -- Short_Circuit_And_Or --
13109          --------------------------
13110
13111          when Pragma_Short_Circuit_And_Or =>
13112             GNAT_Pragma;
13113             Check_Arg_Count (0);
13114             Check_Valid_Configuration_Pragma;
13115             Short_Circuit_And_Or := True;
13116
13117          -------------------
13118          -- Share_Generic --
13119          -------------------
13120
13121          --  pragma Share_Generic (NAME {, NAME});
13122
13123          when Pragma_Share_Generic =>
13124             GNAT_Pragma;
13125             Process_Generic_List;
13126
13127          ------------
13128          -- Shared --
13129          ------------
13130
13131          --  pragma Shared (LOCAL_NAME);
13132
13133          when Pragma_Shared =>
13134             GNAT_Pragma;
13135             Process_Atomic_Shared_Volatile;
13136
13137          --------------------
13138          -- Shared_Passive --
13139          --------------------
13140
13141          --  pragma Shared_Passive [(library_unit_NAME)];
13142
13143          --  Set the flag Is_Shared_Passive of program unit name entity
13144
13145          when Pragma_Shared_Passive => Shared_Passive : declare
13146             Cunit_Node : Node_Id;
13147             Cunit_Ent  : Entity_Id;
13148
13149          begin
13150             Check_Ada_83_Warning;
13151             Check_Valid_Library_Unit_Pragma;
13152
13153             if Nkind (N) = N_Null_Statement then
13154                return;
13155             end if;
13156
13157             Cunit_Node := Cunit (Current_Sem_Unit);
13158             Cunit_Ent  := Cunit_Entity (Current_Sem_Unit);
13159
13160             if not Nkind_In (Unit (Cunit_Node), N_Package_Declaration,
13161                                                 N_Generic_Package_Declaration)
13162             then
13163                Error_Pragma
13164                  ("pragma% can only apply to a package declaration");
13165             end if;
13166
13167             Set_Is_Shared_Passive (Cunit_Ent);
13168          end Shared_Passive;
13169
13170          -----------------------
13171          -- Short_Descriptors --
13172          -----------------------
13173
13174          --  pragma Short_Descriptors;
13175
13176          when Pragma_Short_Descriptors =>
13177             GNAT_Pragma;
13178             Check_Arg_Count (0);
13179             Check_Valid_Configuration_Pragma;
13180             Short_Descriptors := True;
13181
13182          ------------------------------
13183          -- Simple_Storage_Pool_Type --
13184          ------------------------------
13185
13186          --  pragma Simple_Storage_Pool_Type (type_LOCAL_NAME);
13187
13188          when Pragma_Simple_Storage_Pool_Type =>
13189          Simple_Storage_Pool_Type : declare
13190             Type_Id : Node_Id;
13191             Typ     : Entity_Id;
13192
13193          begin
13194             GNAT_Pragma;
13195             Check_Arg_Count (1);
13196             Check_Arg_Is_Library_Level_Local_Name (Arg1);
13197
13198             Type_Id := Get_Pragma_Arg (Arg1);
13199             Find_Type (Type_Id);
13200             Typ := Entity (Type_Id);
13201
13202             if Typ = Any_Type then
13203                return;
13204             end if;
13205
13206             --  We require the pragma to apply to a type declared in a package
13207             --  declaration, but not (immediately) within a package body.
13208
13209             if Ekind (Current_Scope) /= E_Package
13210               or else In_Package_Body (Current_Scope)
13211             then
13212                Error_Pragma
13213                  ("pragma% can only apply to type declared immediately " &
13214                   "within a package declaration");
13215             end if;
13216
13217             --  A simple storage pool type must be an immutably limited record
13218             --  or private type. If the pragma is given for a private type,
13219             --  the full type is similarly restricted (which is checked later
13220             --  in Freeze_Entity).
13221
13222             if Is_Record_Type (Typ)
13223               and then not Is_Immutably_Limited_Type (Typ)
13224             then
13225                Error_Pragma
13226                  ("pragma% can only apply to explicitly limited record type");
13227
13228             elsif Is_Private_Type (Typ) and then not Is_Limited_Type (Typ) then
13229                Error_Pragma
13230                  ("pragma% can only apply to a private type that is limited");
13231
13232             elsif not Is_Record_Type (Typ)
13233               and then not Is_Private_Type (Typ)
13234             then
13235                Error_Pragma
13236                  ("pragma% can only apply to limited record or private type");
13237             end if;
13238
13239             Record_Rep_Item (Typ, N);
13240          end Simple_Storage_Pool_Type;
13241
13242          ----------------------
13243          -- Source_File_Name --
13244          ----------------------
13245
13246          --  There are five forms for this pragma:
13247
13248          --  pragma Source_File_Name (
13249          --    [UNIT_NAME      =>] unit_NAME,
13250          --     BODY_FILE_NAME =>  STRING_LITERAL
13251          --    [, [INDEX =>] INTEGER_LITERAL]);
13252
13253          --  pragma Source_File_Name (
13254          --    [UNIT_NAME      =>] unit_NAME,
13255          --     SPEC_FILE_NAME =>  STRING_LITERAL
13256          --    [, [INDEX =>] INTEGER_LITERAL]);
13257
13258          --  pragma Source_File_Name (
13259          --     BODY_FILE_NAME  => STRING_LITERAL
13260          --  [, DOT_REPLACEMENT => STRING_LITERAL]
13261          --  [, CASING          => CASING_SPEC]);
13262
13263          --  pragma Source_File_Name (
13264          --     SPEC_FILE_NAME  => STRING_LITERAL
13265          --  [, DOT_REPLACEMENT => STRING_LITERAL]
13266          --  [, CASING          => CASING_SPEC]);
13267
13268          --  pragma Source_File_Name (
13269          --     SUBUNIT_FILE_NAME  => STRING_LITERAL
13270          --  [, DOT_REPLACEMENT    => STRING_LITERAL]
13271          --  [, CASING             => CASING_SPEC]);
13272
13273          --  CASING_SPEC ::= Uppercase | Lowercase | Mixedcase
13274
13275          --  Pragma Source_File_Name_Project (SFNP) is equivalent to pragma
13276          --  Source_File_Name (SFN), however their usage is exclusive: SFN can
13277          --  only be used when no project file is used, while SFNP can only be
13278          --  used when a project file is used.
13279
13280          --  No processing here. Processing was completed during parsing, since
13281          --  we need to have file names set as early as possible. Units are
13282          --  loaded well before semantic processing starts.
13283
13284          --  The only processing we defer to this point is the check for
13285          --  correct placement.
13286
13287          when Pragma_Source_File_Name =>
13288             GNAT_Pragma;
13289             Check_Valid_Configuration_Pragma;
13290
13291          ------------------------------
13292          -- Source_File_Name_Project --
13293          ------------------------------
13294
13295          --  See Source_File_Name for syntax
13296
13297          --  No processing here. Processing was completed during parsing, since
13298          --  we need to have file names set as early as possible. Units are
13299          --  loaded well before semantic processing starts.
13300
13301          --  The only processing we defer to this point is the check for
13302          --  correct placement.
13303
13304          when Pragma_Source_File_Name_Project =>
13305             GNAT_Pragma;
13306             Check_Valid_Configuration_Pragma;
13307
13308             --  Check that a pragma Source_File_Name_Project is used only in a
13309             --  configuration pragmas file.
13310
13311             --  Pragmas Source_File_Name_Project should only be generated by
13312             --  the Project Manager in configuration pragmas files.
13313
13314             --  This is really an ugly test. It seems to depend on some
13315             --  accidental and undocumented property. At the very least it
13316             --  needs to be documented, but it would be better to have a
13317             --  clean way of testing if we are in a configuration file???
13318
13319             if Present (Parent (N)) then
13320                Error_Pragma
13321                  ("pragma% can only appear in a configuration pragmas file");
13322             end if;
13323
13324          ----------------------
13325          -- Source_Reference --
13326          ----------------------
13327
13328          --  pragma Source_Reference (INTEGER_LITERAL [, STRING_LITERAL]);
13329
13330          --  Nothing to do, all processing completed in Par.Prag, since we need
13331          --  the information for possible parser messages that are output.
13332
13333          when Pragma_Source_Reference =>
13334             GNAT_Pragma;
13335
13336          --------------------------------
13337          -- Static_Elaboration_Desired --
13338          --------------------------------
13339
13340          --  pragma Static_Elaboration_Desired (DIRECT_NAME);
13341
13342          when Pragma_Static_Elaboration_Desired =>
13343             GNAT_Pragma;
13344             Check_At_Most_N_Arguments (1);
13345
13346             if Is_Compilation_Unit (Current_Scope)
13347               and then Ekind (Current_Scope) = E_Package
13348             then
13349                Set_Static_Elaboration_Desired (Current_Scope, True);
13350             else
13351                Error_Pragma ("pragma% must apply to a library-level package");
13352             end if;
13353
13354          ------------------
13355          -- Storage_Size --
13356          ------------------
13357
13358          --  pragma Storage_Size (EXPRESSION);
13359
13360          when Pragma_Storage_Size => Storage_Size : declare
13361             P   : constant Node_Id := Parent (N);
13362             Arg : Node_Id;
13363
13364          begin
13365             Check_No_Identifiers;
13366             Check_Arg_Count (1);
13367
13368             --  The expression must be analyzed in the special manner described
13369             --  in "Handling of Default Expressions" in sem.ads.
13370
13371             Arg := Get_Pragma_Arg (Arg1);
13372             Preanalyze_Spec_Expression (Arg, Any_Integer);
13373
13374             if not Is_Static_Expression (Arg) then
13375                Check_Restriction (Static_Storage_Size, Arg);
13376             end if;
13377
13378             if Nkind (P) /= N_Task_Definition then
13379                Pragma_Misplaced;
13380                return;
13381
13382             else
13383                if Has_Storage_Size_Pragma (P) then
13384                   Error_Pragma ("duplicate pragma% not allowed");
13385                else
13386                   Set_Has_Storage_Size_Pragma (P, True);
13387                end if;
13388
13389                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13390                --  ???  exp_ch9 should use this!
13391             end if;
13392          end Storage_Size;
13393
13394          ------------------
13395          -- Storage_Unit --
13396          ------------------
13397
13398          --  pragma Storage_Unit (NUMERIC_LITERAL);
13399
13400          --  Only permitted argument is System'Storage_Unit value
13401
13402          when Pragma_Storage_Unit =>
13403             Check_No_Identifiers;
13404             Check_Arg_Count (1);
13405             Check_Arg_Is_Integer_Literal (Arg1);
13406
13407             if Intval (Get_Pragma_Arg (Arg1)) /=
13408               UI_From_Int (Ttypes.System_Storage_Unit)
13409             then
13410                Error_Msg_Uint_1 := UI_From_Int (Ttypes.System_Storage_Unit);
13411                Error_Pragma_Arg
13412                  ("the only allowed argument for pragma% is ^", Arg1);
13413             end if;
13414
13415          --------------------
13416          -- Stream_Convert --
13417          --------------------
13418
13419          --  pragma Stream_Convert (
13420          --    [Entity =>] type_LOCAL_NAME,
13421          --    [Read   =>] function_NAME,
13422          --    [Write  =>] function NAME);
13423
13424          when Pragma_Stream_Convert => Stream_Convert : declare
13425
13426             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id);
13427             --  Check that the given argument is the name of a local function
13428             --  of one argument that is not overloaded earlier in the current
13429             --  local scope. A check is also made that the argument is a
13430             --  function with one parameter.
13431
13432             --------------------------------------
13433             -- Check_OK_Stream_Convert_Function --
13434             --------------------------------------
13435
13436             procedure Check_OK_Stream_Convert_Function (Arg : Node_Id) is
13437                Ent : Entity_Id;
13438
13439             begin
13440                Check_Arg_Is_Local_Name (Arg);
13441                Ent := Entity (Get_Pragma_Arg (Arg));
13442
13443                if Has_Homonym (Ent) then
13444                   Error_Pragma_Arg
13445                     ("argument for pragma% may not be overloaded", Arg);
13446                end if;
13447
13448                if Ekind (Ent) /= E_Function
13449                  or else No (First_Formal (Ent))
13450                  or else Present (Next_Formal (First_Formal (Ent)))
13451                then
13452                   Error_Pragma_Arg
13453                     ("argument for pragma% must be" &
13454                      " function of one argument", Arg);
13455                end if;
13456             end Check_OK_Stream_Convert_Function;
13457
13458          --  Start of processing for Stream_Convert
13459
13460          begin
13461             GNAT_Pragma;
13462             Check_Arg_Order ((Name_Entity, Name_Read, Name_Write));
13463             Check_Arg_Count (3);
13464             Check_Optional_Identifier (Arg1, Name_Entity);
13465             Check_Optional_Identifier (Arg2, Name_Read);
13466             Check_Optional_Identifier (Arg3, Name_Write);
13467             Check_Arg_Is_Local_Name (Arg1);
13468             Check_OK_Stream_Convert_Function (Arg2);
13469             Check_OK_Stream_Convert_Function (Arg3);
13470
13471             declare
13472                Typ   : constant Entity_Id :=
13473                          Underlying_Type (Entity (Get_Pragma_Arg (Arg1)));
13474                Read  : constant Entity_Id := Entity (Get_Pragma_Arg (Arg2));
13475                Write : constant Entity_Id := Entity (Get_Pragma_Arg (Arg3));
13476
13477             begin
13478                Check_First_Subtype (Arg1);
13479
13480                --  Check for too early or too late. Note that we don't enforce
13481                --  the rule about primitive operations in this case, since, as
13482                --  is the case for explicit stream attributes themselves, these
13483                --  restrictions are not appropriate. Note that the chaining of
13484                --  the pragma by Rep_Item_Too_Late is actually the critical
13485                --  processing done for this pragma.
13486
13487                if Rep_Item_Too_Early (Typ, N)
13488                     or else
13489                   Rep_Item_Too_Late (Typ, N, FOnly => True)
13490                then
13491                   return;
13492                end if;
13493
13494                --  Return if previous error
13495
13496                if Etype (Typ) = Any_Type
13497                     or else
13498                   Etype (Read) = Any_Type
13499                     or else
13500                   Etype (Write) = Any_Type
13501                then
13502                   return;
13503                end if;
13504
13505                --  Error checks
13506
13507                if Underlying_Type (Etype (Read)) /= Typ then
13508                   Error_Pragma_Arg
13509                     ("incorrect return type for function&", Arg2);
13510                end if;
13511
13512                if Underlying_Type (Etype (First_Formal (Write))) /= Typ then
13513                   Error_Pragma_Arg
13514                     ("incorrect parameter type for function&", Arg3);
13515                end if;
13516
13517                if Underlying_Type (Etype (First_Formal (Read))) /=
13518                   Underlying_Type (Etype (Write))
13519                then
13520                   Error_Pragma_Arg
13521                     ("result type of & does not match Read parameter type",
13522                      Arg3);
13523                end if;
13524             end;
13525          end Stream_Convert;
13526
13527          -------------------------
13528          -- Style_Checks (GNAT) --
13529          -------------------------
13530
13531          --  pragma Style_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
13532
13533          --  This is processed by the parser since some of the style checks
13534          --  take place during source scanning and parsing. This means that
13535          --  we don't need to issue error messages here.
13536
13537          when Pragma_Style_Checks => Style_Checks : declare
13538             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
13539             S  : String_Id;
13540             C  : Char_Code;
13541
13542          begin
13543             GNAT_Pragma;
13544             Check_No_Identifiers;
13545
13546             --  Two argument form
13547
13548             if Arg_Count = 2 then
13549                Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
13550
13551                declare
13552                   E_Id : Node_Id;
13553                   E    : Entity_Id;
13554
13555                begin
13556                   E_Id := Get_Pragma_Arg (Arg2);
13557                   Analyze (E_Id);
13558
13559                   if not Is_Entity_Name (E_Id) then
13560                      Error_Pragma_Arg
13561                        ("second argument of pragma% must be entity name",
13562                         Arg2);
13563                   end if;
13564
13565                   E := Entity (E_Id);
13566
13567                   if E = Any_Id then
13568                      return;
13569                   else
13570                      loop
13571                         Set_Suppress_Style_Checks (E,
13572                           (Chars (Get_Pragma_Arg (Arg1)) = Name_Off));
13573                         exit when No (Homonym (E));
13574                         E := Homonym (E);
13575                      end loop;
13576                   end if;
13577                end;
13578
13579             --  One argument form
13580
13581             else
13582                Check_Arg_Count (1);
13583
13584                if Nkind (A) = N_String_Literal then
13585                   S   := Strval (A);
13586
13587                   declare
13588                      Slen    : constant Natural := Natural (String_Length (S));
13589                      Options : String (1 .. Slen);
13590                      J       : Natural;
13591
13592                   begin
13593                      J := 1;
13594                      loop
13595                         C := Get_String_Char (S, Int (J));
13596                         exit when not In_Character_Range (C);
13597                         Options (J) := Get_Character (C);
13598
13599                         --  If at end of string, set options. As per discussion
13600                         --  above, no need to check for errors, since we issued
13601                         --  them in the parser.
13602
13603                         if J = Slen then
13604                            Set_Style_Check_Options (Options);
13605                            exit;
13606                         end if;
13607
13608                         J := J + 1;
13609                      end loop;
13610                   end;
13611
13612                elsif Nkind (A) = N_Identifier then
13613                   if Chars (A) = Name_All_Checks then
13614                      if GNAT_Mode then
13615                         Set_GNAT_Style_Check_Options;
13616                      else
13617                         Set_Default_Style_Check_Options;
13618                      end if;
13619
13620                   elsif Chars (A) = Name_On then
13621                      Style_Check := True;
13622
13623                   elsif Chars (A) = Name_Off then
13624                      Style_Check := False;
13625                   end if;
13626                end if;
13627             end if;
13628          end Style_Checks;
13629
13630          --------------
13631          -- Subtitle --
13632          --------------
13633
13634          --  pragma Subtitle ([Subtitle =>] STRING_LITERAL);
13635
13636          when Pragma_Subtitle =>
13637             GNAT_Pragma;
13638             Check_Arg_Count (1);
13639             Check_Optional_Identifier (Arg1, Name_Subtitle);
13640             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13641             Store_Note (N);
13642
13643          --------------
13644          -- Suppress --
13645          --------------
13646
13647          --  pragma Suppress (IDENTIFIER [, [On =>] NAME]);
13648
13649          when Pragma_Suppress =>
13650             Process_Suppress_Unsuppress (True);
13651
13652          ------------------
13653          -- Suppress_All --
13654          ------------------
13655
13656          --  pragma Suppress_All;
13657
13658          --  The only check made here is that the pragma has no arguments.
13659          --  There are no placement rules, and the processing required (setting
13660          --  the Has_Pragma_Suppress_All flag in the compilation unit node was
13661          --  taken care of by the parser). Process_Compilation_Unit_Pragmas
13662          --  then creates and inserts a pragma Suppress (All_Checks).
13663
13664          when Pragma_Suppress_All =>
13665             GNAT_Pragma;
13666             Check_Arg_Count (0);
13667
13668          -------------------------
13669          -- Suppress_Debug_Info --
13670          -------------------------
13671
13672          --  pragma Suppress_Debug_Info ([Entity =>] LOCAL_NAME);
13673
13674          when Pragma_Suppress_Debug_Info =>
13675             GNAT_Pragma;
13676             Check_Arg_Count (1);
13677             Check_Optional_Identifier (Arg1, Name_Entity);
13678             Check_Arg_Is_Local_Name (Arg1);
13679             Set_Debug_Info_Off (Entity (Get_Pragma_Arg (Arg1)));
13680
13681          ----------------------------------
13682          -- Suppress_Exception_Locations --
13683          ----------------------------------
13684
13685          --  pragma Suppress_Exception_Locations;
13686
13687          when Pragma_Suppress_Exception_Locations =>
13688             GNAT_Pragma;
13689             Check_Arg_Count (0);
13690             Check_Valid_Configuration_Pragma;
13691             Exception_Locations_Suppressed := True;
13692
13693          -----------------------------
13694          -- Suppress_Initialization --
13695          -----------------------------
13696
13697          --  pragma Suppress_Initialization ([Entity =>] type_Name);
13698
13699          when Pragma_Suppress_Initialization => Suppress_Init : declare
13700             E_Id : Node_Id;
13701             E    : Entity_Id;
13702
13703          begin
13704             GNAT_Pragma;
13705             Check_Arg_Count (1);
13706             Check_Optional_Identifier (Arg1, Name_Entity);
13707             Check_Arg_Is_Local_Name (Arg1);
13708
13709             E_Id := Get_Pragma_Arg (Arg1);
13710
13711             if Etype (E_Id) = Any_Type then
13712                return;
13713             end if;
13714
13715             E := Entity (E_Id);
13716
13717             if not Is_Type (E) then
13718                Error_Pragma_Arg ("pragma% requires type or subtype", Arg1);
13719             end if;
13720
13721             if Rep_Item_Too_Early (E, N)
13722                  or else
13723                Rep_Item_Too_Late (E, N, FOnly => True)
13724             then
13725                return;
13726             end if;
13727
13728             --  For incomplete/private type, set flag on full view
13729
13730             if Is_Incomplete_Or_Private_Type (E) then
13731                if No (Full_View (Base_Type (E))) then
13732                   Error_Pragma_Arg
13733                     ("argument of pragma% cannot be an incomplete type", Arg1);
13734                else
13735                   Set_Suppress_Initialization (Full_View (Base_Type (E)));
13736                end if;
13737
13738             --  For first subtype, set flag on base type
13739
13740             elsif Is_First_Subtype (E) then
13741                Set_Suppress_Initialization (Base_Type (E));
13742
13743             --  For other than first subtype, set flag on subtype itself
13744
13745             else
13746                Set_Suppress_Initialization (E);
13747             end if;
13748          end Suppress_Init;
13749
13750          -----------------
13751          -- System_Name --
13752          -----------------
13753
13754          --  pragma System_Name (DIRECT_NAME);
13755
13756          --  Syntax check: one argument, which must be the identifier GNAT or
13757          --  the identifier GCC, no other identifiers are acceptable.
13758
13759          when Pragma_System_Name =>
13760             GNAT_Pragma;
13761             Check_No_Identifiers;
13762             Check_Arg_Count (1);
13763             Check_Arg_Is_One_Of (Arg1, Name_Gcc, Name_Gnat);
13764
13765          -----------------------------
13766          -- Task_Dispatching_Policy --
13767          -----------------------------
13768
13769          --  pragma Task_Dispatching_Policy (policy_IDENTIFIER);
13770
13771          when Pragma_Task_Dispatching_Policy => declare
13772             DP : Character;
13773
13774          begin
13775             Check_Ada_83_Warning;
13776             Check_Arg_Count (1);
13777             Check_No_Identifiers;
13778             Check_Arg_Is_Task_Dispatching_Policy (Arg1);
13779             Check_Valid_Configuration_Pragma;
13780             Get_Name_String (Chars (Get_Pragma_Arg (Arg1)));
13781             DP := Fold_Upper (Name_Buffer (1));
13782
13783             if Task_Dispatching_Policy /= ' '
13784               and then Task_Dispatching_Policy /= DP
13785             then
13786                Error_Msg_Sloc := Task_Dispatching_Policy_Sloc;
13787                Error_Pragma
13788                  ("task dispatching policy incompatible with policy#");
13789
13790             --  Set new policy, but always preserve System_Location since we
13791             --  like the error message with the run time name.
13792
13793             else
13794                Task_Dispatching_Policy := DP;
13795
13796                if Task_Dispatching_Policy_Sloc /= System_Location then
13797                   Task_Dispatching_Policy_Sloc := Loc;
13798                end if;
13799             end if;
13800          end;
13801
13802          ---------------
13803          -- Task_Info --
13804          ---------------
13805
13806          --  pragma Task_Info (EXPRESSION);
13807
13808          when Pragma_Task_Info => Task_Info : declare
13809             P : constant Node_Id := Parent (N);
13810
13811          begin
13812             GNAT_Pragma;
13813
13814             if Nkind (P) /= N_Task_Definition then
13815                Error_Pragma ("pragma% must appear in task definition");
13816             end if;
13817
13818             Check_No_Identifiers;
13819             Check_Arg_Count (1);
13820
13821             Analyze_And_Resolve
13822               (Get_Pragma_Arg (Arg1), RTE (RE_Task_Info_Type));
13823
13824             if Etype (Get_Pragma_Arg (Arg1)) = Any_Type then
13825                return;
13826             end if;
13827
13828             if Has_Task_Info_Pragma (P) then
13829                Error_Pragma ("duplicate pragma% not allowed");
13830             else
13831                Set_Has_Task_Info_Pragma (P, True);
13832             end if;
13833          end Task_Info;
13834
13835          ---------------
13836          -- Task_Name --
13837          ---------------
13838
13839          --  pragma Task_Name (string_EXPRESSION);
13840
13841          when Pragma_Task_Name => Task_Name : declare
13842             P   : constant Node_Id := Parent (N);
13843             Arg : Node_Id;
13844
13845          begin
13846             Check_No_Identifiers;
13847             Check_Arg_Count (1);
13848
13849             Arg := Get_Pragma_Arg (Arg1);
13850
13851             --  The expression is used in the call to Create_Task, and must be
13852             --  expanded there, not in the context of the current spec. It must
13853             --  however be analyzed to capture global references, in case it
13854             --  appears in a generic context.
13855
13856             Preanalyze_And_Resolve (Arg, Standard_String);
13857
13858             if Nkind (P) /= N_Task_Definition then
13859                Pragma_Misplaced;
13860             end if;
13861
13862             if Has_Task_Name_Pragma (P) then
13863                Error_Pragma ("duplicate pragma% not allowed");
13864             else
13865                Set_Has_Task_Name_Pragma (P, True);
13866                Record_Rep_Item (Defining_Identifier (Parent (P)), N);
13867             end if;
13868          end Task_Name;
13869
13870          ------------------
13871          -- Task_Storage --
13872          ------------------
13873
13874          --  pragma Task_Storage (
13875          --     [Task_Type =>] LOCAL_NAME,
13876          --     [Top_Guard =>] static_integer_EXPRESSION);
13877
13878          when Pragma_Task_Storage => Task_Storage : declare
13879             Args  : Args_List (1 .. 2);
13880             Names : constant Name_List (1 .. 2) := (
13881                       Name_Task_Type,
13882                       Name_Top_Guard);
13883
13884             Task_Type : Node_Id renames Args (1);
13885             Top_Guard : Node_Id renames Args (2);
13886
13887             Ent : Entity_Id;
13888
13889          begin
13890             GNAT_Pragma;
13891             Gather_Associations (Names, Args);
13892
13893             if No (Task_Type) then
13894                Error_Pragma
13895                  ("missing task_type argument for pragma%");
13896             end if;
13897
13898             Check_Arg_Is_Local_Name (Task_Type);
13899
13900             Ent := Entity (Task_Type);
13901
13902             if not Is_Task_Type (Ent) then
13903                Error_Pragma_Arg
13904                  ("argument for pragma% must be task type", Task_Type);
13905             end if;
13906
13907             if No (Top_Guard) then
13908                Error_Pragma_Arg
13909                  ("pragma% takes two arguments", Task_Type);
13910             else
13911                Check_Arg_Is_Static_Expression (Top_Guard, Any_Integer);
13912             end if;
13913
13914             Check_First_Subtype (Task_Type);
13915
13916             if Rep_Item_Too_Late (Ent, N) then
13917                raise Pragma_Exit;
13918             end if;
13919          end Task_Storage;
13920
13921          ---------------
13922          -- Test_Case --
13923          ---------------
13924
13925          --  pragma Test_Case ([Name     =>] Static_String_EXPRESSION
13926          --                   ,[Mode     =>] MODE_TYPE
13927          --                  [, Requires =>  Boolean_EXPRESSION]
13928          --                  [, Ensures  =>  Boolean_EXPRESSION]);
13929
13930          --  MODE_TYPE ::= Nominal | Robustness
13931
13932          when Pragma_Test_Case => Test_Case : declare
13933          begin
13934             GNAT_Pragma;
13935             Check_At_Least_N_Arguments (2);
13936             Check_At_Most_N_Arguments (4);
13937             Check_Arg_Order
13938                  ((Name_Name, Name_Mode, Name_Requires, Name_Ensures));
13939
13940             Check_Optional_Identifier (Arg1, Name_Name);
13941             Check_Arg_Is_Static_Expression (Arg1, Standard_String);
13942
13943             --  In ASIS mode, for a pragma generated from a source aspect, also
13944             --  analyze the original aspect expression.
13945
13946             if ASIS_Mode
13947               and then Present (Corresponding_Aspect (N))
13948             then
13949                Check_Expr_Is_Static_Expression
13950                  (Original_Node (Get_Pragma_Arg (Arg1)), Standard_String);
13951             end if;
13952
13953             Check_Optional_Identifier (Arg2, Name_Mode);
13954             Check_Arg_Is_One_Of (Arg2, Name_Nominal, Name_Robustness);
13955
13956             if Arg_Count = 4 then
13957                Check_Identifier (Arg3, Name_Requires);
13958                Check_Identifier (Arg4, Name_Ensures);
13959
13960             elsif Arg_Count = 3 then
13961                Check_Identifier_Is_One_Of (Arg3, Name_Requires, Name_Ensures);
13962             end if;
13963
13964             Check_Test_Case;
13965          end Test_Case;
13966
13967          --------------------------
13968          -- Thread_Local_Storage --
13969          --------------------------
13970
13971          --  pragma Thread_Local_Storage ([Entity =>] LOCAL_NAME);
13972
13973          when Pragma_Thread_Local_Storage => Thread_Local_Storage : declare
13974             Id : Node_Id;
13975             E  : Entity_Id;
13976
13977          begin
13978             GNAT_Pragma;
13979             Check_Arg_Count (1);
13980             Check_Optional_Identifier (Arg1, Name_Entity);
13981             Check_Arg_Is_Library_Level_Local_Name (Arg1);
13982
13983             Id := Get_Pragma_Arg (Arg1);
13984             Analyze (Id);
13985
13986             if not Is_Entity_Name (Id)
13987               or else Ekind (Entity (Id)) /= E_Variable
13988             then
13989                Error_Pragma_Arg ("local variable name required", Arg1);
13990             end if;
13991
13992             E := Entity (Id);
13993
13994             if Rep_Item_Too_Early (E, N)
13995               or else Rep_Item_Too_Late (E, N)
13996             then
13997                raise Pragma_Exit;
13998             end if;
13999
14000             Set_Has_Pragma_Thread_Local_Storage (E);
14001             Set_Has_Gigi_Rep_Item (E);
14002          end Thread_Local_Storage;
14003
14004          ----------------
14005          -- Time_Slice --
14006          ----------------
14007
14008          --  pragma Time_Slice (static_duration_EXPRESSION);
14009
14010          when Pragma_Time_Slice => Time_Slice : declare
14011             Val : Ureal;
14012             Nod : Node_Id;
14013
14014          begin
14015             GNAT_Pragma;
14016             Check_Arg_Count (1);
14017             Check_No_Identifiers;
14018             Check_In_Main_Program;
14019             Check_Arg_Is_Static_Expression (Arg1, Standard_Duration);
14020
14021             if not Error_Posted (Arg1) then
14022                Nod := Next (N);
14023                while Present (Nod) loop
14024                   if Nkind (Nod) = N_Pragma
14025                     and then Pragma_Name (Nod) = Name_Time_Slice
14026                   then
14027                      Error_Msg_Name_1 := Pname;
14028                      Error_Msg_N ("duplicate pragma% not permitted", Nod);
14029                   end if;
14030
14031                   Next (Nod);
14032                end loop;
14033             end if;
14034
14035             --  Process only if in main unit
14036
14037             if Get_Source_Unit (Loc) = Main_Unit then
14038                Opt.Time_Slice_Set := True;
14039                Val := Expr_Value_R (Get_Pragma_Arg (Arg1));
14040
14041                if Val <= Ureal_0 then
14042                   Opt.Time_Slice_Value := 0;
14043
14044                elsif Val > UR_From_Uint (UI_From_Int (1000)) then
14045                   Opt.Time_Slice_Value := 1_000_000_000;
14046
14047                else
14048                   Opt.Time_Slice_Value :=
14049                     UI_To_Int (UR_To_Uint (Val * UI_From_Int (1_000_000)));
14050                end if;
14051             end if;
14052          end Time_Slice;
14053
14054          -----------
14055          -- Title --
14056          -----------
14057
14058          --  pragma Title (TITLING_OPTION [, TITLING OPTION]);
14059
14060          --   TITLING_OPTION ::=
14061          --     [Title =>] STRING_LITERAL
14062          --   | [Subtitle =>] STRING_LITERAL
14063
14064          when Pragma_Title => Title : declare
14065             Args  : Args_List (1 .. 2);
14066             Names : constant Name_List (1 .. 2) := (
14067                       Name_Title,
14068                       Name_Subtitle);
14069
14070          begin
14071             GNAT_Pragma;
14072             Gather_Associations (Names, Args);
14073             Store_Note (N);
14074
14075             for J in 1 .. 2 loop
14076                if Present (Args (J)) then
14077                   Check_Arg_Is_Static_Expression (Args (J), Standard_String);
14078                end if;
14079             end loop;
14080          end Title;
14081
14082          ---------------------
14083          -- Unchecked_Union --
14084          ---------------------
14085
14086          --  pragma Unchecked_Union (first_subtype_LOCAL_NAME)
14087
14088          when Pragma_Unchecked_Union => Unchecked_Union : declare
14089             Assoc   : constant Node_Id := Arg1;
14090             Type_Id : constant Node_Id := Get_Pragma_Arg (Assoc);
14091             Typ     : Entity_Id;
14092             Discr   : Entity_Id;
14093             Tdef    : Node_Id;
14094             Clist   : Node_Id;
14095             Vpart   : Node_Id;
14096             Comp    : Node_Id;
14097             Variant : Node_Id;
14098
14099          begin
14100             Ada_2005_Pragma;
14101             Check_No_Identifiers;
14102             Check_Arg_Count (1);
14103             Check_Arg_Is_Local_Name (Arg1);
14104
14105             Find_Type (Type_Id);
14106             Typ := Entity (Type_Id);
14107
14108             if Typ = Any_Type
14109               or else Rep_Item_Too_Early (Typ, N)
14110             then
14111                return;
14112             else
14113                Typ := Underlying_Type (Typ);
14114             end if;
14115
14116             if Rep_Item_Too_Late (Typ, N) then
14117                return;
14118             end if;
14119
14120             Check_First_Subtype (Arg1);
14121
14122             --  Note remaining cases are references to a type in the current
14123             --  declarative part. If we find an error, we post the error on
14124             --  the relevant type declaration at an appropriate point.
14125
14126             if not Is_Record_Type (Typ) then
14127                Error_Msg_N ("Unchecked_Union must be record type", Typ);
14128                return;
14129
14130             elsif Is_Tagged_Type (Typ) then
14131                Error_Msg_N ("Unchecked_Union must not be tagged", Typ);
14132                return;
14133
14134             elsif not Has_Discriminants (Typ) then
14135                Error_Msg_N
14136                 ("Unchecked_Union must have one discriminant", Typ);
14137                return;
14138
14139             --  Note: in previous versions of GNAT we used to check for limited
14140             --  types and give an error, but in fact the standard does allow
14141             --  Unchecked_Union on limited types, so this check was removed.
14142
14143             --  Proceed with basic error checks completed
14144
14145             else
14146                Discr := First_Discriminant (Typ);
14147                while Present (Discr) loop
14148                   if No (Discriminant_Default_Value (Discr)) then
14149                      Error_Msg_N
14150                        ("Unchecked_Union discriminant must have default value",
14151                         Discr);
14152                   end if;
14153
14154                   Next_Discriminant (Discr);
14155                end loop;
14156
14157                Tdef  := Type_Definition (Declaration_Node (Typ));
14158                Clist := Component_List (Tdef);
14159
14160                Comp := First (Component_Items (Clist));
14161                while Present (Comp) loop
14162                   Check_Component (Comp, Typ);
14163                   Next (Comp);
14164                end loop;
14165
14166                if No (Clist) or else No (Variant_Part (Clist)) then
14167                   Error_Msg_N
14168                     ("Unchecked_Union must have variant part",
14169                      Tdef);
14170                   return;
14171                end if;
14172
14173                Vpart := Variant_Part (Clist);
14174
14175                Variant := First (Variants (Vpart));
14176                while Present (Variant) loop
14177                   Check_Variant (Variant, Typ);
14178                   Next (Variant);
14179                end loop;
14180             end if;
14181
14182             Set_Is_Unchecked_Union  (Typ);
14183             Set_Convention (Typ, Convention_C);
14184             Set_Has_Unchecked_Union (Base_Type (Typ));
14185             Set_Is_Unchecked_Union  (Base_Type (Typ));
14186          end Unchecked_Union;
14187
14188          ------------------------
14189          -- Unimplemented_Unit --
14190          ------------------------
14191
14192          --  pragma Unimplemented_Unit;
14193
14194          --  Note: this only gives an error if we are generating code, or if
14195          --  we are in a generic library unit (where the pragma appears in the
14196          --  body, not in the spec).
14197
14198          when Pragma_Unimplemented_Unit => Unimplemented_Unit : declare
14199             Cunitent : constant Entity_Id :=
14200                          Cunit_Entity (Get_Source_Unit (Loc));
14201             Ent_Kind : constant Entity_Kind :=
14202                          Ekind (Cunitent);
14203
14204          begin
14205             GNAT_Pragma;
14206             Check_Arg_Count (0);
14207
14208             if Operating_Mode = Generate_Code
14209               or else Ent_Kind = E_Generic_Function
14210               or else Ent_Kind = E_Generic_Procedure
14211               or else Ent_Kind = E_Generic_Package
14212             then
14213                Get_Name_String (Chars (Cunitent));
14214                Set_Casing (Mixed_Case);
14215                Write_Str (Name_Buffer (1 .. Name_Len));
14216                Write_Str (" is not supported in this configuration");
14217                Write_Eol;
14218                raise Unrecoverable_Error;
14219             end if;
14220          end Unimplemented_Unit;
14221
14222          ------------------------
14223          -- Universal_Aliasing --
14224          ------------------------
14225
14226          --  pragma Universal_Aliasing [([Entity =>] type_LOCAL_NAME)];
14227
14228          when Pragma_Universal_Aliasing => Universal_Alias : declare
14229             E_Id : Entity_Id;
14230
14231          begin
14232             GNAT_Pragma;
14233             Check_Arg_Count (1);
14234             Check_Optional_Identifier (Arg2, Name_Entity);
14235             Check_Arg_Is_Local_Name (Arg1);
14236             E_Id := Entity (Get_Pragma_Arg (Arg1));
14237
14238             if E_Id = Any_Type then
14239                return;
14240             elsif No (E_Id) or else not Is_Type (E_Id) then
14241                Error_Pragma_Arg ("pragma% requires type", Arg1);
14242             end if;
14243
14244             Set_Universal_Aliasing (Implementation_Base_Type (E_Id));
14245          end Universal_Alias;
14246
14247          --------------------
14248          -- Universal_Data --
14249          --------------------
14250
14251          --  pragma Universal_Data [(library_unit_NAME)];
14252
14253          when Pragma_Universal_Data =>
14254             GNAT_Pragma;
14255
14256             --  If this is a configuration pragma, then set the universal
14257             --  addressing option, otherwise confirm that the pragma satisfies
14258             --  the requirements of library unit pragma placement and leave it
14259             --  to the GNAAMP back end to detect the pragma (avoids transitive
14260             --  setting of the option due to withed units).
14261
14262             if Is_Configuration_Pragma then
14263                Universal_Addressing_On_AAMP := True;
14264             else
14265                Check_Valid_Library_Unit_Pragma;
14266             end if;
14267
14268             if not AAMP_On_Target then
14269                Error_Pragma ("?pragma% ignored (applies only to AAMP)");
14270             end if;
14271
14272          ----------------
14273          -- Unmodified --
14274          ----------------
14275
14276          --  pragma Unmodified (local_Name {, local_Name});
14277
14278          when Pragma_Unmodified => Unmodified : declare
14279             Arg_Node : Node_Id;
14280             Arg_Expr : Node_Id;
14281             Arg_Ent  : Entity_Id;
14282
14283          begin
14284             GNAT_Pragma;
14285             Check_At_Least_N_Arguments (1);
14286
14287             --  Loop through arguments
14288
14289             Arg_Node := Arg1;
14290             while Present (Arg_Node) loop
14291                Check_No_Identifier (Arg_Node);
14292
14293                --  Note: the analyze call done by Check_Arg_Is_Local_Name will
14294                --  in fact generate reference, so that the entity will have a
14295                --  reference, which will inhibit any warnings about it not
14296                --  being referenced, and also properly show up in the ali file
14297                --  as a reference. But this reference is recorded before the
14298                --  Has_Pragma_Unreferenced flag is set, so that no warning is
14299                --  generated for this reference.
14300
14301                Check_Arg_Is_Local_Name (Arg_Node);
14302                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14303
14304                if Is_Entity_Name (Arg_Expr) then
14305                   Arg_Ent := Entity (Arg_Expr);
14306
14307                   if not Is_Assignable (Arg_Ent) then
14308                      Error_Pragma_Arg
14309                        ("pragma% can only be applied to a variable",
14310                         Arg_Expr);
14311                   else
14312                      Set_Has_Pragma_Unmodified (Arg_Ent);
14313                   end if;
14314                end if;
14315
14316                Next (Arg_Node);
14317             end loop;
14318          end Unmodified;
14319
14320          ------------------
14321          -- Unreferenced --
14322          ------------------
14323
14324          --  pragma Unreferenced (local_Name {, local_Name});
14325
14326          --    or when used in a context clause:
14327
14328          --  pragma Unreferenced (library_unit_NAME {, library_unit_NAME}
14329
14330          when Pragma_Unreferenced => Unreferenced : declare
14331             Arg_Node : Node_Id;
14332             Arg_Expr : Node_Id;
14333             Arg_Ent  : Entity_Id;
14334             Citem    : Node_Id;
14335
14336          begin
14337             GNAT_Pragma;
14338             Check_At_Least_N_Arguments (1);
14339
14340             --  Check case of appearing within context clause
14341
14342             if Is_In_Context_Clause then
14343
14344                --  The arguments must all be units mentioned in a with clause
14345                --  in the same context clause. Note we already checked (in
14346                --  Par.Prag) that the arguments are either identifiers or
14347                --  selected components.
14348
14349                Arg_Node := Arg1;
14350                while Present (Arg_Node) loop
14351                   Citem := First (List_Containing (N));
14352                   while Citem /= N loop
14353                      if Nkind (Citem) = N_With_Clause
14354                        and then
14355                          Same_Name (Name (Citem), Get_Pragma_Arg (Arg_Node))
14356                      then
14357                         Set_Has_Pragma_Unreferenced
14358                           (Cunit_Entity
14359                              (Get_Source_Unit
14360                                 (Library_Unit (Citem))));
14361                         Set_Unit_Name
14362                           (Get_Pragma_Arg (Arg_Node), Name (Citem));
14363                         exit;
14364                      end if;
14365
14366                      Next (Citem);
14367                   end loop;
14368
14369                   if Citem = N then
14370                      Error_Pragma_Arg
14371                        ("argument of pragma% is not withed unit", Arg_Node);
14372                   end if;
14373
14374                   Next (Arg_Node);
14375                end loop;
14376
14377             --  Case of not in list of context items
14378
14379             else
14380                Arg_Node := Arg1;
14381                while Present (Arg_Node) loop
14382                   Check_No_Identifier (Arg_Node);
14383
14384                   --  Note: the analyze call done by Check_Arg_Is_Local_Name
14385                   --  will in fact generate reference, so that the entity will
14386                   --  have a reference, which will inhibit any warnings about
14387                   --  it not being referenced, and also properly show up in the
14388                   --  ali file as a reference. But this reference is recorded
14389                   --  before the Has_Pragma_Unreferenced flag is set, so that
14390                   --  no warning is generated for this reference.
14391
14392                   Check_Arg_Is_Local_Name (Arg_Node);
14393                   Arg_Expr := Get_Pragma_Arg (Arg_Node);
14394
14395                   if Is_Entity_Name (Arg_Expr) then
14396                      Arg_Ent := Entity (Arg_Expr);
14397
14398                      --  If the entity is overloaded, the pragma applies to the
14399                      --  most recent overloading, as documented. In this case,
14400                      --  name resolution does not generate a reference, so it
14401                      --  must be done here explicitly.
14402
14403                      if Is_Overloaded (Arg_Expr) then
14404                         Generate_Reference (Arg_Ent, N);
14405                      end if;
14406
14407                      Set_Has_Pragma_Unreferenced (Arg_Ent);
14408                   end if;
14409
14410                   Next (Arg_Node);
14411                end loop;
14412             end if;
14413          end Unreferenced;
14414
14415          --------------------------
14416          -- Unreferenced_Objects --
14417          --------------------------
14418
14419          --  pragma Unreferenced_Objects (local_Name {, local_Name});
14420
14421          when Pragma_Unreferenced_Objects => Unreferenced_Objects : declare
14422             Arg_Node : Node_Id;
14423             Arg_Expr : Node_Id;
14424
14425          begin
14426             GNAT_Pragma;
14427             Check_At_Least_N_Arguments (1);
14428
14429             Arg_Node := Arg1;
14430             while Present (Arg_Node) loop
14431                Check_No_Identifier (Arg_Node);
14432                Check_Arg_Is_Local_Name (Arg_Node);
14433                Arg_Expr := Get_Pragma_Arg (Arg_Node);
14434
14435                if not Is_Entity_Name (Arg_Expr)
14436                  or else not Is_Type (Entity (Arg_Expr))
14437                then
14438                   Error_Pragma_Arg
14439                     ("argument for pragma% must be type or subtype", Arg_Node);
14440                end if;
14441
14442                Set_Has_Pragma_Unreferenced_Objects (Entity (Arg_Expr));
14443                Next (Arg_Node);
14444             end loop;
14445          end Unreferenced_Objects;
14446
14447          ------------------------------
14448          -- Unreserve_All_Interrupts --
14449          ------------------------------
14450
14451          --  pragma Unreserve_All_Interrupts;
14452
14453          when Pragma_Unreserve_All_Interrupts =>
14454             GNAT_Pragma;
14455             Check_Arg_Count (0);
14456
14457             if In_Extended_Main_Code_Unit (Main_Unit_Entity) then
14458                Unreserve_All_Interrupts := True;
14459             end if;
14460
14461          ----------------
14462          -- Unsuppress --
14463          ----------------
14464
14465          --  pragma Unsuppress (IDENTIFIER [, [On =>] NAME]);
14466
14467          when Pragma_Unsuppress =>
14468             Ada_2005_Pragma;
14469             Process_Suppress_Unsuppress (False);
14470
14471          -------------------
14472          -- Use_VADS_Size --
14473          -------------------
14474
14475          --  pragma Use_VADS_Size;
14476
14477          when Pragma_Use_VADS_Size =>
14478             GNAT_Pragma;
14479             Check_Arg_Count (0);
14480             Check_Valid_Configuration_Pragma;
14481             Use_VADS_Size := True;
14482
14483          ---------------------
14484          -- Validity_Checks --
14485          ---------------------
14486
14487          --  pragma Validity_Checks (On | Off | ALL_CHECKS | STRING_LITERAL);
14488
14489          when Pragma_Validity_Checks => Validity_Checks : declare
14490             A  : constant Node_Id   := Get_Pragma_Arg (Arg1);
14491             S  : String_Id;
14492             C  : Char_Code;
14493
14494          begin
14495             GNAT_Pragma;
14496             Check_Arg_Count (1);
14497             Check_No_Identifiers;
14498
14499             if Nkind (A) = N_String_Literal then
14500                S   := Strval (A);
14501
14502                declare
14503                   Slen    : constant Natural := Natural (String_Length (S));
14504                   Options : String (1 .. Slen);
14505                   J       : Natural;
14506
14507                begin
14508                   J := 1;
14509                   loop
14510                      C := Get_String_Char (S, Int (J));
14511                      exit when not In_Character_Range (C);
14512                      Options (J) := Get_Character (C);
14513
14514                      if J = Slen then
14515                         Set_Validity_Check_Options (Options);
14516                         exit;
14517                      else
14518                         J := J + 1;
14519                      end if;
14520                   end loop;
14521                end;
14522
14523             elsif Nkind (A) = N_Identifier then
14524                if Chars (A) = Name_All_Checks then
14525                   Set_Validity_Check_Options ("a");
14526                elsif Chars (A) = Name_On then
14527                   Validity_Checks_On := True;
14528                elsif Chars (A) = Name_Off then
14529                   Validity_Checks_On := False;
14530                end if;
14531             end if;
14532          end Validity_Checks;
14533
14534          --------------
14535          -- Volatile --
14536          --------------
14537
14538          --  pragma Volatile (LOCAL_NAME);
14539
14540          when Pragma_Volatile =>
14541             Process_Atomic_Shared_Volatile;
14542
14543          -------------------------
14544          -- Volatile_Components --
14545          -------------------------
14546
14547          --  pragma Volatile_Components (array_LOCAL_NAME);
14548
14549          --  Volatile is handled by the same circuit as Atomic_Components
14550
14551          --------------
14552          -- Warnings --
14553          --------------
14554
14555          --  pragma Warnings (On | Off);
14556          --  pragma Warnings (On | Off, LOCAL_NAME);
14557          --  pragma Warnings (static_string_EXPRESSION);
14558          --  pragma Warnings (On | Off, STRING_LITERAL);
14559
14560          when Pragma_Warnings => Warnings : begin
14561             GNAT_Pragma;
14562             Check_At_Least_N_Arguments (1);
14563             Check_No_Identifiers;
14564
14565             --  If debug flag -gnatd.i is set, pragma is ignored
14566
14567             if Debug_Flag_Dot_I then
14568                return;
14569             end if;
14570
14571             --  Process various forms of the pragma
14572
14573             declare
14574                Argx : constant Node_Id := Get_Pragma_Arg (Arg1);
14575
14576             begin
14577                --  One argument case
14578
14579                if Arg_Count = 1 then
14580
14581                   --  On/Off one argument case was processed by parser
14582
14583                   if Nkind (Argx) = N_Identifier
14584                     and then
14585                       (Chars (Argx) = Name_On
14586                          or else
14587                        Chars (Argx) = Name_Off)
14588                   then
14589                      null;
14590
14591                   --  One argument case must be ON/OFF or static string expr
14592
14593                   elsif not Is_Static_String_Expression (Arg1) then
14594                      Error_Pragma_Arg
14595                        ("argument of pragma% must be On/Off or " &
14596                         "static string expression", Arg1);
14597
14598                   --  One argument string expression case
14599
14600                   else
14601                      declare
14602                         Lit : constant Node_Id   := Expr_Value_S (Argx);
14603                         Str : constant String_Id := Strval (Lit);
14604                         Len : constant Nat       := String_Length (Str);
14605                         C   : Char_Code;
14606                         J   : Nat;
14607                         OK  : Boolean;
14608                         Chr : Character;
14609
14610                      begin
14611                         J := 1;
14612                         while J <= Len loop
14613                            C := Get_String_Char (Str, J);
14614                            OK := In_Character_Range (C);
14615
14616                            if OK then
14617                               Chr := Get_Character (C);
14618
14619                               --  Dot case
14620
14621                               if J < Len and then Chr = '.' then
14622                                  J := J + 1;
14623                                  C := Get_String_Char (Str, J);
14624                                  Chr := Get_Character (C);
14625
14626                                  if not Set_Dot_Warning_Switch (Chr) then
14627                                     Error_Pragma_Arg
14628                                       ("invalid warning switch character " &
14629                                        '.' & Chr, Arg1);
14630                                  end if;
14631
14632                               --  Non-Dot case
14633
14634                               else
14635                                  OK := Set_Warning_Switch (Chr);
14636                               end if;
14637                            end if;
14638
14639                            if not OK then
14640                               Error_Pragma_Arg
14641                                 ("invalid warning switch character " & Chr,
14642                                  Arg1);
14643                            end if;
14644
14645                            J := J + 1;
14646                         end loop;
14647                      end;
14648                   end if;
14649
14650                --  Two or more arguments (must be two)
14651
14652                else
14653                   Check_Arg_Is_One_Of (Arg1, Name_On, Name_Off);
14654                   Check_At_Most_N_Arguments (2);
14655
14656                   declare
14657                      E_Id : Node_Id;
14658                      E    : Entity_Id;
14659                      Err  : Boolean;
14660
14661                   begin
14662                      E_Id := Get_Pragma_Arg (Arg2);
14663                      Analyze (E_Id);
14664
14665                      --  In the expansion of an inlined body, a reference to
14666                      --  the formal may be wrapped in a conversion if the
14667                      --  actual is a conversion. Retrieve the real entity name.
14668
14669                      if (In_Instance_Body or In_Inlined_Body)
14670                        and then Nkind (E_Id) = N_Unchecked_Type_Conversion
14671                      then
14672                         E_Id := Expression (E_Id);
14673                      end if;
14674
14675                      --  Entity name case
14676
14677                      if Is_Entity_Name (E_Id) then
14678                         E := Entity (E_Id);
14679
14680                         if E = Any_Id then
14681                            return;
14682                         else
14683                            loop
14684                               Set_Warnings_Off
14685                                 (E, (Chars (Get_Pragma_Arg (Arg1)) =
14686                                                               Name_Off));
14687
14688                               if Chars (Get_Pragma_Arg (Arg1)) = Name_Off
14689                                 and then Warn_On_Warnings_Off
14690                               then
14691                                  Warnings_Off_Pragmas.Append ((N, E));
14692                               end if;
14693
14694                               if Is_Enumeration_Type (E) then
14695                                  declare
14696                                     Lit : Entity_Id;
14697                                  begin
14698                                     Lit := First_Literal (E);
14699                                     while Present (Lit) loop
14700                                        Set_Warnings_Off (Lit);
14701                                        Next_Literal (Lit);
14702                                     end loop;
14703                                  end;
14704                               end if;
14705
14706                               exit when No (Homonym (E));
14707                               E := Homonym (E);
14708                            end loop;
14709                         end if;
14710
14711                      --  Error if not entity or static string literal case
14712
14713                      elsif not Is_Static_String_Expression (Arg2) then
14714                         Error_Pragma_Arg
14715                           ("second argument of pragma% must be entity " &
14716                            "name or static string expression", Arg2);
14717
14718                      --  String literal case
14719
14720                      else
14721                         String_To_Name_Buffer
14722                           (Strval (Expr_Value_S (Get_Pragma_Arg (Arg2))));
14723
14724                         --  Note on configuration pragma case: If this is a
14725                         --  configuration pragma, then for an OFF pragma, we
14726                         --  just set Config True in the call, which is all
14727                         --  that needs to be done. For the case of ON, this
14728                         --  is normally an error, unless it is canceling the
14729                         --  effect of a previous OFF pragma in the same file.
14730                         --  In any other case, an error will be signalled (ON
14731                         --  with no matching OFF).
14732
14733                         --  Note: We set Used if we are inside a generic to
14734                         --  disable the test that the non-config case actually
14735                         --  cancels a warning. That's because we can't be sure
14736                         --  there isn't an instantiation in some other unit
14737                         --  where a warning is suppressed.
14738
14739                         --  We could do a little better here by checking if the
14740                         --  generic unit we are inside is public, but for now
14741                         --  we don't bother with that refinement.
14742
14743                         if Chars (Argx) = Name_Off then
14744                            Set_Specific_Warning_Off
14745                              (Loc, Name_Buffer (1 .. Name_Len),
14746                               Config => Is_Configuration_Pragma,
14747                               Used   => Inside_A_Generic or else In_Instance);
14748
14749                         elsif Chars (Argx) = Name_On then
14750                            Set_Specific_Warning_On
14751                              (Loc, Name_Buffer (1 .. Name_Len), Err);
14752
14753                            if Err then
14754                               Error_Msg
14755                                 ("?pragma Warnings On with no " &
14756                                  "matching Warnings Off",
14757                                  Loc);
14758                            end if;
14759                         end if;
14760                      end if;
14761                   end;
14762                end if;
14763             end;
14764          end Warnings;
14765
14766          -------------------
14767          -- Weak_External --
14768          -------------------
14769
14770          --  pragma Weak_External ([Entity =>] LOCAL_NAME);
14771
14772          when Pragma_Weak_External => Weak_External : declare
14773             Ent : Entity_Id;
14774
14775          begin
14776             GNAT_Pragma;
14777             Check_Arg_Count (1);
14778             Check_Optional_Identifier (Arg1, Name_Entity);
14779             Check_Arg_Is_Library_Level_Local_Name (Arg1);
14780             Ent := Entity (Get_Pragma_Arg (Arg1));
14781
14782             if Rep_Item_Too_Early (Ent, N) then
14783                return;
14784             else
14785                Ent := Underlying_Type (Ent);
14786             end if;
14787
14788             --  The only processing required is to link this item on to the
14789             --  list of rep items for the given entity. This is accomplished
14790             --  by the call to Rep_Item_Too_Late (when no error is detected
14791             --  and False is returned).
14792
14793             if Rep_Item_Too_Late (Ent, N) then
14794                return;
14795             else
14796                Set_Has_Gigi_Rep_Item (Ent);
14797             end if;
14798          end Weak_External;
14799
14800          -----------------------------
14801          -- Wide_Character_Encoding --
14802          -----------------------------
14803
14804          --  pragma Wide_Character_Encoding (IDENTIFIER);
14805
14806          when Pragma_Wide_Character_Encoding =>
14807             GNAT_Pragma;
14808
14809             --  Nothing to do, handled in parser. Note that we do not enforce
14810             --  configuration pragma placement, this pragma can appear at any
14811             --  place in the source, allowing mixed encodings within a single
14812             --  source program.
14813
14814             null;
14815
14816          --------------------
14817          -- Unknown_Pragma --
14818          --------------------
14819
14820          --  Should be impossible, since the case of an unknown pragma is
14821          --  separately processed before the case statement is entered.
14822
14823          when Unknown_Pragma =>
14824             raise Program_Error;
14825       end case;
14826
14827       --  AI05-0144: detect dangerous order dependence. Disabled for now,
14828       --  until AI is formally approved.
14829
14830       --  Check_Order_Dependence;
14831
14832    exception
14833       when Pragma_Exit => null;
14834    end Analyze_Pragma;
14835
14836    -----------------------------
14837    -- Analyze_TC_In_Decl_Part --
14838    -----------------------------
14839
14840    procedure Analyze_TC_In_Decl_Part (N : Node_Id; S : Entity_Id) is
14841    begin
14842       --  Install formals and push subprogram spec onto scope stack so that we
14843       --  can see the formals from the pragma.
14844
14845       Install_Formals (S);
14846       Push_Scope (S);
14847
14848       --  Preanalyze the boolean expressions, we treat these as spec
14849       --  expressions (i.e. similar to a default expression).
14850
14851       Preanalyze_TC_Args (N,
14852                           Get_Requires_From_Test_Case_Pragma (N),
14853                           Get_Ensures_From_Test_Case_Pragma (N));
14854
14855       --  Remove the subprogram from the scope stack now that the pre-analysis
14856       --  of the expressions in the test-case is done.
14857
14858       End_Scope;
14859    end Analyze_TC_In_Decl_Part;
14860
14861    --------------------
14862    -- Check_Disabled --
14863    --------------------
14864
14865    function Check_Disabled (Nam : Name_Id) return Boolean is
14866       PP : Node_Id;
14867
14868    begin
14869       --  Loop through entries in check policy list
14870
14871       PP := Opt.Check_Policy_List;
14872       loop
14873          --  If there are no specific entries that matched, then nothing is
14874          --  disabled, so return False.
14875
14876          if No (PP) then
14877             return False;
14878
14879          --  Here we have an entry see if it matches
14880
14881          else
14882             declare
14883                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14884             begin
14885                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14886                   return Chars (Get_Pragma_Arg (Last (PPA))) = Name_Disable;
14887                else
14888                   PP := Next_Pragma (PP);
14889                end if;
14890             end;
14891          end if;
14892       end loop;
14893    end Check_Disabled;
14894
14895    -------------------
14896    -- Check_Enabled --
14897    -------------------
14898
14899    function Check_Enabled (Nam : Name_Id) return Boolean is
14900       PP : Node_Id;
14901
14902    begin
14903       --  Loop through entries in check policy list
14904
14905       PP := Opt.Check_Policy_List;
14906       loop
14907          --  If there are no specific entries that matched, then we let the
14908          --  setting of assertions govern. Note that this provides the needed
14909          --  compatibility with the RM for the cases of assertion, invariant,
14910          --  precondition, predicate, and postcondition.
14911
14912          if No (PP) then
14913             return Assertions_Enabled;
14914
14915          --  Here we have an entry see if it matches
14916
14917          else
14918             declare
14919                PPA : constant List_Id := Pragma_Argument_Associations (PP);
14920
14921             begin
14922                if Nam = Chars (Get_Pragma_Arg (First (PPA))) then
14923                   case (Chars (Get_Pragma_Arg (Last (PPA)))) is
14924                      when Name_On | Name_Check =>
14925                         return True;
14926                      when Name_Off | Name_Ignore =>
14927                         return False;
14928                      when others =>
14929                         raise Program_Error;
14930                   end case;
14931
14932                else
14933                   PP := Next_Pragma (PP);
14934                end if;
14935             end;
14936          end if;
14937       end loop;
14938    end Check_Enabled;
14939
14940    ---------------------------------
14941    -- Delay_Config_Pragma_Analyze --
14942    ---------------------------------
14943
14944    function Delay_Config_Pragma_Analyze (N : Node_Id) return Boolean is
14945    begin
14946       return Pragma_Name (N) = Name_Interrupt_State
14947                or else
14948              Pragma_Name (N) = Name_Priority_Specific_Dispatching;
14949    end Delay_Config_Pragma_Analyze;
14950
14951    -------------------------
14952    -- Get_Base_Subprogram --
14953    -------------------------
14954
14955    function Get_Base_Subprogram (Def_Id : Entity_Id) return Entity_Id is
14956       Result : Entity_Id;
14957
14958    begin
14959       --  Follow subprogram renaming chain
14960
14961       Result := Def_Id;
14962
14963       if Is_Subprogram (Result)
14964         and then
14965           Nkind (Parent (Declaration_Node (Result))) =
14966                                          N_Subprogram_Renaming_Declaration
14967         and then Present (Alias (Result))
14968       then
14969          Result := Alias (Result);
14970       end if;
14971
14972       return Result;
14973    end Get_Base_Subprogram;
14974
14975    ----------------
14976    -- Initialize --
14977    ----------------
14978
14979    procedure Initialize is
14980    begin
14981       Externals.Init;
14982    end Initialize;
14983
14984    -----------------------------
14985    -- Is_Config_Static_String --
14986    -----------------------------
14987
14988    function Is_Config_Static_String (Arg : Node_Id) return Boolean is
14989
14990       function Add_Config_Static_String (Arg : Node_Id) return Boolean;
14991       --  This is an internal recursive function that is just like the outer
14992       --  function except that it adds the string to the name buffer rather
14993       --  than placing the string in the name buffer.
14994
14995       ------------------------------
14996       -- Add_Config_Static_String --
14997       ------------------------------
14998
14999       function Add_Config_Static_String (Arg : Node_Id) return Boolean is
15000          N : Node_Id;
15001          C : Char_Code;
15002
15003       begin
15004          N := Arg;
15005
15006          if Nkind (N) = N_Op_Concat then
15007             if Add_Config_Static_String (Left_Opnd (N)) then
15008                N := Right_Opnd (N);
15009             else
15010                return False;
15011             end if;
15012          end if;
15013
15014          if Nkind (N) /= N_String_Literal then
15015             Error_Msg_N ("string literal expected for pragma argument", N);
15016             return False;
15017
15018          else
15019             for J in 1 .. String_Length (Strval (N)) loop
15020                C := Get_String_Char (Strval (N), J);
15021
15022                if not In_Character_Range (C) then
15023                   Error_Msg
15024                     ("string literal contains invalid wide character",
15025                      Sloc (N) + 1 + Source_Ptr (J));
15026                   return False;
15027                end if;
15028
15029                Add_Char_To_Name_Buffer (Get_Character (C));
15030             end loop;
15031          end if;
15032
15033          return True;
15034       end Add_Config_Static_String;
15035
15036    --  Start of processing for Is_Config_Static_String
15037
15038    begin
15039
15040       Name_Len := 0;
15041       return Add_Config_Static_String (Arg);
15042    end Is_Config_Static_String;
15043
15044    -----------------------------------------
15045    -- Is_Non_Significant_Pragma_Reference --
15046    -----------------------------------------
15047
15048    --  This function makes use of the following static table which indicates
15049    --  whether appearance of some name in a given pragma is to be considered
15050    --  as a reference for the purposes of warnings about unreferenced objects.
15051
15052    --  -1  indicates that references in any argument position are significant
15053    --  0   indicates that appearance in any argument is not significant
15054    --  +n  indicates that appearance as argument n is significant, but all
15055    --      other arguments are not significant
15056    --  99  special processing required (e.g. for pragma Check)
15057
15058    Sig_Flags : constant array (Pragma_Id) of Int :=
15059      (Pragma_AST_Entry                      => -1,
15060       Pragma_Abort_Defer                    => -1,
15061       Pragma_Ada_83                         => -1,
15062       Pragma_Ada_95                         => -1,
15063       Pragma_Ada_05                         => -1,
15064       Pragma_Ada_2005                       => -1,
15065       Pragma_Ada_12                         => -1,
15066       Pragma_Ada_2012                       => -1,
15067       Pragma_All_Calls_Remote               => -1,
15068       Pragma_Annotate                       => -1,
15069       Pragma_Assert                         => -1,
15070       Pragma_Assertion_Policy               =>  0,
15071       Pragma_Assume_No_Invalid_Values       =>  0,
15072       Pragma_Asynchronous                   => -1,
15073       Pragma_Atomic                         =>  0,
15074       Pragma_Atomic_Components              =>  0,
15075       Pragma_Attach_Handler                 => -1,
15076       Pragma_Check                          => 99,
15077       Pragma_Check_Name                     =>  0,
15078       Pragma_Check_Policy                   =>  0,
15079       Pragma_CIL_Constructor                => -1,
15080       Pragma_CPP_Class                      =>  0,
15081       Pragma_CPP_Constructor                =>  0,
15082       Pragma_CPP_Virtual                    =>  0,
15083       Pragma_CPP_Vtable                     =>  0,
15084       Pragma_CPU                            => -1,
15085       Pragma_C_Pass_By_Copy                 =>  0,
15086       Pragma_Comment                        =>  0,
15087       Pragma_Common_Object                  => -1,
15088       Pragma_Compile_Time_Error             => -1,
15089       Pragma_Compile_Time_Warning           => -1,
15090       Pragma_Compiler_Unit                  =>  0,
15091       Pragma_Complete_Representation        =>  0,
15092       Pragma_Complex_Representation         =>  0,
15093       Pragma_Component_Alignment            => -1,
15094       Pragma_Controlled                     =>  0,
15095       Pragma_Convention                     =>  0,
15096       Pragma_Convention_Identifier          =>  0,
15097       Pragma_Debug                          => -1,
15098       Pragma_Debug_Policy                   =>  0,
15099       Pragma_Detect_Blocking                => -1,
15100       Pragma_Default_Storage_Pool           => -1,
15101       Pragma_Disable_Atomic_Synchronization => -1,
15102       Pragma_Discard_Names                  =>  0,
15103       Pragma_Dispatching_Domain             => -1,
15104       Pragma_Elaborate                      => -1,
15105       Pragma_Elaborate_All                  => -1,
15106       Pragma_Elaborate_Body                 => -1,
15107       Pragma_Elaboration_Checks             => -1,
15108       Pragma_Eliminate                      => -1,
15109       Pragma_Enable_Atomic_Synchronization  => -1,
15110       Pragma_Export                         => -1,
15111       Pragma_Export_Exception               => -1,
15112       Pragma_Export_Function                => -1,
15113       Pragma_Export_Object                  => -1,
15114       Pragma_Export_Procedure               => -1,
15115       Pragma_Export_Value                   => -1,
15116       Pragma_Export_Valued_Procedure        => -1,
15117       Pragma_Extend_System                  => -1,
15118       Pragma_Extensions_Allowed             => -1,
15119       Pragma_External                       => -1,
15120       Pragma_Favor_Top_Level                => -1,
15121       Pragma_External_Name_Casing           => -1,
15122       Pragma_Fast_Math                      => -1,
15123       Pragma_Finalize_Storage_Only          =>  0,
15124       Pragma_Float_Representation           =>  0,
15125       Pragma_Ident                          => -1,
15126       Pragma_Implementation_Defined         => -1,
15127       Pragma_Implemented                    => -1,
15128       Pragma_Implicit_Packing               =>  0,
15129       Pragma_Import                         => +2,
15130       Pragma_Import_Exception               =>  0,
15131       Pragma_Import_Function                =>  0,
15132       Pragma_Import_Object                  =>  0,
15133       Pragma_Import_Procedure               =>  0,
15134       Pragma_Import_Valued_Procedure        =>  0,
15135       Pragma_Independent                    =>  0,
15136       Pragma_Independent_Components         =>  0,
15137       Pragma_Initialize_Scalars             => -1,
15138       Pragma_Inline                         =>  0,
15139       Pragma_Inline_Always                  =>  0,
15140       Pragma_Inline_Generic                 =>  0,
15141       Pragma_Inspection_Point               => -1,
15142       Pragma_Interface                      => +2,
15143       Pragma_Interface_Name                 => +2,
15144       Pragma_Interrupt_Handler              => -1,
15145       Pragma_Interrupt_Priority             => -1,
15146       Pragma_Interrupt_State                => -1,
15147       Pragma_Invariant                      => -1,
15148       Pragma_Java_Constructor               => -1,
15149       Pragma_Java_Interface                 => -1,
15150       Pragma_Keep_Names                     =>  0,
15151       Pragma_License                        => -1,
15152       Pragma_Link_With                      => -1,
15153       Pragma_Linker_Alias                   => -1,
15154       Pragma_Linker_Constructor             => -1,
15155       Pragma_Linker_Destructor              => -1,
15156       Pragma_Linker_Options                 => -1,
15157       Pragma_Linker_Section                 => -1,
15158       Pragma_List                           => -1,
15159       Pragma_Locking_Policy                 => -1,
15160       Pragma_Long_Float                     => -1,
15161       Pragma_Machine_Attribute              => -1,
15162       Pragma_Main                           => -1,
15163       Pragma_Main_Storage                   => -1,
15164       Pragma_Memory_Size                    => -1,
15165       Pragma_No_Return                      =>  0,
15166       Pragma_No_Body                        =>  0,
15167       Pragma_No_Run_Time                    => -1,
15168       Pragma_No_Strict_Aliasing             => -1,
15169       Pragma_Normalize_Scalars              => -1,
15170       Pragma_Obsolescent                    =>  0,
15171       Pragma_Optimize                       => -1,
15172       Pragma_Optimize_Alignment             => -1,
15173       Pragma_Ordered                        =>  0,
15174       Pragma_Pack                           =>  0,
15175       Pragma_Page                           => -1,
15176       Pragma_Passive                        => -1,
15177       Pragma_Preelaborable_Initialization   => -1,
15178       Pragma_Polling                        => -1,
15179       Pragma_Persistent_BSS                 =>  0,
15180       Pragma_Postcondition                  => -1,
15181       Pragma_Precondition                   => -1,
15182       Pragma_Predicate                      => -1,
15183       Pragma_Preelaborate                   => -1,
15184       Pragma_Preelaborate_05                => -1,
15185       Pragma_Priority                       => -1,
15186       Pragma_Priority_Specific_Dispatching  => -1,
15187       Pragma_Profile                        =>  0,
15188       Pragma_Profile_Warnings               =>  0,
15189       Pragma_Propagate_Exceptions           => -1,
15190       Pragma_Psect_Object                   => -1,
15191       Pragma_Pure                           => -1,
15192       Pragma_Pure_05                        => -1,
15193       Pragma_Pure_12                        => -1,
15194       Pragma_Pure_Function                  => -1,
15195       Pragma_Queuing_Policy                 => -1,
15196       Pragma_Ravenscar                      => -1,
15197       Pragma_Relative_Deadline              => -1,
15198       Pragma_Remote_Access_Type             => -1,
15199       Pragma_Remote_Call_Interface          => -1,
15200       Pragma_Remote_Types                   => -1,
15201       Pragma_Restricted_Run_Time            => -1,
15202       Pragma_Restriction_Warnings           => -1,
15203       Pragma_Restrictions                   => -1,
15204       Pragma_Reviewable                     => -1,
15205       Pragma_Short_Circuit_And_Or           => -1,
15206       Pragma_Share_Generic                  => -1,
15207       Pragma_Shared                         => -1,
15208       Pragma_Shared_Passive                 => -1,
15209       Pragma_Short_Descriptors              =>  0,
15210       Pragma_Simple_Storage_Pool_Type       =>  0,
15211       Pragma_Source_File_Name               => -1,
15212       Pragma_Source_File_Name_Project       => -1,
15213       Pragma_Source_Reference               => -1,
15214       Pragma_Storage_Size                   => -1,
15215       Pragma_Storage_Unit                   => -1,
15216       Pragma_Static_Elaboration_Desired     => -1,
15217       Pragma_Stream_Convert                 => -1,
15218       Pragma_Style_Checks                   => -1,
15219       Pragma_Subtitle                       => -1,
15220       Pragma_Suppress                       =>  0,
15221       Pragma_Suppress_Exception_Locations   =>  0,
15222       Pragma_Suppress_All                   => -1,
15223       Pragma_Suppress_Debug_Info            =>  0,
15224       Pragma_Suppress_Initialization        =>  0,
15225       Pragma_System_Name                    => -1,
15226       Pragma_Task_Dispatching_Policy        => -1,
15227       Pragma_Task_Info                      => -1,
15228       Pragma_Task_Name                      => -1,
15229       Pragma_Task_Storage                   =>  0,
15230       Pragma_Test_Case                      => -1,
15231       Pragma_Thread_Local_Storage           =>  0,
15232       Pragma_Time_Slice                     => -1,
15233       Pragma_Title                          => -1,
15234       Pragma_Unchecked_Union                =>  0,
15235       Pragma_Unimplemented_Unit             => -1,
15236       Pragma_Universal_Aliasing             => -1,
15237       Pragma_Universal_Data                 => -1,
15238       Pragma_Unmodified                     => -1,
15239       Pragma_Unreferenced                   => -1,
15240       Pragma_Unreferenced_Objects           => -1,
15241       Pragma_Unreserve_All_Interrupts       => -1,
15242       Pragma_Unsuppress                     =>  0,
15243       Pragma_Use_VADS_Size                  => -1,
15244       Pragma_Validity_Checks                => -1,
15245       Pragma_Volatile                       =>  0,
15246       Pragma_Volatile_Components            =>  0,
15247       Pragma_Warnings                       => -1,
15248       Pragma_Weak_External                  => -1,
15249       Pragma_Wide_Character_Encoding        =>  0,
15250       Unknown_Pragma                        =>  0);
15251
15252    function Is_Non_Significant_Pragma_Reference (N : Node_Id) return Boolean is
15253       Id : Pragma_Id;
15254       P  : Node_Id;
15255       C  : Int;
15256       A  : Node_Id;
15257
15258    begin
15259       P := Parent (N);
15260
15261       if Nkind (P) /= N_Pragma_Argument_Association then
15262          return False;
15263
15264       else
15265          Id := Get_Pragma_Id (Parent (P));
15266          C := Sig_Flags (Id);
15267
15268          case C is
15269             when -1 =>
15270                return False;
15271
15272             when 0 =>
15273                return True;
15274
15275             when 99 =>
15276                case Id is
15277
15278                   --  For pragma Check, the first argument is not significant,
15279                   --  the second and the third (if present) arguments are
15280                   --  significant.
15281
15282                   when Pragma_Check =>
15283                      return
15284                        P = First (Pragma_Argument_Associations (Parent (P)));
15285
15286                   when others =>
15287                      raise Program_Error;
15288                end case;
15289
15290             when others =>
15291                A := First (Pragma_Argument_Associations (Parent (P)));
15292                for J in 1 .. C - 1 loop
15293                   if No (A) then
15294                      return False;
15295                   end if;
15296
15297                   Next (A);
15298                end loop;
15299
15300                return A = P; -- is this wrong way round ???
15301          end case;
15302       end if;
15303    end Is_Non_Significant_Pragma_Reference;
15304
15305    ------------------------------
15306    -- Is_Pragma_String_Literal --
15307    ------------------------------
15308
15309    --  This function returns true if the corresponding pragma argument is a
15310    --  static string expression. These are the only cases in which string
15311    --  literals can appear as pragma arguments. We also allow a string literal
15312    --  as the first argument to pragma Assert (although it will of course
15313    --  always generate a type error).
15314
15315    function Is_Pragma_String_Literal (Par : Node_Id) return Boolean is
15316       Pragn : constant Node_Id := Parent (Par);
15317       Assoc : constant List_Id := Pragma_Argument_Associations (Pragn);
15318       Pname : constant Name_Id := Pragma_Name (Pragn);
15319       Argn  : Natural;
15320       N     : Node_Id;
15321
15322    begin
15323       Argn := 1;
15324       N := First (Assoc);
15325       loop
15326          exit when N = Par;
15327          Argn := Argn + 1;
15328          Next (N);
15329       end loop;
15330
15331       if Pname = Name_Assert then
15332          return True;
15333
15334       elsif Pname = Name_Export then
15335          return Argn > 2;
15336
15337       elsif Pname = Name_Ident then
15338          return Argn = 1;
15339
15340       elsif Pname = Name_Import then
15341          return Argn > 2;
15342
15343       elsif Pname = Name_Interface_Name then
15344          return Argn > 1;
15345
15346       elsif Pname = Name_Linker_Alias then
15347          return Argn = 2;
15348
15349       elsif Pname = Name_Linker_Section then
15350          return Argn = 2;
15351
15352       elsif Pname = Name_Machine_Attribute then
15353          return Argn = 2;
15354
15355       elsif Pname = Name_Source_File_Name then
15356          return True;
15357
15358       elsif Pname = Name_Source_Reference then
15359          return Argn = 2;
15360
15361       elsif Pname = Name_Title then
15362          return True;
15363
15364       elsif Pname = Name_Subtitle then
15365          return True;
15366
15367       else
15368          return False;
15369       end if;
15370    end Is_Pragma_String_Literal;
15371
15372    -----------------------------------------
15373    -- Make_Aspect_For_PPC_In_Gen_Sub_Decl --
15374    -----------------------------------------
15375
15376    procedure Make_Aspect_For_PPC_In_Gen_Sub_Decl (Decl : Node_Id) is
15377       Aspects : constant List_Id := New_List;
15378       Loc     : constant Source_Ptr := Sloc (Decl);
15379       Or_Decl : constant Node_Id := Original_Node (Decl);
15380
15381       Original_Aspects : List_Id;
15382       --  To capture global references, a copy of the created aspects must be
15383       --  inserted in the original tree.
15384
15385       Prag         : Node_Id;
15386       Prag_Arg_Ass : Node_Id;
15387       Prag_Id      : Pragma_Id;
15388
15389    begin
15390       --  Check for any PPC pragmas that appear within Decl
15391
15392       Prag := Next (Decl);
15393       while Nkind (Prag) = N_Pragma loop
15394          Prag_Id := Get_Pragma_Id (Chars (Pragma_Identifier (Prag)));
15395
15396          case Prag_Id is
15397             when Pragma_Postcondition | Pragma_Precondition =>
15398                Prag_Arg_Ass := First (Pragma_Argument_Associations (Prag));
15399
15400                --  Make an aspect from any PPC pragma
15401
15402                Append_To (Aspects,
15403                  Make_Aspect_Specification (Loc,
15404                    Identifier =>
15405                      Make_Identifier (Loc, Chars (Pragma_Identifier (Prag))),
15406                    Expression =>
15407                      Copy_Separate_Tree (Expression (Prag_Arg_Ass))));
15408
15409                --  Generate the analysis information in the pragma expression
15410                --  and then set the pragma node analyzed to avoid any further
15411                --  analysis.
15412
15413                Analyze (Expression (Prag_Arg_Ass));
15414                Set_Analyzed (Prag, True);
15415
15416             when others => null;
15417          end case;
15418
15419          Next (Prag);
15420       end loop;
15421
15422       --  Set all new aspects into the generic declaration node
15423
15424       if Is_Non_Empty_List (Aspects) then
15425
15426          --  Create the list of aspects to be inserted in the original tree
15427
15428          Original_Aspects := Copy_Separate_List (Aspects);
15429
15430          --  Check if Decl already has aspects
15431
15432          --  Attach the new lists of aspects to both the generic copy and the
15433          --  original tree.
15434
15435          if Has_Aspects (Decl) then
15436             Append_List (Aspects, Aspect_Specifications (Decl));
15437             Append_List (Original_Aspects, Aspect_Specifications (Or_Decl));
15438
15439          else
15440             Set_Parent (Aspects, Decl);
15441             Set_Aspect_Specifications (Decl, Aspects);
15442             Set_Parent (Original_Aspects, Or_Decl);
15443             Set_Aspect_Specifications (Or_Decl, Original_Aspects);
15444          end if;
15445       end if;
15446    end Make_Aspect_For_PPC_In_Gen_Sub_Decl;
15447
15448    ------------------------
15449    -- Preanalyze_TC_Args --
15450    ------------------------
15451
15452    procedure Preanalyze_TC_Args (N, Arg_Req, Arg_Ens : Node_Id) is
15453    begin
15454       --  Preanalyze the boolean expressions, we treat these as spec
15455       --  expressions (i.e. similar to a default expression).
15456
15457       if Present (Arg_Req) then
15458          Preanalyze_Spec_Expression
15459            (Get_Pragma_Arg (Arg_Req), Standard_Boolean);
15460
15461          --  In ASIS mode, for a pragma generated from a source aspect, also
15462          --  analyze the original aspect expression.
15463
15464          if ASIS_Mode and then Present (Corresponding_Aspect (N)) then
15465             Preanalyze_Spec_Expression
15466               (Original_Node (Get_Pragma_Arg (Arg_Req)), Standard_Boolean);
15467          end if;
15468       end if;
15469
15470       if Present (Arg_Ens) then
15471          Preanalyze_Spec_Expression
15472            (Get_Pragma_Arg (Arg_Ens), Standard_Boolean);
15473
15474          --  In ASIS mode, for a pragma generated from a source aspect, also
15475          --  analyze the original aspect expression.
15476
15477          if ASIS_Mode and then Present (Corresponding_Aspect (N)) then
15478             Preanalyze_Spec_Expression
15479               (Original_Node (Get_Pragma_Arg (Arg_Ens)), Standard_Boolean);
15480          end if;
15481       end if;
15482    end Preanalyze_TC_Args;
15483
15484    --------------------------------------
15485    -- Process_Compilation_Unit_Pragmas --
15486    --------------------------------------
15487
15488    procedure Process_Compilation_Unit_Pragmas (N : Node_Id) is
15489    begin
15490       --  A special check for pragma Suppress_All, a very strange DEC pragma,
15491       --  strange because it comes at the end of the unit. Rational has the
15492       --  same name for a pragma, but treats it as a program unit pragma, In
15493       --  GNAT we just decide to allow it anywhere at all. If it appeared then
15494       --  the flag Has_Pragma_Suppress_All was set on the compilation unit
15495       --  node, and we insert a pragma Suppress (All_Checks) at the start of
15496       --  the context clause to ensure the correct processing.
15497
15498       if Has_Pragma_Suppress_All (N) then
15499          Prepend_To (Context_Items (N),
15500            Make_Pragma (Sloc (N),
15501              Chars                        => Name_Suppress,
15502              Pragma_Argument_Associations => New_List (
15503                Make_Pragma_Argument_Association (Sloc (N),
15504                  Expression => Make_Identifier (Sloc (N), Name_All_Checks)))));
15505       end if;
15506
15507       --  Nothing else to do at the current time!
15508
15509    end Process_Compilation_Unit_Pragmas;
15510
15511    --------
15512    -- rv --
15513    --------
15514
15515    procedure rv is
15516    begin
15517       null;
15518    end rv;
15519
15520    --------------------------------
15521    -- Set_Encoded_Interface_Name --
15522    --------------------------------
15523
15524    procedure Set_Encoded_Interface_Name (E : Entity_Id; S : Node_Id) is
15525       Str : constant String_Id := Strval (S);
15526       Len : constant Int       := String_Length (Str);
15527       CC  : Char_Code;
15528       C   : Character;
15529       J   : Int;
15530
15531       Hex : constant array (0 .. 15) of Character := "0123456789abcdef";
15532
15533       procedure Encode;
15534       --  Stores encoded value of character code CC. The encoding we use an
15535       --  underscore followed by four lower case hex digits.
15536
15537       ------------
15538       -- Encode --
15539       ------------
15540
15541       procedure Encode is
15542       begin
15543          Store_String_Char (Get_Char_Code ('_'));
15544          Store_String_Char
15545            (Get_Char_Code (Hex (Integer (CC / 2 ** 12))));
15546          Store_String_Char
15547            (Get_Char_Code (Hex (Integer (CC / 2 ** 8 and 16#0F#))));
15548          Store_String_Char
15549            (Get_Char_Code (Hex (Integer (CC / 2 ** 4 and 16#0F#))));
15550          Store_String_Char
15551            (Get_Char_Code (Hex (Integer (CC and 16#0F#))));
15552       end Encode;
15553
15554    --  Start of processing for Set_Encoded_Interface_Name
15555
15556    begin
15557       --  If first character is asterisk, this is a link name, and we leave it
15558       --  completely unmodified. We also ignore null strings (the latter case
15559       --  happens only in error cases) and no encoding should occur for Java or
15560       --  AAMP interface names.
15561
15562       if Len = 0
15563         or else Get_String_Char (Str, 1) = Get_Char_Code ('*')
15564         or else VM_Target /= No_VM
15565         or else AAMP_On_Target
15566       then
15567          Set_Interface_Name (E, S);
15568
15569       else
15570          J := 1;
15571          loop
15572             CC := Get_String_Char (Str, J);
15573
15574             exit when not In_Character_Range (CC);
15575
15576             C := Get_Character (CC);
15577
15578             exit when C /= '_' and then C /= '$'
15579               and then C not in '0' .. '9'
15580               and then C not in 'a' .. 'z'
15581               and then C not in 'A' .. 'Z';
15582
15583             if J = Len then
15584                Set_Interface_Name (E, S);
15585                return;
15586
15587             else
15588                J := J + 1;
15589             end if;
15590          end loop;
15591
15592          --  Here we need to encode. The encoding we use as follows:
15593          --     three underscores  + four hex digits (lower case)
15594
15595          Start_String;
15596
15597          for J in 1 .. String_Length (Str) loop
15598             CC := Get_String_Char (Str, J);
15599
15600             if not In_Character_Range (CC) then
15601                Encode;
15602             else
15603                C := Get_Character (CC);
15604
15605                if C = '_' or else C = '$'
15606                  or else C in '0' .. '9'
15607                  or else C in 'a' .. 'z'
15608                  or else C in 'A' .. 'Z'
15609                then
15610                   Store_String_Char (CC);
15611                else
15612                   Encode;
15613                end if;
15614             end if;
15615          end loop;
15616
15617          Set_Interface_Name (E,
15618            Make_String_Literal (Sloc (S),
15619              Strval => End_String));
15620       end if;
15621    end Set_Encoded_Interface_Name;
15622
15623    -------------------
15624    -- Set_Unit_Name --
15625    -------------------
15626
15627    procedure Set_Unit_Name (N : Node_Id; With_Item : Node_Id) is
15628       Pref : Node_Id;
15629       Scop : Entity_Id;
15630
15631    begin
15632       if Nkind (N) = N_Identifier
15633         and then Nkind (With_Item) = N_Identifier
15634       then
15635          Set_Entity (N, Entity (With_Item));
15636
15637       elsif Nkind (N) = N_Selected_Component then
15638          Change_Selected_Component_To_Expanded_Name (N);
15639          Set_Entity (N, Entity (With_Item));
15640          Set_Entity (Selector_Name (N), Entity (N));
15641
15642          Pref := Prefix (N);
15643          Scop := Scope (Entity (N));
15644          while Nkind (Pref) = N_Selected_Component loop
15645             Change_Selected_Component_To_Expanded_Name (Pref);
15646             Set_Entity (Selector_Name (Pref), Scop);
15647             Set_Entity (Pref, Scop);
15648             Pref := Prefix (Pref);
15649             Scop := Scope (Scop);
15650          end loop;
15651
15652          Set_Entity (Pref, Scop);
15653       end if;
15654    end Set_Unit_Name;
15655
15656 end Sem_Prag;